I just wanted to check that my documentation was correct and my ifdef
reasonable; it validates fine. Then I'll commit, if it's fine.
Fri Dec 28 11:02:55 EST 2007 Isaac Dupree <[EMAIL PROTECTED]>
* document BreakArray better
Fri Dec 28 11:39:22 EST 2007 Isaac Dupree <[EMAIL PROTECTED]>
* properly ifdef BreakArray for GHCI
New patches:
[document BreakArray better
Isaac Dupree <[EMAIL PROTECTED]>**20071228160255] {
hunk ./compiler/main/BreakArray.hs 6
+-- Conceptually, a zero-indexed IOArray of Bools, initially False.
+-- They're represented as Words with 0==False, 1==True.
+-- They're used to determine whether GHCI breakpoints are on or off.
+--
}
[properly ifdef BreakArray for GHCI
Isaac Dupree <[EMAIL PROTECTED]>**20071228163922] {
hunk ./compiler/main/BreakArray.hs 22
- ( BreakArray (BA)
- -- constructor is exported only for ByteCodeGen
+ ( BreakArray
+#ifdef GHCI
+ (BA) -- constructor is exported only for ByteCodeGen
+#endif
hunk ./compiler/main/BreakArray.hs 27
+#ifdef GHCI
hunk ./compiler/main/BreakArray.hs 32
+#endif
hunk ./compiler/main/BreakArray.hs 34
-
+#ifdef GHCI
hunk ./compiler/main/BreakArray.hs 117
+#else /* GHCI */
+--stub implementation to make main/, etc., code happier.
+--IOArray and IOUArray are increasingly non-portable,
+--still don't have quite the same interface, and (for GHCI)
+--presumably have a different representation.
+data BreakArray = Unspecified
+newBreakArray :: Int -> IO BreakArray
+newBreakArray _ = return Unspecified
+#endif /* GHCI */
+
+
}
Context:
[import ord that alex secretly imported
Isaac Dupree <[EMAIL PROTECTED]>**20071228175727]
[generalize instance Outputable GenCmm to H98 (#1405)
Isaac Dupree <[EMAIL PROTECTED]>**20071226175915]
[move and generalize another instance (#1405)
Isaac Dupree <[EMAIL PROTECTED]>**20071226174904
was instance Outputable CmmGraph
type CmmGraph = LGraph Middle Last
now instance (ctx) => Outputable (LGraph m l),
in module with LGraph where it belongs
This also let us reduce the context of DebugNodes to Haskell98,
leaving that class's only extension being multi-parameter.
(also Outputable (LGraph M Last) with M = ExtendWithSpills Middle
was another redundant instance that was then removed)
]
[move and generalize an instance (#1405)
Isaac Dupree <[EMAIL PROTECTED]>**20071226171913
UserOfLocalRegs (ZLast Last) isn't Haskell98, but it was just as
good an instance to be UserOfLocalRegs a => UserOfLocalRegs (ZLast a)
]
[add missing import that happy -agc secretly provided
Isaac Dupree <[EMAIL PROTECTED]>**20071227171335]
[correct type mistake, hidden by happy -agc coercions!
Isaac Dupree <[EMAIL PROTECTED]>**20071226140743]
[API changes for cabal-HEAD
Clemens Fruhwirth <[EMAIL PROTECTED]>**20071227143114
Rename interfacedir to haddockdir
Change empty(Copy|Register)Flags to default(Copy|Register)Flags
Wrap content of RegisterFlags with toFlag (the Flag type is actually just
Maybe)
]
[Extend API for compiling to and from Core
Tim Chevalier <[EMAIL PROTECTED]>**20071225200411
Added API support for compiling Haskell to simplified Core, and for
compiling Core to machine code. The latter, especially, should be
considered experimental and has only been given cursory testing. Also
fixed warnings in DriverPipeline. Merry Christmas.
]
[When complaining about non-rigid context, give suggestion of adding a signature
[EMAIL PROTECTED]
[Improve handling of newtypes (fixes Trac 1495)
[EMAIL PROTECTED]
In a few places we want to "look through" newtypes to get to the
representation type. But we need to be careful that we don't fall
into an ininite loop with e.g.
newtype T = MkT T
The old mechansim for doing this was to have a field nt_rep, inside
a newtype TyCon, that gave the "ultimate representation" of the type.
But that failed for Trac 1495, which looked like this:
newtype Fix a = Fix (a (Fix a))
data I a = I a
Then, expanding the type (Fix I) went on for ever.
The right thing to do seems to be to check for loops when epxanding
the *type*, rather than in the *tycon*. This patch does that,
- Removes nt_rep from TyCon
- Make Type.repType check for loops
See Note [Expanding newtypes] in Type.lhs.
At the same time I also fixed a bug for Roman, where newtypes were not
being expanded properly in FamInstEnv.topNormaliseType. This function
and Type.repType share a common structure.
Ian, see if this merges easily to the branch
If not, I don't think it's essential to fix 6.8
]
[Fix Trac #1981: seq on a type-family-typed expression
[EMAIL PROTECTED]
We were crashing when we saw
case x of DEFAULT -> rhs
where x had a type-family type. This patch fixes it.
MERGE to the 6.8 branch.
]
[Comment only
[EMAIL PROTECTED]
[Fix nasty recompilation bug in MkIface.computeChangedOccs
[EMAIL PROTECTED]
MERGE to 6.8 branch
In computeChangedOccs we look up the old version of a Name.
But a WiredIn Name doesn't have an old version, because WiredIn things
don't appear in interface files at all.
Result: ghc-6.9: panic! (the 'impossible' happened)
(GHC version 6.9 for x86_64-unknown-linux):
lookupVers1 base:GHC.Prim chr#{v}
This fixes the problem. The patch should merge easily onto the branch.
]
[Fix Trac #1988; keep the ru_fn field of a RULE up to date
[EMAIL PROTECTED]
The ru_fn field was wrong when we moved RULES from one Id to another.
The fix is simple enough.
However, looking at this makes me realise that the worker/wrapper stuff
for recursive newtypes isn't very clever: we generate demand info but
then don't properly exploit it.
This patch fixes the crash though.
]
[Add better panic message in getSRTInfo (Trac #1973)
[EMAIL PROTECTED]
[Remove obselete code for update-in-place (which we no longer do)
[EMAIL PROTECTED]
[Implement generalised list comprehensions
[EMAIL PROTECTED]
This patch implements generalised list comprehensions, as described in
the paper "Comprehensive comprehensions" (Peyton Jones & Wadler, Haskell
Workshop 2007). If you don't use the new comprehensions, nothing
should change.
The syntax is not exactly as in the paper; see the user manual entry
for details.
You need an accompanying patch to the base library for this stuff
to work.
The patch is the work of Max Bolingbroke [EMAIL PROTECTED],
with some advice from Simon PJ.
The related GHC Wiki page is
http://hackage.haskell.org/trac/ghc/wiki/SQLLikeComprehensions
]
[More bindist-publishing fixes and refactoring
Ian Lynagh <[EMAIL PROTECTED]>**20071218144505]
[Fix publishing the docs
Ian Lynagh <[EMAIL PROTECTED]>**20071216122544]
[FIX #1980: must check for ThreadRelocated in killThread#
Simon Marlow <[EMAIL PROTECTED]>**20071217164610]
[Eliminate external GMP dependencies
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071217093839
- Ensure the stage1 compiler uses ghc's own GMP library on Mac OS
- Need to rebuild installPackage and ifBuildable with stage1 compiler as they
go into bindists
]
[Include ~/Library/Frameworks in the framework searchpath
Ian Lynagh <[EMAIL PROTECTED]>**20071217233457
Patch from Christian Maeder
]
[Make ghcii.sh executable
Ian Lynagh <[EMAIL PROTECTED]>**20071217195734]
[Don't rely on distrib/prep-bin-dist-mingw being executable
Ian Lynagh <[EMAIL PROTECTED]>**20071217195554]
[always try to remove the new file before restoring the old one (#1963)
Simon Marlow <[EMAIL PROTECTED]>**20071214123345]
[Fix a bug in gen_contents_index
Ian Lynagh <[EMAIL PROTECTED]>**20071212121154
The library doc index thought that the docs were in $module.html, rather
than $package/$module.html.
]
[Fix lifting of case expressions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071215000837
We have to explicity check for empty arrays in each alternative as recursive
algorithms wouldn't terminate otherwise.
]
[Use (UArr Int) instead of PArray_Int# in vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071215000739]
[Fix bug in VectInfo loading
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071214230914]
[Remove unused vectorisation built-in
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071214011015]
[Treat some standard data cons specially during vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213034855
This is a temporary hack which allows us to vectorise literals.
]
[More vectorisation-related built ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213034839]
[Track changes to package ndp
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071212062714]
[Add vectorisation built-ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071212040521]
[FIX #1963: catch Ctrl-C and clean up properly
Simon Marlow <[EMAIL PROTECTED]>**20071213154056]
[Document the new threshold flags
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071214003003]
[Separate and optional size thresholds for SpecConstr and LiberateCase
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071214002719
This patch replaces -fspec-threshold by -fspec-constr-threshold and
-fliberate-case-threshold. The thresholds can be disabled by
-fno-spec-constr-threshold and -fno-liberate-case-threshold.
]
[Make HscTypes.tyThingId respond not panic on ADataCon
[EMAIL PROTECTED]
[Use Unix format for RnPat (no other change)
[EMAIL PROTECTED]
[Improve free-variable handling for rnPat and friends (fixes Trac #1972)
[EMAIL PROTECTED]
As well as fixing the immediate problem (Trac #1972) this patch does
a signficant simplification and refactoring of pattern renaming.
Fewer functions, fewer parameters passed....it's all good. But it
took much longer than I expected to figure out.
The most significant change is that the NameMaker type does *binding*
as well as *making* and, in the matchNameMaker case, checks for unused
bindings as well. This is much tider.
(No need to merge to the 6.8 branch, but no harm either.)
]
[Allow more than 3 simplifier iterations to be run in phase 0
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213040835
The number of iterations during the first run of phase 0 was erroneously
hardcoded to 3. It should be *at least* 3 (see comments in code) but can be
more.
]
[Document -ddump-simpl-phases
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213040822]
[New flag: -ddump-simpl-phases
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213040644
This outputs the core after each simplifier phase (i.e., it produces less
information that -ddump-simpl-iterations).
]
[Don't dump simplifier iterations with -dverbose-core2core
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071213034635
SimonPJ says this is the correct behaviour. We still have
-ddump-simpl-iterations.
]
["list --simple-output" should be quiet when there are no packages to list
Simon Marlow <[EMAIL PROTECTED]>**20071212102230
Previously:
$ ghc-pkg list --user --simple-output
ghc-pkg: no matches
$
Now:
$ ghc-pkg list --user --simple-output
$
]
[Fix vectorisation bug
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071206233015]
[Vectorisation-related built ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071206040829]
[Teach vectorisation about some temporary conversion functions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071206032547]
[Vectorise case of unit correctly
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205221305]
[Teach vectorisation about singletonP
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205221240]
[Optimise desugaring of parallel array comprehensions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205221213]
[Teach vectorisation about tuple datacons
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205050221]
[Track additions to package ndp
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205042649]
[Track changes to package ndp
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071205033859]
[Improve pretty-printing of InstDecl
[EMAIL PROTECTED]
Fixes Trac #1966.
]
[Comments only
Pepe Iborra <[EMAIL PROTECTED]>**20071208204815]
[Refactoring only
Pepe Iborra <[EMAIL PROTECTED]>**20071208195222
Suspensions in the Term datatype used for RTTI
always get assigned a Type, so there is no reason
to juggle around with a (Maybe Type) anymore.
]
[Change the format used by :print to show the content of references
Pepe Iborra <[EMAIL PROTECTED]>**20071208193013
This comes as result of the short discussion linked below.
http://www.haskell.org/pipermail/cvs-ghc/2007-December/040049.html
]
[Help the user when she tries to do :history without :trace
Pepe Iborra <[EMAIL PROTECTED]>**20071208180918
Teach GHCi to show a "perhaps you forgot to use :trace?" when
it finds that the user is trying to retrieve an empty :history
]
[Prevent the binding of unboxed things by :print
Pepe Iborra <[EMAIL PROTECTED]>**20071208181830]
[Coercions from boxy splitters must be sym'ed in pattern matches
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071208105018]
[Properly keep track of whether normalising given or wanted dicts
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071207071302
- The information of whether given or wanted class dictionaries where
normalised by rewriting wasn't always correctly propagated in TcTyFuns,
which lead to malformed dictionary bindings.
- Also fixes a bug in TcPat.tcConPat where GADT equalities where emitted in
the wrong position in case bindings (which led to CoreLint failures).
]
[TcPat.tcConPat uses equalities instead of GADT refinement
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071120071208
* This patch implements the use of equality constraints instead of GADT
refinements that we have been discussing for a while.
* It just changes TcPat.tcConPat. It doesn't have any of the simplification
and dead code removal that is possible due to this change.
* At the moment, this patch breaks a fair number of GADT regression tests.
]
[Use installPackage for register --inplace as well as installing
Ian Lynagh <[EMAIL PROTECTED]>**20071207234652
We also need to do the GHC.Prim hack when registering inplace or the
tests that use it fail.
]
[Fix the libraries Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20071205125015
x && y
is not the same as
if x; then y; fi
as the latter doesn't fail when x fails
]
[Copy hscolour.css into dist/... so it gets installed with the library docs
Ian Lynagh <[EMAIL PROTECTED]>**20071205013703]
[Add the hscolour.css from hscolour 1.8
Ian Lynagh <[EMAIL PROTECTED]>**20071205011733]
[BIN_DIST_INST_SUBDIR Needs to be defined in config.mk so ./Makefile can see it
Ian Lynagh <[EMAIL PROTECTED]>**20071207121317]
[#include ../includes/MachRegs.h rather than just MachRegs.h
Ian Lynagh <[EMAIL PROTECTED]>**20071205170335
This fixes building on NixOS. I'm not sure why it worked everywhere else,
but not on NixOS, before.
]
[Fix bindist creation: readline/config.mk is gone
Ian Lynagh <[EMAIL PROTECTED]>**20071203123031]
[FIX #1843: Generate different instructions on PPC
Ian Lynagh <[EMAIL PROTECTED]>**20071203123237
The old ones caused lots of
unknown scattered relocation type 4
errors. Patch from Chris Kuklewicz.
]
[Refactor gen_contents_index
Ian Lynagh <[EMAIL PROTECTED]>**20071207183538
Also fixes it with Solaris's sh, spotted by Christian Maeder
]
[Use GHC.Exts rather than GHC.Prim
Ian Lynagh <[EMAIL PROTECTED]>**20071202234222]
[Alter the base:GHC.Prim hack in installPackage, following changes in base
Ian Lynagh <[EMAIL PROTECTED]>**20071202215719]
[Remove debug warning, and explain why
[EMAIL PROTECTED]
[comment only
Simon Marlow <[EMAIL PROTECTED]>**20071206092422]
[comment typo
Simon Marlow <[EMAIL PROTECTED]>**20071206092412]
[add Outputable instance for OccIfaceEq
Simon Marlow <[EMAIL PROTECTED]>**20071206092403]
[Workaround for #1959: assume untracked names have changed
Simon Marlow <[EMAIL PROTECTED]>**20071206092349
This fixes the 1959 test, but will do more recompilation than is
strictly necessary (but only when -O is on). Still, more
recompilation is better than segfaults, link errors or other random
breakage.
]
[FIX part of #1959: declaration versions were not being incremented correctly
Simon Marlow <[EMAIL PROTECTED]>**20071206084556
We were building a mapping from ModuleName to [Occ] from the usage
list, using the usg_mod field as the key. Unfortunately, due to a
very poor naming decision, usg_mod is actually the module version, not
the ModuleName. usg_name is the ModuleName. Since Version is also an
instance of Uniquable, there was no type error: all that happened was
lookups in the map never succeeded. I shall rename the fields of
Usage in a separate patch.
This doesn't completely fix #1959, but it gets part of the way there.
I have to take partial blame as the person who wrote this fragment of
code in late 2006 (patch "Interface file optimisation and removal of
nameParent").
]
[move FP_FIND_ROOT after the "GHC is required" check
Simon Marlow <[EMAIL PROTECTED]>**20071205101814]
[FIX #1110: hackery also needed when running gcc for CPP
Simon Marlow <[EMAIL PROTECTED]>**20071205150230]
[Teach :print to follow references (STRefs and IORefs)
Pepe Iborra <[EMAIL PROTECTED]>**20071204105511
Prelude Data.IORef> :p l
l = (_t4::Maybe Integer) : (_t5::[Maybe Integer])
Prelude Data.IORef> p <- newIORef l
Prelude Data.IORef> :p p
p = GHC.IOBase.IORef (GHC.STRef.STRef {((_t6::Maybe Integer) :
(_t7::[Maybe Integer]))})
Prelude Data.IORef> :sp p
p = GHC.IOBase.IORef (GHC.STRef.STRef {(_ : _)})
I used braces to denote the contents of a reference.
Perhaps there is a more appropriate notation?
]
[refactoring only
Pepe Iborra <[EMAIL PROTECTED]>**20071202125400]
[Change --shared to -shared in Win32 DLL docs
[EMAIL PROTECTED]
[protect console handler against concurrent access (#1922)
Simon Marlow <[EMAIL PROTECTED]>**20071204153918]
[Make eta reduction check more carefully for bottoms (fix Trac #1947)
[EMAIL PROTECTED]
Eta reduction was wrongly transforming
f = \x. f x
to
f = f
Solution: don't trust f's arity information; instead look at its
unfolding. See Note [Eta reduction conditions]
Almost all the new lines are comments!
]
[Improve inlining for INLINE non-functions
[EMAIL PROTECTED]
(No need to merge to 6.8, but no harm if a subsequent patch needs it.)
The proximate cause for this patch is to improve the inlining for INLINE
things that are not functions; this came up in the NDP project. See
Note [Lone variables] in CoreUnfold.
This caused some refactoring that actually made things simpler. In
particular, more of the inlining logic has moved from SimplUtils to
CoreUnfold, where it belongs.
]
[fix race conditions in sandboxIO (#1583, #1922, #1946)
Simon Marlow <[EMAIL PROTECTED]>**20071204114444
using the new block-inheriting forkIO (#1048)
]
[:cd with no argument goes to the user's home directory
Simon Marlow <[EMAIL PROTECTED]>**20071204113945
Seems better than getting a confusing 'cannot find directory' exception.
]
[forkIO starts the new thread blocked if the parent is blocked (#1048)
Simon Marlow <[EMAIL PROTECTED]>**20071204110947]
[Improve eta reduction, to reduce Simplifier iterations
[EMAIL PROTECTED]
I finally got around to investigating why the Simplifier was sometimes
iterating so often. There's a nice example in Text.ParserCombinators.ReadPrec,
which produced:
NOTE: Simplifier still going after 3 iterations; bailing out. Size = 339
NOTE: Simplifier still going after 3 iterations; bailing out. Size = 339
NOTE: Simplifier still going after 3 iterations; bailing out. Size = 339
No progress is being made. It turned out that an interaction between
eta-expansion, casts, and eta reduction was responsible. The change is
small and simple, in SimplUtils.mkLam: do not require the body to be
a Lam when floating the cast outwards.
I also discovered a missing side condition in the same equation, so fixing
that is good too. Now there is no loop when compiling ReadPrec.
Should do a full nofib run though.
]
[Don't default to stripping binaries when installing
Ian Lynagh <[EMAIL PROTECTED]>**20071202195817]
[Improve pretty-printing for Insts
[EMAIL PROTECTED]
[Reorganise TcSimplify (again); FIX Trac #1919
[EMAIL PROTECTED]
This was a bit tricky. We had a "given" dict like (d7:Eq a); then it got
supplied to reduceImplication, which did some zonking, and emerged with
a "needed given" (d7:Eq Int). That got everything confused.
I found a way to simplify matters significantly. Now reduceContext
- first deals with methods/literals/dictionaries
- then deals with implications
Separating things in this way not only made the bug go away, but
eliminated the need for the recently-added "needed-givens" results returned
by checkLoop. Hurrah.
It's still a swamp. But it's a bit better.
]
[FIX #1914: GHCi forgot all the modules that were loaded before an error
Simon Marlow <[EMAIL PROTECTED]>**20071130130734]
[FIX #1744: ignore the byte-order mark at the beginning of a file
Simon Marlow <[EMAIL PROTECTED]>**20071130101100]
[FIX Trac #1935: generate superclass constraints for derived classes
[EMAIL PROTECTED]
This bug only reports a problem with phantom types, but actually
there was quite a long-standing and significant omission in the
constraint generation for derived classes. See
Note [Superclasses of derived instance] in TcDeriv.
The test deriving-1935 tests both cases.
]
[Print a bit more info in VarBinds (no need to merge)
[EMAIL PROTECTED]
[Check for duplicate bindings in CoreLint
[EMAIL PROTECTED]
[add comment
Simon Marlow <[EMAIL PROTECTED]>**20071128111417]
[FIX #1916: don't try to convert float constants to int in CMM optimizer
Bertram Felgenhauer <[EMAIL PROTECTED]>**20071122095513]
[give a more useful message when the static flags have not been initialised
(#1938)
Simon Marlow <[EMAIL PROTECTED]>**20071127135435]
[Rebuild utils with the stage1 compiler when making a bindist; fixes trac #1860
Ian Lynagh <[EMAIL PROTECTED]>**20071127203959
This is a bit unpleasant, as "make binary-dist" really shouldn't actually
build anything, but it works.
]
[Remove the --print-docdir flag
Ian Lynagh <[EMAIL PROTECTED]>**20071127195605
It wasn't doing the right thing for bindists. Let's rethink...
]
[FIX #1925: the interpreter was not maintaining tag bits correctly
Simon Marlow <[EMAIL PROTECTED]>**20071127122614
See comment for details
]
[add missing instruction: ALLOC_AP_NOUPD
Simon Marlow <[EMAIL PROTECTED]>**20071127122604]
[Check tag bits on the fun pointer of a PAP
Simon Marlow <[EMAIL PROTECTED]>**20071126160420]
[canonicalise the path to HsColour
Simon Marlow <[EMAIL PROTECTED]>**20071126141614]
[Consistently put www. on the front of haskell.org in URLs
Ian Lynagh <[EMAIL PROTECTED]>**20071126215256]
[Fix some more URLs
Ian Lynagh <[EMAIL PROTECTED]>**20071126214147]
[Tweak some URLs
Ian Lynagh <[EMAIL PROTECTED]>**20071126194148]
[Fix some links
Ian Lynagh <[EMAIL PROTECTED]>**20071126184406]
[Copy gmp stamps into bindists, so we don't try and rebuild gmp
Ian Lynagh <[EMAIL PROTECTED]>**20071125211919]
[On Windows, Delete the CriticalSection's we Initialize
Ian Lynagh <[EMAIL PROTECTED]>**20071125125845]
[On Windows, add a start menu link to the flag reference
Ian Lynagh <[EMAIL PROTECTED]>**20071125124429]
[Remove html/ from the paths we put in the start menu on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20071125124150]
[MERGED: Make ":" in GHCi repeat the last command
Ian Lynagh <[EMAIL PROTECTED]>**20071125122020
Ian Lynagh <[EMAIL PROTECTED]>**20071124231857
It used to be a synonym for ":r" in 6.6.1, but this wasn't documented or
known about by the developers. In 6.8.1 it was accidentally broken.
This patch brings it back, but as "repeat the last command", similar to
pressing enter in gdb. This is almost as good for people who want it to
reload, and means that it can also be used to repeat commands like :step.
]
[MERGED: Put library docs in a $pkg, rather than $pkgid, directory; fixes trac
#1864
Ian Lynagh <[EMAIL PROTECTED]>**20071124212305
Ian Lynagh <[EMAIL PROTECTED]>**20071124171220
]
[Don't make a library documentation prologue
Ian Lynagh <[EMAIL PROTECTED]>**20071124211943
It's far too large now, and no-one complained when 6.8.1 didn't have one.
]
[Don't put package version numbers in links in index.html
Ian Lynagh <[EMAIL PROTECTED]>**20071124211629]
[Define install-strip in Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20071124205037]
[Define install-strip in distrib/Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20071124204803]
[Install gmp from bindists; fixes trac #1848
Ian Lynagh <[EMAIL PROTECTED]>**20071124185240]
[(native gen) fix code generated for GDTOI on x86_32
Bertram Felgenhauer <[EMAIL PROTECTED]>**20071121063942
See trac #1910.
]
[Copy the INSTALL hack from mk/config.mk.in into distrib/Makefile-bin-vars.in
Ian Lynagh <[EMAIL PROTECTED]>**20071124163028
configure will set INSTALL to ./install-sh if it can't find it in the path,
so we need to replace the . with the path to our root.
]
[Make install-sh executable /before/ we try to find it
Ian Lynagh <[EMAIL PROTECTED]>**20071124162450]
[Document --info in the +RTS -? help
Ian Lynagh <[EMAIL PROTECTED]>**20071123204352]
[MERGED: If we have hscolour then make source code links in teh haddock docs
Ian Lynagh <[EMAIL PROTECTED]>**20071123233113
Fri Nov 23 13:15:59 PST 2007 Ian Lynagh <[EMAIL PROTECTED]>
]
[Tidy and trim the type environment in mkBootModDetails
[EMAIL PROTECTED]
Should fix Trac #1833
We were failing to trim the type envt in mkBootModDetails, so several
functions all called (*), for example, were getting into the interface.
Result chaos. It only actually bites when we do the retyping-loop thing,
which is why it's gone so long without a fix.
]
[refactor: HscNothing and boot modules do not need desugaring
Simon Marlow <[EMAIL PROTECTED]>**20071123135237]
[FIX #1910: fix code generated for GDTOI on x86_32
Bertram Felgenhauer <[EMAIL PROTECTED]>*-20071121102627]
[Properly ppr InstEqs in wanteds of implication constraints
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071122093002]
[FIX #1910: fix code generated for GDTOI on x86_32
Bertram Felgenhauer <[EMAIL PROTECTED]>**20071121102627]
[Add built-in Double operations to vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071122002517]
[Teach vectorisation about Double
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071121054932]
[Vectorise polyexprs with notes
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071121053102]
[Make rebindable do-notation behave as advertised
[EMAIL PROTECTED]
Adopt Trac #1537. The patch ended up a bit bigger than I expected,
so I suggest we do not merge this into the 6.8 branch. But there
is no funadamental reason why not.
With this patch, rebindable do-notation really does type as if you
had written the original (>>) and (>>=) operations in desguared form.
I ended up refactoring some of the (rather complicated) error-context
stuff in TcUnify, by pushing an InstOrigin into tcSubExp and its
various calls. That means we could get rid of tcFunResTy, and the
SubCtxt type. This should improve error messages slightly
in complicated situations, because we have an Origin to hand
to instCall (in the (isSigmaTy actual_ty) case of tc_sub1).
Thanks to Pepe for the first draft of the patch.
]
[Add DEBUG-only flag -dsuppress-uniques to suppress printing of uniques
[EMAIL PROTECTED]
This is intended only for debugging use: it makes it easier to
compare two variants without the variations between uniques mattering.
(Of course, you can't actually feed the output to the C compiler
or assembler and expect anything sensible to happen!)
]
[Add -dcore-lint when validating libraries
[EMAIL PROTECTED]
[Fix Trac #1913: check data const for derived types are in scope
[EMAIL PROTECTED]
When deriving an instance, the data constructors should all be in scope.
This patch checks the condition.
]
[Fix Trac #1909: type of map in docs
[EMAIL PROTECTED]
[Move file locking into the RTS, fixing #629, #1109
Simon Marlow <[EMAIL PROTECTED]>**20071120140859
File locking (of the Haskell 98 variety) was previously done using a
static table with linear search, which had two problems: the array had
a fixed size and was sometimes too small (#1109), and performance of
lockFile/unlockFile was suboptimal due to the linear search.
Also the algorithm failed to count readers as required by Haskell 98
(#629).
Now it's done using a hash table (provided by the RTS). Furthermore I
avoided the extra fstat() for every open file by passing the dev_t and
ino_t into lockFile. This and the improvements to the locking
algorithm result in a healthy 20% or so performance increase for
opening/closing files (see openFile008 test).
]
[FIX Trac #1825: standalone deriving Typeable
[EMAIL PROTECTED]
Standalone deriving of typeable now requires you to say
instance Typeable1 Maybe
which is exactly the shape of instance decl that is generated
by a 'deriving( Typeable )' clause on the data type decl.
This is a bit horrid, but it's the only consistent way, at least
for now. If you say something else, the error messages are helpful.
MERGE to 6.8 branch
]
[FIX #1715: egregious bug in ifaceDeclSubBndrs
[EMAIL PROTECTED]
ifaceDeclSubBndrs didn't have an IfaceSyn case; but with type
families an IfaceSyn can introduce subordinate binders. Result:
chaos.
The fix is easy though. Merge to 6.8 branch.
]
[Always do 'setup makefile' before building each library
Simon Marlow <[EMAIL PROTECTED]>**20071120103329
This forces preprocessing to happen, which is necessary if any of the
.hsc files have been modified. Without this change, a 'setup
makefile' would be required by hand after a .hsc file changed.
Fortunately 'setup makefile' isn't much extra work, and I've made it
not overwrite GNUmakefile if it hasn't changed, which avoids
recalculating the dependencies each time.
]
[FIX #1847 (improve :browse! docs, fix unqual)
[EMAIL PROTECTED]
- add example to docs, explain how to interpret
output of `:browse! Data.Maybe`
- print unqualified names according to current
context, not the context of the target module
]
[Track changes to package ndp
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071120033716]
[Temporary hack for passing PArrays from unvectorised to vectorised code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071120024545]
[Bind NDP stuff to [:.:] arrays
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071119020302]
[Don't treat enumerations specially during vectorisation for the moment
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071119013729]
[Fix bugs in vectorisation of case expressions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071119013714]
[More built-in NDP combinators
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071119012205]
[New vectorisation built-ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118051940]
[Fix bug in conversion unvect/vect
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118051926]
[Extend built-in vectorisation environments
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118045219]
[Fix bug in generation of environments for vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118045203]
[Add builtin var->var mapping to vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118042605]
[Extend vectorisation built-in mappings with datacons
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118034351]
[Change representation of parallel arrays of enumerations
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118033355]
[Add vectorisation-related builtin
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071118031513]
[Teach vectorisation about Bool
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071117042714]
[Incomplete support for boxing during vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071117040739]
[Make sure some TyCons always vectorise to themselves
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071117040537]
[Simple conversion vectorised -> unvectorised
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071117023029]
[Fix bug in case vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071117015014]
[Vectorisation of algebraic case expressions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071116074814]
[More vectorisation-related built-ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071116061831]
[Vectorisation utilities
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071116051037]
[Add vectorisation built-ins
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071116050959]
[Fix vectorisation of binders in case expressions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20071116021833]
[Two small typos in the flags summary (merge to 6.8 branch)
[EMAIL PROTECTED]
[Improve the situation for Trac #959: civilised warning instead of a trace msg
[EMAIL PROTECTED]
This doesn't fix the root cause of the bug, but it makes the report
more civilised, and points to further info.
]
[FIX Trac #1806: test for correct arity for datacon in infix pattern patch
[EMAIL PROTECTED]
Happily the fix is easy; pls merge
]
[Accept x86_64-*-freebsd* as well as amd64-*-freebsd* in configure.ac
Ian Lynagh <[EMAIL PROTECTED]>**20071117154502
Patch from Brian P. O'Hanlon
]
[Attempt at fixing #1873, #1360
Simon Marlow <[EMAIL PROTECTED]>**20071116152148
I think I figured out a reasonable way to manage the GHCi context,
comments welcome.
Rule 1: external package modules in the context are persistent. That
is, when you say 'import Data.Maybe' it survives over :load, :add,
:reload and :cd.
Rule 2: :load and :add remove all home-package modules from the
context and add the rightmost target, as a *-module if possible. This
is as before, and makes sense for :load because we're starting a new
program; the old home-package modules don't make sense any more. For
:add, it usually does what you want, because the new target will
become the context.
Rule 3: any modules from the context that fail to load during a
:reload are remembered, and re-added to the context at the next
successful :reload.
Claus' suggestion about adding the "remembered" modules to the prompt
prefixed with a ! is implemented but commented out. I couldn't
decide whether it was useful or confusing.
One difference that people might notice is that after a :reload where
there were errors, GHCi would previously dump you in the most recent
module that it loaded. Now it dumps you in whatever subset of the
current context still makes sense, and in the common case that will
probably be {Prelude}.
]
[Wibble to fix Trac #1901 (shorten messsage slightly)
[EMAIL PROTECTED]
[Improve links from flag reference to the relevant section; and improve doc of
RankN flags
[EMAIL PROTECTED]
[FIX Trac #1901: check no existential context in H98 mode
[EMAIL PROTECTED]
[Improve documentation of data type declarations (Trac #1901)
[EMAIL PROTECTED]
[Change the command-line semantics for query commands
Simon Marlow <[EMAIL PROTECTED]>**20071116132046
From the help text:
Commands that query the package database (list, latest, describe,
field) operate on the list of databases specified by the flags
--user, --global, and --package-conf. If none of these flags are
given, the default is --global --user.
This makes it possible to query just a single database (e.g. the
global one without the user one), which needed tricks to accomplish
before.
]
[use "ghc-pkg latest --global" instead of "ghc-pkg list --simple-output"
Simon Marlow <[EMAIL PROTECTED]>**20071116122018
The former now does the right thing: it uses the global database only,
and picks the most recent package with the given name.
]
[Disallow installing packages whose names differ in case only.
Simon Marlow <[EMAIL PROTECTED]>**20071116121153
--force overrides. Requested by Duncan Coutts, with a view to
treating package names as case-insensitive in the future.
]
[FIX BUILD (with GHC 6.2.x): update .hi-boot file
Simon Marlow <[EMAIL PROTECTED]>**20071116101227]
[FIX #1828: installing to a patch with spaces in
Simon Marlow <[EMAIL PROTECTED]>**20071115155747
We have to pass the path to gcc when calling windres, which itself
might have spaces in. Furthermore, we have to pass the path to gcc's
tools to gcc. This means getting the quoting right, and after much
experimentation and reading of the windres sources I found something
that works: passing --use-temp-files to windres makes it use its own
implementation of quoting instead of popen(), and this does what we
want. Sigh.
]
[on Windows, install to a directory with spaces (test for #1828)
Simon Marlow <[EMAIL PROTECTED]>**20071115155327]
[FIX #1679: crash on returning from a foreign call
Simon Marlow <[EMAIL PROTECTED]>**20071115131635
We forgot to save a pointer to the BCO over the foreign call. Doing
enough allocation and GC during the call could provoke a crash.
]
[Avoid the use of unversioned package dependencies
Simon Marlow <[EMAIL PROTECTED]>**20071115103249
Fortunately "ghc-pkg list $pkg --simple-output" is a good way to add
the version number.
]
[FIX #1596 (remove deprecated --define-name)
Simon Marlow <[EMAIL PROTECTED]>**20071114165323
Also remove the old command-line syntax for ghc-pkg, which was not
documented. Do not merge.
]
[FIX #1837: remove deprecated support for unversioned dependencies (do not
merge)
Simon Marlow <[EMAIL PROTECTED]>**20071114161044
]
[wibble
Pepe Iborra <[EMAIL PROTECTED]>**20071114233356]
[Make pprNameLoc more robust in absence of loc information
Pepe Iborra <[EMAIL PROTECTED]>**20071114233343]
[Try to manage the size of the text rendered for ':show bindings'
Pepe Iborra <[EMAIL PROTECTED]>**20071114231601]
[Make the Term ppr depth aware
Pepe Iborra <[EMAIL PROTECTED]>**20071114183417]
[Use paragraph fill sep where possible
Pepe Iborra <[EMAIL PROTECTED]>**20071114181233]
[Make SpecConstr work again
[EMAIL PROTECTED]
In a typo I'd written env instead of env', and as a result RULES are
practically guaranteed not to work in a recursive group. This pretty
much kills SpecConstr in its tracks!
Well done Kenny Lu for spotting this. The fix is easy.
Merge into 6.8 please.
]
[Documentation only - fix typo in flags reference
Tim Chevalier <[EMAIL PROTECTED]>**20071115055748]
[Avoid making Either String an instance of Monad in the Haddock parser
David Waern <[EMAIL PROTECTED]>**20071114204050]
[FIX 1463 (implement 'ghc-pkg find-module')
[EMAIL PROTECTED]
- the ticket asks for a module2package lookup in ghc-pkg
(this would be useful to have in cabal, as well)
- we can now ask which packages expose a module we need,
eg, when preparing a cabal file or when getting errors
after package reorganisations:
$ ./ghc-pkg-inplace find-module Var
c:/fptools/ghc/driver/package.conf.inplace:
(ghc-6.9.20071106)
$ ./ghc-pkg-inplace find-module Data.Sequence
c:/fptools/ghc/driver/package.conf.inplace:
containers-0.1
- implemented as a minor variation on listPackages
(as usual, it would be useful if one could combine
multiple queries into one)
]
[remove --define-name from the --help usage message (#1596)
Simon Marlow <[EMAIL PROTECTED]>**20071114153417
]
[FIX #1837: emit deprecated message for unversioned dependencies
Simon Marlow <[EMAIL PROTECTED]>**20071114153010]
[Fix #782, #1483, #1649: Unicode GHCi input
Simon Marlow <[EMAIL PROTECTED]>**20071114151411
GHCi input is now treated universally as UTF-8, except for the Windows
console where we do the correct conversion from the current code
page (see System.Win32.stringToUnicode).
That leaves non-UTF-8 locales on Unix as unsupported, but (a) we only
accept source files in UTF-8 anyway, and (b) UTF-8 is quite ubiquitous
as the default locale.
]
[Fix build
David Waern <[EMAIL PROTECTED]>**20071114125842
I had forgot to update HaddockLex.hi-boot-6, so the build with 6.2.2
failed. This fixes that.
]
[FIX Trac 1662: actually check for existentials in proc patterns
[EMAIL PROTECTED]
I'd fixed the bug for code that should be OK, but had forgotten to
make the test for code that should be rejected!
Test is arrowfail004
]
[FIX Trac 1888; duplicate INLINE pragmas
[EMAIL PROTECTED]
There are actually three things here
- INLINE pragmas weren't being pretty-printed properly
- They were being classified into too-narrow boxes by eqHsSig
- They were being printed in to much detail by hsSigDoc
All easy. Test is rnfail048.
]
[Run the -frule-check pass more often (when asked)
[EMAIL PROTECTED]
[GHCi debugger: added a new flag, -fno-print-binding-contents
Pepe Iborra <[EMAIL PROTECTED]>**20071113174539
The contents of bindings show at breakpoints and by :show bindings
is rendered using the same printer that :print uses.
But sometimes the output it gives spans over too many lines and the
user may want to be able to disable it.
]
[Fix Trac 1865: GHCi debugger crashes with :print
Pepe Iborra <[EMAIL PROTECTED]>**20071113170113]
[Replaced two uses of head b explicit pattern matching
Pepe Iborra <[EMAIL PROTECTED]>**20071013113136]
[Print binding contents in :show bindings
Pepe Iborra <[EMAIL PROTECTED]>**20071006123952]
[ Leftovers from the 1st GHCi debugger prototype
Pepe Iborra <[EMAIL PROTECTED]>**20071004204718]
[Following an indirection doesn't count as a RTTI step
Pepe Iborra <[EMAIL PROTECTED]>**20070928091941]
[FIX #1653 (partially): add -X flags to completion for :set
Simon Marlow <[EMAIL PROTECTED]>**20071113153257]
[Merge from Haddock: Add <<url>> for images
David Waern <[EMAIL PROTECTED]>**20071112220537
A merge of this patch:
Mon Aug 7 16:22:14 CEST 2006 Simon Marlow <[EMAIL PROTECTED]>
* Add <<url>> for images
Submitted by: Lennart Augustsson
Please merge to the 6.8.2 branch.
]
[Improve documentation of INLINE, esp its interactions with other
transformations
[EMAIL PROTECTED]
[Comment re Trac #1220
[EMAIL PROTECTED]
[Merge from Haddock: Modify lexing of /../
David Waern <[EMAIL PROTECTED]>**20071112023856
Tue Aug 28 11:19:54 CEST 2007 Simon Marlow <[EMAIL PROTECTED]>
* Modify lexing of /../
This makes /../ more like '..', so that a single / on a line doesn't
trigger a parse error. This should reduce the causes of accidental
parse errors in Haddock comments; apparently stray / characters are
a common source of failures.
Please merge this to the 6.8.2 branch.
]
[Merge from Haddock: allow blank lines inside code blocks
David Waern <[EMAIL PROTECTED]>**20071112013439
Tue Jan 9 14:14:34 CET 2007 Simon Marlow <[EMAIL PROTECTED]>
* allow blank lines inside a @...@ code block
Please merge this to the 6.8.2 branch
]
[Merge of a patch from the old Haddock branch:
David Waern <[EMAIL PROTECTED]>**20071112013143
Fri Jan 5 12:13:41 CET 2007 Simon Marlow <[EMAIL PROTECTED]>
* Fix up a case of extra vertical space after a code block
Please merge this to the 6.8.2 branch
]
[Remove ex-extralibs from libraries/Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20071111213618]
[Remove the X11 and HGL libraries from extralibs
Ian Lynagh <[EMAIL PROTECTED]>**20071111213447
Don Stewart, X11 maintainer, requested we remove X11, and HGL depends on it
on Linux (and we don't try to build HGL on Windows).
]
[arrows is no longer an extralib
Ian Lynagh <[EMAIL PROTECTED]>**20071027123656]
[Turn -fprint-bind-result off by default
Ian Lynagh <[EMAIL PROTECTED]>**20071111001126]
[TAG 2007-11-11
Ian Lynagh <[EMAIL PROTECTED]>**20071111161540]
Patch bundle hash:
e4e1064df01fc99ce7ab7f1387324d70d021f9e7
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc