This is a rather fun patch (imo) that lets runghc read from stdin (into
a temp file) if no filename is provided.
It means this works,
$ cat A.hs | runghc | python2.4| ruby | runghc | python2.4 | ruby
Where A.hs is sigfpe's 3rd order quine,
http://sigfpe.blogspot.com/2008/02/third-order-quine-in-three-languages.html
-- Don
New patches:
[Have runghc read from stdin, if no filename provided
Don Stewart <[EMAIL PROTECTED]>**20080206041851
As for ruby, perl, python, read from stdin (into a temp file), if no
filename provided. Let's cute meta-quines work:
$ runghc A.hs | python | ruby | runghc
Also, more mundane:
$ echo 'main = print "woot"' | runghc
"woot"
] {
hunk ./utils/runghc/runghc.hs 26
+import Control.Exception
hunk ./utils/runghc/runghc.hs 34
-import Compat.Directory ( findExecutable )
+import Compat.Directory ( findExecutable, removeFile )
hunk ./utils/runghc/runghc.hs 37
-import System.Directory ( findExecutable )
+import System.Directory ( findExecutable, removeFile )
hunk ./utils/runghc/runghc.hs 63
- [] -> dieProg usage
+ [] -> do
+ -- behave like typical perl, python, ruby interpreters: read from
stdin
+ (filename,h) <- openTempFile "/tmp" "runghcXXXX.hs"
+ getContents >>= hPutStr h
+ hFlush h
+ hClose h
+ finally
+ (doIt ghc (ghc_args ++ [filename]))
+ (removeFile filename)
+
}
Context:
[clean ghci-inplace
Simon Marlow <[EMAIL PROTECTED]>**20071031093932]
[clean Haddock droppings
Simon Marlow <[EMAIL PROTECTED]>**20071031093923]
[Fix warning in OSMem for darwin
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071030133003]
[FIX BUILD: a glitch in the new rules and inlining stuff
[EMAIL PROTECTED]
Don't re-add the worker info to a binder until completeBind. It's not
needed in its own RHS, and it may be replaced, via the substitution
following postInlineUnconditionally.
(Fixes build of the stage2 compiler which fell over when Coercion.lhs
was being compiled.)
]
[Fix LiberateCase
[EMAIL PROTECTED]
Merge to STABLE please
Liberate case was being far too gung-ho about what to specialise. This
bug only showed up when a recursive function 'f' has a nested recursive
function 'g', where 'g' calls 'f' (as well as recursively calling 'g').
This exact situation happens in GHC/IO.writeLines.
This patch puts things right; see Note [When to specialise]. Result:
much less code bloat.
]
[Improve error-message output slightly
[EMAIL PROTECTED]
[Improve documentation of orphan instances (thanks to Adrian Hey)
[EMAIL PROTECTED]
Please push to stable branch
Simon
]
[fix installation of haddock.css and friends
Simon Marlow <[EMAIL PROTECTED]>**20071029120732]
[In a pattern binding, a type sig in the pattern cannot bind a type variable
[EMAIL PROTECTED]
In a pattern binding with a pattern type signature, such as
(Just (x::a)) = e
the pattern type signature cannot bind type variables. Hence
'a' must be in scope already for the above example to be legal.
This has been the situation for some time, but Dan changed it when
adding view patterns. This one-line change restores the old behaviour.
]
[Substantial improvement to the interaction of RULES and inlining
[EMAIL PROTECTED]
(Merge to 6.8 branch after testing.)
There were a number of delicate interactions between RULEs and inlining
in GHC 6.6. I've wanted to fix this for a long time, and some perf
problems in the 6.8 release candidate finally forced me over the edge!
The issues are documented extensively in OccurAnal, Note [Loop breaking
and RULES], and I won't duplicate them here. (Many of the extra lines in
OccurAnal are comments!)
This patch resolves Trac bugs #1709, #1794, #1763, I believe.
]
[Add newline in debug print
[EMAIL PROTECTED]
[Explicit pattern match in default case of addTickLHsBind
[EMAIL PROTECTED]
[Generalise the types of mk_FunBind, mk_easy_FunBind, mkVarBind
[EMAIL PROTECTED]
[Fix the build with GHC < 6.4 (foldl1' didn't exist)
Ian Lynagh <[EMAIL PROTECTED]>*-20071027210526]
[Fix the build with GHC < 6.4 (foldl1' didn't exist)
Ian Lynagh <[EMAIL PROTECTED]>**20071027210526]
[MERGED: We need to install-docs when making the Windows bindist
Ian Lynagh <[EMAIL PROTECTED]>**20071027203220]
[We need to set _way=* in rts/ both when making and installing bindists
Ian Lynagh <[EMAIL PROTECTED]>**20071027142914
This is a hack, but it means we get libHSrts*.a etc rather than just
libHSrts.a.
]
[Fix a whole heap of speling errrs in the docs
Josef Svenningsson <[EMAIL PROTECTED]>**20071007213858]
[Only build/install the man page if XSLTPROC is defined
Ian Lynagh <[EMAIL PROTECTED]>**20071027122155]
[install the Cabal docs, and make them show up in a binary distribution
Simon Marlow <[EMAIL PROTECTED]>**20071026122456]
[cp => $(CP)
Simon Marlow <[EMAIL PROTECTED]>**20071026111054]
[get rid of the html subdirectory under share/doc/ghc/users_guide
Simon Marlow <[EMAIL PROTECTED]>**20071026110919]
[Make 'improvement' work properly in TcSimplify
[EMAIL PROTECTED]
(Please merge this, and the preceding
handful from me to the 6.8 branch.)
This patch fixes a serious problem in the type checker, whereby
TcSimplify was going into a loop because it thought improvement
had taken place, but actually the unificataion was actually deferred.
We thereby fix Trac #1781, #1783, #1795, and #1797!
In fixing this I found what a mess TcSimplify.reduceContext is!
We need to fix this.
The main idea is to replace the "improvement flag" in Avails with
a simpler and more direct test: have any of the mutable type variables
in the (zonked) 'given' or 'irred' constraints been filled in?
This test uses the new function TcMType.isFilledMetaTyVar; the test
itself is towards the end of reduceContext.
I fixed a variety of other infelicities too, and left some ToDos.
]
[An implication constraint can abstract over EqInsts
[EMAIL PROTECTED]
[In an AbsBinds, the 'dicts' can include EqInsts
[EMAIL PROTECTED]
An AbsBinds abstrats over evidence, and the evidence can be both
Dicts (class constraints, implicit parameters) and EqInsts (equality
constraints). So we need to
- use varType rather than idType
- use instToVar rather than instToId
- use zonkDictBndr rather than zonkIdBndr in zonking
It actually all worked before, but gave warnings.
]
[More notes
[EMAIL PROTECTED]
[Comments only
[EMAIL PROTECTED]
[Add anyM to IOEnv
[EMAIL PROTECTED]
[Add a note to NOTES
[EMAIL PROTECTED]
[Make compileToCore return the module name and type environment along with
bindings
Tim Chevalier <[EMAIL PROTECTED]>**20071027100530
compileToCore returned just a list of CoreBind, which isn't enough,
since to do anything with the resulting Core code, you probably also
want the type declarations. I left compileToCore as it is, but added a
function compileToCoreModule that returns a complete Core module (with
module name, type environment, and bindings). I'm not sure that
returning the type environment is the best way to represent the type
declarations for the given module, but I don't want to reinvent the
External Core wheel for this.
]
[binary-dist: Makefile-vars needs HADDOCK_DOCS=YES
Simon Marlow <[EMAIL PROTECTED]>**20071025135816]
[fix the links in the library documentation index
Simon Marlow <[EMAIL PROTECTED]>**20071025152245]
[default to installing runhaskell and hsc2hs again, but provide knobs to turn
them off
Simon Marlow <[EMAIL PROTECTED]>**20071025084222]
[Adding hpc documentation about sum and map, push to STABLE.
[EMAIL PROTECTED]
[Fixing typo in runtime documentation for hpc, push to stable
[EMAIL PROTECTED]
[Correct a comment
Ian Lynagh <[EMAIL PROTECTED]>**20071024114549]
[Fix ghc package in bindists; it wasn't adding the depenedency on readline
Ian Lynagh <[EMAIL PROTECTED]>**20071024120633]
[Fix installing the ghc package .hi files in a bindist
Ian Lynagh <[EMAIL PROTECTED]>**20071024114219]
[Build the manpage when building, not when installing
Ian Lynagh <[EMAIL PROTECTED]>**20071024112914]
[Hack to make sure we get all the RTS ways in bindists
Ian Lynagh <[EMAIL PROTECTED]>**20071024004155]
[Fix installing the documentation in the bindists
Ian Lynagh <[EMAIL PROTECTED]>**20071023234624]
[-ftype-families -> -XTypeFamilies
Ian Lynagh <[EMAIL PROTECTED]>**20071024142828]
[FIX #1791: fail with out-of-heap when allocating more than the max heap size
in one go
Simon Marlow <[EMAIL PROTECTED]>**20071024095420
Normally the out-of-heap check is performed post-GC, but there are
cases where we can detect earlier that we definitely have exhausted
the heap size limit.
]
[Fix more warnings
Simon Marlow <[EMAIL PROTECTED]>**20071023131351]
[FIX BUILD (on 32-bit platforms): hs_hpc_module() type mismatch
Simon Marlow <[EMAIL PROTECTED]>**20071023082233]
[patch from #1782; fixes check-packages target on Solaris
Simon Marlow <[EMAIL PROTECTED]>**20071022133337]
[fix creation of ghc-inplace for non-std ways
Simon Marlow <[EMAIL PROTECTED]>**20071017152820]
[remove an incorrect assertion
Simon Marlow <[EMAIL PROTECTED]>**20071016151829]
[second attempt to fix C compiler warnings with -fhpc
Simon Marlow <[EMAIL PROTECTED]>**20071019133243
The hs_hpc_module() prototype in RtsExternal.h didn't match its usage:
we were passing StgWord-sized parameters but the prototype used C
ints. I think it accidentally worked because we only ever passed
constants that got promoted. The constants unfortunately were
sometimes negative, which caused the C compiler to emit warnings.
I suspect PprC.pprHexVal may be wrong to emit negative constants in
the generated C, but I'm not completely sure. Anyway, it's easy to
fix this in CgHpc, which is what I've done.
]
[Zonk quantified tyvars with skolems
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071019115653
We used to zonk quantified type variables to regular TyVars. However, this
leads to problems. Consider this program from the regression test suite:
eval :: Int -> String -> String -> String
eval 0 root actual = evalRHS 0 root actual
evalRHS :: Int -> a
evalRHS 0 root actual = eval 0 root actual
It leads to the deferral of an equality
(String -> String -> String) ~ a
which is propagated up to the toplevel (see TcSimplify.tcSimplifyInferCheck).
In the meantime `a' is zonked and quantified to form `evalRHS's signature.
This has the *side effect* of also zonking the `a' in the deferred equality
(which at this point is being handed around wrapped in an implication
constraint).
Finally, the equality (with the zonked `a') will be handed back to the
simplifier by TcRnDriver.tcRnSrcDecls calling TcSimplify.tcSimplifyTop.
If we zonk `a' with a regular type variable, we will have this regular type
variable now floating around in the simplifier, which in many places assumes to
only see proper TcTyVars.
We can avoid this problem by zonking with a skolem. The skolem is rigid
(which we requirefor a quantified variable), but is still a TcTyVar that the
simplifier knows how to deal with.
]
[Fix typo that prevented zonking of rhs of EqInsts
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071018131040
MERGE TO STABLE
]
[implement #1468, :browse on its own uses the currently-loaded module
Simon Marlow <[EMAIL PROTECTED]>**20071019115751]
[FIX #1784: EM_AMD64 and EM_X86_64 might both be defined to the same value
Simon Marlow <[EMAIL PROTECTED]>**20071019110223]
[Tell Cabal what it's version number is while bootstrapping it
Duncan Coutts <[EMAIL PROTECTED]>**20071018222128
This means that it'll work with all the packages that specify a cabal-version
]
[FIX #1450: asynchronous exceptions are now printed by +RTS -xc
Simon Marlow <[EMAIL PROTECTED]>**20071018134951]
[fix -fbreak-on-exception for unregsterised
Simon Marlow <[EMAIL PROTECTED]>**20071018110621]
[fix :print when !tablesNextToCode
Simon Marlow <[EMAIL PROTECTED]>**20071018105340]
[fix breakpoints in unregisterised mode
Simon Marlow <[EMAIL PROTECTED]>**20071018101929]
[Change some ints to unsigned ints
Simon Marlow <[EMAIL PROTECTED]>**20071018095503
Fixes some gratuitous warnings when compiling via C with -fhpc
]
[fix warnings when compiling via C
Simon Marlow <[EMAIL PROTECTED]>**20071018095417]
[rollback "accounting wibble: we were missing an alloc_blocks .. "
Simon Marlow <[EMAIL PROTECTED]>**20071018094415
I misread the code, now added a comment to explain why it isn't necessary
]
[recordMutable: test for gen>0 before calling recordMutableCap
Simon Marlow <[EMAIL PROTECTED]>**20071017125657
For some reason the C-- version of recordMutable wasn't verifying that
the object was in an old generation before attempting to add it to the
mutable list, and this broke maessen_hashtab. This version of
recordMutable is only used in unsafeThaw#.
]
[re-instate missing parts of "put the @N suffix on stdcall foreign calls in
.cmm code"
Simon Marlow <[EMAIL PROTECTED]>**20071017144007
These changes were apparently lost during "massive changes to add a
'zipper' representation of C-"
]
[Don't barf on error message with non-tc tyvars
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071018060336
MERGE TO STABLE
]
[Fix deferring on tyvars in TcUnify.subFunTys
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071018044352]
[TcUnify.subFunTys must take type families into account
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071017114326
* A bug reported by Andrew Appleyard revealed that subFunTys did take
neither type families nor equalities into account. In a fairly obscure
case there was also a coercion ignored.
]
[Refactoring: extract platform-specific code from sm/MBlock.c
Simon Marlow <[EMAIL PROTECTED]>**20071017134145
Also common-up some duplicate bits in the platform-specific code
]
[fix an error message (barf -> sysErrorBelch)
Simon Marlow <[EMAIL PROTECTED]>**20071017121855]
[fix warning on Windows
Simon Marlow <[EMAIL PROTECTED]>**20071017121645]
[Don't clean gmp when validating (speeds up validation on Windows)
Simon Marlow <[EMAIL PROTECTED]>**20071017100908]
[document float2Int# and double2Int#
Simon Marlow <[EMAIL PROTECTED]>**20070925121139]
[Update HsExpr.hi-boot-6 for view pattern changes
[EMAIL PROTECTED]
[Fix #1709: do not expose the worker for a loop-breaker
[EMAIL PROTECTED]
The massive 'Uni' program produced a situation in which a function that
had a worker/wrapper split was chosen as a loop breaker. If the worker
is exposed in the interface file, then an importing module may go into
an inlining loop: see comments on TidyPgm.tidyWorker.
This patch fixes the inlining bug. The code that gives rise to this
bizarre case is still not good (it's a bunch of implication constraints
and we are choosing a bad loop breaker) but the first thing is to fix the
bug.
It's rather hard to produce a test case!
Please merge to the 6.8 branch.
]
[Fix #1662: do not simplify constraints for vanilla pattern matches
[EMAIL PROTECTED]
See Note [Arrows and patterns] in TcPat.
This fixes Trac 1662. Test is arrows/should_compile/arrowpat.hs
Please merge
]
[Eliminate over-zealous warning in CoreToStg
[EMAIL PROTECTED]
[Show inlined function in the header of 'Inlining done' message
[EMAIL PROTECTED]
[Show program size in the simplifier-bailing-out message
[EMAIL PROTECTED]
[View patterns, record wildcards, and record puns
Dan Licata <[EMAIL PROTECTED]>**20071010150254
This patch implements three new features:
* view patterns (syntax: expression -> pat in a pattern)
* working versions of record wildcards and record puns
See the manual for detailed descriptions.
Other minor observable changes:
* There is a check prohibiting local fixity declarations
when the variable being fixed is not defined in the same let
* The warn-unused-binds option now reports warnings for do and mdo stmts
Implementation notes:
* The pattern renamer is now in its own module, RnPat, and the
implementation is now in a CPS style so that the correct context is
delivered to pattern expressions.
* These features required a fairly major upheaval to the renamer.
Whereas the old version used to collect up all the bindings from a let
(or top-level, or recursive do statement, ...) and put them into scope
before renaming anything, the new version does the collection as it
renames. This allows us to do the right thing with record wildcard
patterns (which need to be expanded to see what names should be
collected), and it allows us to implement the desired semantics for view
patterns in lets. This change had a bunch of domino effects brought on
by fiddling with the top-level renaming.
* Prior to this patch, there was a tricky bug in mkRecordSelId in HEAD,
which did not maintain the invariant necessary for loadDecl. See note
[Tricky iface loop] for details.
]
[FIX profiling after my storage manager changes
Simon Marlow <[EMAIL PROTECTED]>**20071015103939]
[More docu for skolemOccurs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071015075644]
[Slightly improved comments in TcTyClsDecls
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071010142023]
[TcTyFuns: remove some duplicate code
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071004142315]
[TcTyFuns.eqInstToRewrite
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071003145715]
[Add allocateInGen() for allocating in a specific generation, and cleanups
Simon Marlow <[EMAIL PROTECTED]>**20071012124413
Now allocate() is a synonym for allocateInGen().
I also made various cleanups: there is now less special-case code for
supporting -G1 (two-space collection), and -G1 now works with
-threaded.
]
[optimise isAlive()
Simon Marlow <[EMAIL PROTECTED]>**20071012103810]
[accounting wibble: we were missing an alloc_blocks++ in allocateLocal()
Simon Marlow <[EMAIL PROTECTED]>**20071012101711]
[threadStackOverflow should be using allocateLocal
Simon Marlow <[EMAIL PROTECTED]>**20071012100405]
[FIX #1759 while respecting the ticks
[EMAIL PROTECTED]
[Improving the combine mode for hpc
[EMAIL PROTECTED]
we now have
Processing Coverage files:
sum Sum multiple .tix files in a single .tix file
combine Combine two .tix files in a single .tix file
map Map a function over a single .tix file
Where sum joins many .tix files, combine joins two files (with
extra functionality possible), and map just applied a function
to single .tix file.
These changes were improvements driven by hpc use cases.
END OF DESCRIPTION***
Place the long patch description above the ***END OF DESCRIPTION*** marker.
The first line of this file will be the patch name.
This patch contains the following changes:
M ./utils/hpc/Hpc.hs -1 +3
M ./utils/hpc/HpcCombine.hs -33 +84
M ./utils/hpc/HpcFlags.hs -11 +59
]
[Fix DoCon: Another try at getting extractResults right
[EMAIL PROTECTED]
For some reason TcSimplify.extractResults is quite difficult to get right.
This is another attempt; finally I think I have it.
Strangely enough, it's only Sergey's DoCon program that shows up the
bug, which manifested as a failure in the Simplifier
lookupRecBndr $dGCDRing{v a1Lz} [lid]
But it was due to extractResults producing multiple bindings for
the same dictionary.
Please merge this to the stable branch (after previous patches to
TcSimplify though).
]
[mention what SCC stands for
Simon Marlow <[EMAIL PROTECTED]>**20071011135736]
[Add a proper write barrier for MVars
Simon Marlow <[EMAIL PROTECTED]>**20071011135505
Previously MVars were always on the mutable list of the old
generation, which meant every MVar was visited during every minor GC.
With lots of MVars hanging around, this gets expensive. We addressed
this problem for MUT_VARs (aka IORefs) a while ago, the solution is to
use a traditional GC write-barrier when the object is modified. This
patch does the same thing for MVars.
TVars are still done the old way, they could probably benefit from the
same treatment too.
]
[we need to #include "Stg.h" first, we can't rely on GHC to inject it
Simon Marlow <[EMAIL PROTECTED]>**20071010153244
This fixes the unreg build, and in general building the RTS code
via-C. I'm not sure at what stage this was broken, but I think it
was working accidentally before.
]
[Fix Trac #1680; check for unboxed tuples in TcType.marshalableTyCon
[EMAIL PROTECTED]
[Fix Trac #1759: do not let ticks get in the way of spotting trivially-true
guards
[EMAIL PROTECTED]
GHC spots that an 'otherwise' guard is true, and uses that knowledge to
avoid reporting spurious missing-pattern or overlaps with -Wall.
The HPC ticks were disguising the 'otherwise', which led to this failure.
Now we check. The key change is defining DsGRHSs.isTrueLHsExpr.
Test is ds062
]
[Fix Trac #1755; check for stage errors in TH quoted Names
[EMAIL PROTECTED]
There are a number of situations in which you aren't allowed to use
a quoted Name in a TH program, such as
\x -> 'x
But we weren't checking for that! Now we are.
Merge to stable branch.
Test is TH_qname.
]
[checkWellStaged: reverse comparsion (no change in semantics), plus some
comments
[EMAIL PROTECTED]
[Add traceTc in tcSimplifyDefault
[EMAIL PROTECTED]
[Improve pretty-printing of splices in HsSyn
[EMAIL PROTECTED]
[Fix Trac #1678; be more careful about catching and reporting exceptions in
spliced TH monadic computations
[EMAIL PROTECTED]
Many of the new lines are comments to explain the slightly-convoluted
in which exceptions get propagated out of the Q monad.
This fixes Trac 1679; test is TH_runIO (as well as the exising TH_fail).
Please merge
]
[Comments only
[EMAIL PROTECTED]
[FIX BUILD (when compiling base via C): declare n_capabilities
Simon Marlow <[EMAIL PROTECTED]>**20071010103704]
[GHCi: use non-updatable thunks for breakpoints
Simon Marlow <[EMAIL PROTECTED]>**20071010093241
The extra safe points introduced for breakpoints were previously
compiled as normal updatable thunks, but they are guaranteed
single-entry, so we can use non-updatable thunks here. This restores
the tail-call property where it was lost in some cases (although stack
squeezing probably often recovered it), and should improve
performance.
]
[FIX #1681: withBreakAction had too large a scope in runStmt
Simon Marlow <[EMAIL PROTECTED]>**20071010085820]
[tiny refactoring
Simon Marlow <[EMAIL PROTECTED]>**20071009145002]
[small reworking of the loop-breaker-choosing algorithm
Simon Marlow <[EMAIL PROTECTED]>**20071009145305
Previously inline candidates were given higher preference as
non-loop-breakers than constructor applications, but the reason for
this was that making a wrapper into a loop-breaker is to be avoided at
all costs. This patch refines the algorithm slightly so that wrappers
are explicitly avoided by giving them a much higher score, and other
inline candidates are given lower scores than constructor
applications.
This makes almost zero difference to a complete nofib run, so it
amounts to just a tidyup.
]
[Fix warnings when build w/o readline
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071010101840]
[Update documentation for win32 DLL linking
Clemens Fruhwirth <[EMAIL PROTECTED]>**20071010074415]
[FIX: tidy up TcSimplify following equality constraints additions
[EMAIL PROTECTED]
The combination of "type refinement" for GADTs and the new equality
constraints has made TcSimplify rather complicated. And wrong:
it generated bogus code for cholewo-eval.
This patch is still far from entirely satisfactory. There are
too many places where invariants are unclear, and the code is
still a bit of a mess. But I believe it's better, and it passes
the regression tests! So I think it's good enough for the 6.8 release.
Please merge.
The main changes are:
- get rid of extractLocalResults (which was always suspicious)
- instead, treat the 'refinement' along with 'givens', by
adding a field to RedEnv, red_reft which travels with red_givens
- I also reworked extractResults a bit, which looked wrong to me
This entailed changing the Given constructor in Avail to take
an Inst rather than a TcId
]
[Improve pretty-printing for HsSyn
[EMAIL PROTECTED]
[Fix Trac #1746: make rule-matching work properly with Cast expressions
[EMAIL PROTECTED]
The Cast case of the rule-matcher was simply wrong.
This patch fixes it; see Trac #1746.
I also fixed the rule generation in SpecConstr to generate a wild-card
for the cast expression, which we don't want to match on. This makes
the rule more widely applicable; it wasn't the cause of the bug.
]
[Small comment only
[EMAIL PROTECTED]
[export n_capabilities, see #1733
Simon Marlow <[EMAIL PROTECTED]>**20071009142701]
[FIX #1743, create a fresh unique for each Id we bind at a breakpoint
Simon Marlow <[EMAIL PROTECTED]>**20071009142554]
[remove vestiges of way 'u' (see #1008)
Simon Marlow <[EMAIL PROTECTED]>**20071009130942]
[also call initMutex on every task->lock, see #1391
Simon Marlow <[EMAIL PROTECTED]>**20071009122409]
[remove the "-unreg" flag and the unregisterised way, see #1008
Simon Marlow <[EMAIL PROTECTED]>**20071009122338]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071009105138]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071003170005]
[refactoring only: use the parameterised InstalledPackageInfo
Simon Marlow <[EMAIL PROTECTED]>**20071003163536
This required moving PackageId from PackageConfig to Module
]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071003174016]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071003173448]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071003173202]
[warning removal
Simon Marlow <[EMAIL PROTECTED]>**20071003172715]
[remove most warnings
Simon Marlow <[EMAIL PROTECTED]>**20071003090804]
[mkIfaceExports: sort the children of AvailTC
Simon Marlow <[EMAIL PROTECTED]>**20071002114917
This fixes a problem with spurious recompilations: each time a module
was recompiled, the order of the children would change, causing extra
recompilation.
MERGE TO STABLE
]
[error message fix (#1758)
Simon Marlow <[EMAIL PROTECTED]>**20071008134958]
[FIX validate for PPC Mac OS X - RegAllocStats.hs
Thorkil Naur <[EMAIL PROTECTED]>**20071005144105]
[FIX validate for PPC Mac OS X - RegAllocLinear.hs
Thorkil Naur <[EMAIL PROTECTED]>**20071005143607]
[FIX validate for PPC Mac OS X - Linker.c
Thorkil Naur <[EMAIL PROTECTED]>**20071005144908]
[FIX validate for PPC Mac OS X - Evac.h
Thorkil Naur <[EMAIL PROTECTED]>**20071005144454]
[FIX #1748: -main-is wasn't handling the case of a single hierarchical module
Simon Marlow <[EMAIL PROTECTED]>**20071008131305
test case is driver062.5
]
[FIX BUILD FD_SETSIZE signed
[EMAIL PROTECTED]
On FreeBSD FD_SETSIZE is unsigned. Cast it to a signed int
for portability.
]
[FIX BUILD addDLL returns const char*
[EMAIL PROTECTED]
addDLL returns const char*, not just a char*.
Fix compiler warning
]
[FIX BUILD `set -o igncr'-issue on FreeBSD
[EMAIL PROTECTED]
`set -o igncr' does not work on non-cygwin-systems.
Fail silently if this command does not work, instead
of aborting the build.
]
[comment-out "use vars" in 3 places (see #1739)
Simon Marlow <[EMAIL PROTECTED]>**20071008115740]
[Change DOCOPTIONS pragma to DOC_OPTIONS
David Waern <[EMAIL PROTECTED]>**20071002143849
MERGE TO STABLE
]
[FIX: parsing of doc options
David Waern <[EMAIL PROTECTED]>**20071002143713
Lexing of the doc options pragma was changed, but but no change was
made to the parser to reflect that. This patch fixes this problem.
MERGE TO STABLE
]
[FIX: add missing case to OccName.isSymOcc
David Waern <[EMAIL PROTECTED]>**20071002143459]
[Remove warnings from WwLib
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071002130736]
[FIX: mkWWcpr takes open alg types into account
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071002130407
- This fixed the failures of GMapAssoc and GMapTop for optmising ways
MERGE TO STABLE
]
[FIX #1738: KPush rule of FC must take dataConEqTheta into account
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071001154343
MERGE TO STABLE
]
[FIX #1729: Don't try to expand syn families with -XLiberalTypeSynonyms
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070929122624
MERGE TO STABLE
]
[Some more traceTcs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070929121941]
[FIX: Make boxy splitters aware of type families
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070928225541
MERGE TO STABLE
]
[Finally, I managed to squash an infamous bug in :print
Pepe Iborra <[EMAIL PROTECTED]>**20070927151300
It turns out the newtype handling code in :print
was slipping non mutable Tyvars in the types reconstructed.
The error message eventually produced was rather obscure:
[src/Tp.hs:75:28-64] *MainTp> :p x
*** Exception: No match in record selector Var.tcTyVarDetails
[src/Tp.hs:75:28-64] *MainTp>
Due to non mutable tyvars, unifyType was failing.
A well placed assertion in the unifyType code would have made
my life much easier.
Which reminds me I should install a -ddump-* system in the
RTTI subsystem, or future hackers will run away in swearing.
MERGE TO STABLE
]
[Be a bit more flexible in terminal identification for do_bold
Pepe Iborra <[EMAIL PROTECTED]>**20070927141549
In Os X for instance, by default we have TERM=xterm-color
MERGE TO STABLE
]
[html_installed_root shouldn't contain $$pkgid
Ian Lynagh <[EMAIL PROTECTED]>**20070927130427
This actually didn't break anything, as the shell expanded $pkgid to the
empty string, but it was still wrong.
]
[Comments and debug output only
[EMAIL PROTECTED]
[further stub filename fix: I managed to break non-stubdir -fvia-C compilation
Simon Marlow <[EMAIL PROTECTED]>**20070927102539]
[also acquire/release task->lock across fork()
Simon Marlow <[EMAIL PROTECTED]>**20070927091331
further attempt to fix #1391 on MacOS
]
[FIX -stubdir bug: the .hc file was #including the wrong _stub.h filename
Simon Marlow <[EMAIL PROTECTED]>**20070926134539
Using -stubdir together with hierarchical modules, -fvia-C, and --make
is essentially broken in 6.6.x. Recently discovered by Cabal's use of
-stubdir.
Test cases: driver027/driver028 (I've updated them to use -fvia-C, in
order to test for this bug).
]
[Add STANDARD_OPTS to SRC_HC_OPTS in rts/Makefile so we get -I../includes for
.cmm files
Ian Lynagh <[EMAIL PROTECTED]>**20070926122637
Patch from Clemens Fruhwirth
]
[fix #1734, panic in :show modules after load failure
Simon Marlow <[EMAIL PROTECTED]>**20070926100732]
[Remove current package from preloaded package set
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070926084802]
[Fixing #1340, adding HPC Documentation
[EMAIL PROTECTED]
[TAG 2007-09-25
Ian Lynagh <[EMAIL PROTECTED]>**20070925164536]
Patch bundle hash:
eb69be050ccf0fc3ffcfaa23a1c56a710bcc170b
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc