Wed Sep 12 16:33:46 CEST 2007  [EMAIL PROTECTED]
  * Forgot to import Data.List.find
New patches:

[Forgot to import Data.List.find
[EMAIL PROTECTED] {
hunk ./compiler/nativeGen/RegSpillClean.hs 45
-import Data.List        ( nub )
+import Data.List        ( find, nub )
}

Context:

[foldl1' was added to Data.List in GHC 6.4.x
Simon Marlow <[EMAIL PROTECTED]>**20070912110909] 
[update .hi-boot-6 to track .lhs-boot
Simon Marlow <[EMAIL PROTECTED]>**20070912104312] 
[update to track .lhs-boot file
Simon Marlow <[EMAIL PROTECTED]>**20070912103417] 
[Refactoring & documenting the Term pprinter used by :print
Pepe Iborra <[EMAIL PROTECTED]>**20070911180411] 
[Custom printer for the Term datatype that won't output TypeRep values
Pepe Iborra <[EMAIL PROTECTED]>*-20070911151454
 
 The term pretty printer used by :print shouldn't output 
 the contents of TypeRep values, e.g. inside Dynamic values
] 
[Try and rewrite reloads to reg-reg moves in the spill cleaner
[EMAIL PROTECTED] 
[Fix type error in MkZipCfg
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070912010458
 - Fixes a bug introduced with the patch named 
   'check for unreachable code only with -DDEBUG'
 - Breakage occured only without -DDEBUG (which is 'valdiate's default!)
] 
[scrape some unused barnacles off of ZipCfg and put them into ZipCfgExtras
Norman Ramsey <[EMAIL PROTECTED]>**20070911154533] 
[split the CmmGraph constructor interface from the representation
Norman Ramsey <[EMAIL PROTECTED]>**20070911150635
 Interface MkZipCfgCmm should now be sufficient for all construction
 needs, though some identifiers are re-exported from (and explained in)
 MkZipCfg.  ZipCfgCmmRep should be used only by modules involved in
 analysis, optimization, or translation of Cmm programs.
] 
[correct two single-identifier bugs that stopped the Adams optimization from working
Norman Ramsey <[EMAIL PROTECTED]>**20070911142914] 
[default ppr method for CmmGraph now tells more about the representation
Norman Ramsey <[EMAIL PROTECTED]>**20070911142701
 (Previously, ppr had tried to make the zipper representation look as
 much like the ListGraph representation as possible.  This decision was
 unhelpful for debugging, so although the old code has been retained,
 the new default is to tell it like it is.  It may be possible to
 retire PprCmmZ one day, although it may be desirable to retain it as
 the internal form becomes less readable.
 
] 
[prettyprint 'hinted' things in a more readable way
Norman Ramsey <[EMAIL PROTECTED]>**20070911142535] 
[check for unreachable code only with -DDEBUG
Norman Ramsey <[EMAIL PROTECTED]>**20070911142410] 
[add a big diagnostic for failures in CmmCvt.toZgraph
Norman Ramsey <[EMAIL PROTECTED]>**20070911142338] 
[Don't try and coalesce nodes with themselves
[EMAIL PROTECTED] 
[Try and allocate vregs spilled/reloaded from some slot to the same hreg
[EMAIL PROTECTED] 
[Better handling of live range joins via spill slots in spill cleaner
[EMAIL PROTECTED] 
[Make sure to coalesce all the nodes found during iterative scanning
[EMAIL PROTECTED] 
[Add iterative coalescing to graph coloring allocator
[EMAIL PROTECTED]
 
 Iterative coalescing interleaves conservative coalesing with the regular
 simplify/scan passes. This increases the chance that nodes will be coalesced
 as they will have a lower degree than at the beginning of simplify. The end
 result is that more register to register moves will be eliminated in the
 output code, though the iterative nature of the algorithm makes it slower
 compared to non-iterative coloring.
 
 Use -fregs-iterative  for graph coloring allocation with iterative coalescing
     -fregs-graph      for non-iterative coalescing.
 
 The plan is for iterative coalescing to be enabled with -O2 and have a 
 quicker, non-iterative algorithm otherwise. The time/benefit tradeoff
 between iterative and not is still being tuned - optimal graph coloring
 is NP-hard, afterall..
] 
[Custom printer for the Term datatype that won't output TypeRep values
Pepe Iborra <[EMAIL PROTECTED]>**20070911151454
 
 The term pretty printer used by :print shouldn't output 
 the contents of TypeRep values, e.g. inside Dynamic values
] 
[FIX #1466 (partly), which was causing concprog001(ghci) to fail
Simon Marlow <[EMAIL PROTECTED]>**20070911130228
 An AP_STACK now ensures that there is at least AP_STACK_SPLIM words of
 stack headroom available after unpacking the payload.  Continuations
 that require more than AP_STACK_SPLIM words of stack must do their own
 stack checks instead of aggregating their stack usage into the parent
 frame.  I have made this change for the interpreter, but not for
 compiled code yet - we should do this in the glorious rewrite of the
 code generator.
] 
[Fix type signatures
Pepe Iborra <[EMAIL PROTECTED]>**20070911113212] 
[Documentation for -fbreak-on-error
Pepe Iborra <[EMAIL PROTECTED]>**20070911101944] 
[GHCi debugger: new flag -fbreak-on-error
Pepe Iborra <[EMAIL PROTECTED]>**20070911101443
     
     This flag works like -fbreak-on-exception, but only stops
     on uncaught exceptions.
] 
[Remove obsolete -fdebugging flag
Pepe Iborra <[EMAIL PROTECTED]>**20070907135857
 
 A left over from the 1st GHCi debugger prototype
] 
[refactoring: eliminate DriverPipeline.CompResult and GHC.upsweep_compile
Simon Marlow <[EMAIL PROTECTED]>**20070910145747] 
[refactoring: inline hscMkCompiler
Simon Marlow <[EMAIL PROTECTED]>**20070910145718] 
[FIX #1677; poor error message for misspelled module declaration
Simon Marlow <[EMAIL PROTECTED]>**20070911085452] 
[Synched documentation links with current directory layout
[EMAIL PROTECTED]
 Somehow the "html" subdirs are gone, this change was not completely
 intentional, but it is nice, anyway. Those subdirs never served any
 real purpose...
 
 MERGE TO STABLE
] 
[Add a BeConservative setting to the make system
Ian Lynagh <[EMAIL PROTECTED]>**20070910133528
 If it is set, we don't try to use clock_gettime
] 
[Nicer GHCi debugger underlining
Pepe Iborra <[EMAIL PROTECTED]>**20070910145319
 
 Improved the underlining of blocks.
 With this patch it does:
 
 Stopped at break020.hs:(6,20)-(7,29)
 _result :: t1 () = _
 5  
                      vv
 6  in_another_decl _ = do line1 0
 7                         line2 0
                                  ^^
 8  
 
 Instead of
 
 Stopped at break020.hs:(6,20)-(7,29)
 _result :: t1 () = _
 5  
 6  in_another_decl _ = do line1 0
                        ^^
 7                         line2 0
                                  ^^
 8  
 
 
] 
[FIX #1669 (GHCi debugger underlining is in the wrong place)
Pepe Iborra <[EMAIL PROTECTED]>**20070910142129
 
 We weren't taking into account the offset added by the line numbers:
 
 Stopped at break020.hs:10:2-8
 _result :: IO () = _
 9  main = do
 10    line1 0
      ^^^^^^^
 11    line2 0
 
 
 This patch adjusts that 
 
] 
[Turn off orphan warnings
Ian Lynagh <[EMAIL PROTECTED]>**20070910122756
 We also avoid using -fno-warn-orphans with older GHCs that don't understand
 the flag.
] 
[Add some more bits to the boring file
Ian Lynagh <[EMAIL PROTECTED]>**20070907212208] 
[Add a --names-only flag for list --simple-output
Ian Lynagh <[EMAIL PROTECTED]>**20070907181944
 We use this in the testsuite to find out which libraries we should run
 the tests from.
] 
[FIX #903: mkWWcpr: not a product
Simon Marlow <[EMAIL PROTECTED]>**20070910103830
 This fixes the long-standing bug that prevents some code with
 mutally-recursive modules from being compiled with --make and -O,
 including GHC itself.  See the comments for details.
 
 There are some additional cleanups that were forced/enabled by this
 patch: I removed importedSrcLoc/importedSrcSpan: it wasn't adding any
 useful information, since a Name already contains its defining Module.
 In fact when re-typechecking an interface file we were wrongly
 replacing the interesting SrcSpans in the Names with boring
 importedSrcSpans, which meant that location information could degrade
 after reloading modules.  Also, recreating all these Names was a waste
 of space/time.
] 
[Cleaned up version of Tom's unflattened skolemOccurs
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070910083457] 
[The RTS is Haddock-less, tell make about it
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Include package documentation, n-th attempt...
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Yet another attempt to get the paths for the installed documentation correct
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Add a "show" target here, too, quite useful for debugging the build process
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Never try to build Haddock docs in ghc/compiler, even with HADDOCK_DOCS=YES
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Removed install-dirs target, it is unnecessary and leads to stray empty directories
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Removed install-dirs from phony targets, it is unused
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Add a crucial missing ;
Ian Lynagh <[EMAIL PROTECTED]>**20070908231024] 
[implement the outOfLine primitive in MkZipCfg (proposed as mkBlock)
Norman Ramsey <[EMAIL PROTECTED]>**20070908155141] 
[withUnique and mkBlock as requested by SLPJ (but only one is implemented)
Norman Ramsey <[EMAIL PROTECTED]>**20070907172030] 
[no registers are available after a call
Norman Ramsey <[EMAIL PROTECTED]>**20070907170843] 
[wrote an analysis to help in sinking Reload instructions
Norman Ramsey <[EMAIL PROTECTED]>**20070907165955] 
[We seem to use Outputable unconditionally these days
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Removed setting of default values for variables which are never empty
[EMAIL PROTECTED]
 The standard autoconf variables like prefix, exec_prefix, ... are always set by
 configure, so there is no need to provide explicit defaults in the Makefile.
 
 The lines were introduced about a decade ago, perhaps there were some bugs in
 ancient autoconfs, but today I can't think of a reason why this should be still
 necessary.
] 
[Use := for PACKAGE_TARNAME, no reason for not doing so
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Removed unused oldincludedir, things are already complicated enough
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Added comment about GNU coding standards/autoconf history
[EMAIL PROTECTED]
 MERGE TO STABLE
] 
[Fixing Hpc's Finite Map compat lib for ghc 6.2.1
[EMAIL PROTECTED] 
[updating hpc toolkit
[EMAIL PROTECTED]
 
 The hpc overlay has been ported from hpc-0.4
 The new API for readMix is now used.
 
] 
[Fixing hpc to allow use of hash function to seperate source files on source path
[EMAIL PROTECTED] 
[Make various assertions work when !DEBUG
Ian Lynagh <[EMAIL PROTECTED]>**20070908003112] 
[Fix assertions in RtClosureInspect
Ian Lynagh <[EMAIL PROTECTED]>**20070907233330] 
[In ASSERT and friends, use all the expressions we are passed even if !DEBUG
Ian Lynagh <[EMAIL PROTECTED]>**20070907233324
 Otherwise we may get unused variable warnings. GHC should optimise them
 all out for us.
] 
[Don't put directories for unbuildable libraries in bindists
Ian Lynagh <[EMAIL PROTECTED]>**20070907210037
 We think there is a library there, and then installPackage fails to
 install it.
] 
[a good deal of salutory renaming
Norman Ramsey <[EMAIL PROTECTED]>**20070907161246
 I've renamed a number of type and data constructors within Cmm so that
 the names used in the compiler may more closely reflect the C--
 specification 2.1.  I've done a bit of other renaming as well.
 Highlights:
 
   CmmFormal and CmmActual now bear a CmmKind (which for now is a
                                               MachHint as before)
   CmmFormals = [CmmFormal] and CmmActuals = [CmmActual]
   
   suitable changes have been made to both code and nonterminals in the
   Cmm parser (which is as yet untested)
 
   For reasons I don't understand, parts of the code generator use a
   sequence of 'formal parameters' with no C-- kinds.  For these we now
   have the types
     type CmmFormalWithoutKind   = LocalReg
     type CmmFormalsWithoutKinds = [CmmFormalWithoutKind]
 
   A great many appearances of (Tau, MachHint) have been simplified to
   the appropriate CmmFormal or CmmActual, though I'm sure there are
   more opportunities.
 
   Kind and its data constructors are now renamed to
      data GCKind = GCKindPtr | GCKindNonPtr 
   to avoid confusion with the Kind used in the type checker and with CmmKind.
 
 Finally, in a somewhat unrelated bit (and in honor of Simon PJ, who
 thought of the name), the Whalley/Davidson 'transaction limit' is now
 called 'OptimizationFuel' with the net effect that there are no longer
 two unrelated uses of the abbreviation 'tx'.
 
 
] 
[Made TcTyFuns warning clean
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070907121113] 
[fix for Simple9
Tom Schrijvers <[EMAIL PROTECTED]>**20070906171703
 
 No longer include non-indexed arguments
 in lookup of matching type function clause.
 By including non-indexed (additional) arguments,
 the lookup always fails.
] 
[Improved error messages for higher-rank equality contexts
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070907101901] 
[FIX: Type families test Simple14
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070907092217] 
[refactor duplicated code in main/HscMain 
Norman Ramsey <[EMAIL PROTECTED]>**20070907132442
   I kept making mistakes because all the ZipCfg and CPS stuff
   was called from two different places (compiling Haskell and 
   compiling Cmm).  Now it is called from a single place, and therefore
   successfully turned off by default.
 
   I still don't know why turning it on causes rts/Apply.cmm not to
   compile; that development is new since yesterday.
 
] 
[in CmmExpr, always have (Show GlobalReg), regardless of DEBUG setting
Norman Ramsey <[EMAIL PROTECTED]>**20070907132417] 
[Rejig boot
Ian Lynagh <[EMAIL PROTECTED]>**20070907122847
 find on Windows doesn't understand -L, so stop trying to be clever and
 just autoreconf everything.
 
 Also, print out the names of directories as we autoreconf them, so that
 if autoreconfing one breaks then we know which one it was.
] 
[Fix publishing
Ian Lynagh <[EMAIL PROTECTED]>**20070907121414
 Paths like c:/foo/bar get misinterpreted by rsync (really SSH?), as it
 thinks we want /foo/bar on the machine c.
] 
[Fix building with old compilers which don't understand -fno-warn-orphans
Ian Lynagh <[EMAIL PROTECTED]>**20070906195737] 
[Tiny optimisation/simplification to FunDeps.grow
[EMAIL PROTECTED] 
[Warning police
[EMAIL PROTECTED] 
[Add clarifying comments
[EMAIL PROTECTED] 
[Fix zonking in mkExports
[EMAIL PROTECTED]
 
 I'd missed zonk, so that an error message for missing type signature
 read (unhelpfully)
 
   main/GHC.hs:1070:0:
      Warning: Definition but no type signature for `upsweep''
               Inferred type: upsweep' :: forall t1. t
 
 The trouble was that 't' hadn't been zonked.
 
 Push to the stable branch
 
] 
[adding new files to do with new cmm functionality
Norman Ramsey <[EMAIL PROTECTED]>**20070907075754] 
[Set do_bold based on $TERM, not platform
Ian Lynagh <[EMAIL PROTECTED]>**20070906175535] 
[Updates to work with latest cabal.
Duncan Coutts <[EMAIL PROTECTED]>**20070906131726] 
[massive changes to add a 'zipper' representation of C--
Norman Ramsey <[EMAIL PROTECTED]>**20070906161948
 
 Changes too numerous to comment on, but here is some old history that
 I saved: 
 
 
 Wed Aug 15 11:07:13 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * type synonyms made consistent with new Cmm types
 
     M ./compiler/nativeGen/MachInstrs.hs -2 +2
 
 Mon Aug 20 19:22:14 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * pushing return info beyond cmm into codegen
 
     M ./compiler/codeGen/Bitmap.hs r3
     M ./compiler/codeGen/CgBindery.lhs r3
     M ./compiler/codeGen/CgCallConv.hs r3
     M ./compiler/codeGen/CgCase.lhs r3
     M ./compiler/codeGen/CgClosure.lhs r3
     M ./compiler/codeGen/CgCon.lhs r3
     M ./compiler/codeGen/CgExpr.lhs r3
     M ./compiler/codeGen/CgForeignCall.hs -6 +7 r3
     M ./compiler/codeGen/CgHeapery.lhs r3
     M ./compiler/codeGen/CgHpc.hs +1 r3
     M ./compiler/codeGen/CgInfoTbls.hs r3
     M ./compiler/codeGen/CgLetNoEscape.lhs r3
     M ./compiler/codeGen/CgMonad.lhs r3
     M ./compiler/codeGen/CgParallel.hs r3
     M ./compiler/codeGen/CgPrimOp.hs +3 r3
     M ./compiler/codeGen/CgProf.hs r3
     M ./compiler/codeGen/CgStackery.lhs r3
     M ./compiler/codeGen/CgTailCall.lhs r3
     M ./compiler/codeGen/CgTicky.hs r3
     M ./compiler/codeGen/CgUtils.hs -1 +1 r3
     M ./compiler/codeGen/ClosureInfo.lhs r3
     M ./compiler/codeGen/CodeGen.lhs r3
     M ./compiler/codeGen/SMRep.lhs r3
     M ./compiler/nativeGen/AsmCodeGen.lhs -2 +2 r1
     M ./compiler/nativeGen/MachCodeGen.hs -3 +3 r1
     M ./compiler/nativeGen/MachInstrs.hs r1
     M ./compiler/nativeGen/MachRegs.lhs r1
     M ./compiler/nativeGen/NCGMonad.hs r1
     M ./compiler/nativeGen/PositionIndependentCode.hs r1
     M ./compiler/nativeGen/PprMach.hs r1
     M ./compiler/nativeGen/RegAllocInfo.hs r1
     M ./compiler/nativeGen/RegisterAlloc.hs r1
 
 Mon Aug 20 20:54:41 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * put CmmReturnInfo into a CmmCall (and related types)
 
     M ./compiler/cmm/Cmm.hs -2 +1 r3
     M ./compiler/cmm/CmmBrokenBlock.hs -13 +12 r1
     M ./compiler/cmm/CmmCPS.hs -3 +3
     M ./compiler/cmm/CmmCPSGen.hs -8 +6 r1
     M ./compiler/cmm/CmmLint.hs -1 +1
     M ./compiler/cmm/CmmLive.hs -1 +1
     M ./compiler/cmm/CmmOpt.hs -3 +3
     M ./compiler/cmm/CmmParse.y -6 +6 r3
     M ./compiler/cmm/PprC.hs -3 +3
     M ./compiler/cmm/PprCmm.hs -7 +4 r2
     M ./compiler/codeGen/CgForeignCall.hs -7 +6 r2
     M ./compiler/codeGen/CgHpc.hs -1 r1
     M ./compiler/codeGen/CgPrimOp.hs -3 r1
     M ./compiler/codeGen/CgUtils.hs -1 +1 r1
     M ./compiler/nativeGen/AsmCodeGen.lhs -2 +2
     M ./compiler/nativeGen/MachCodeGen.hs -3 +3 r1
 
 Tue Aug 21 18:09:13 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * add call info in nativeGen
 
     M ./compiler/nativeGen/AsmCodeGen.lhs r1
     M ./compiler/nativeGen/MachInstrs.hs r1
     M ./compiler/nativeGen/MachRegs.lhs r1
     M ./compiler/nativeGen/NCGMonad.hs r1
     M ./compiler/nativeGen/PositionIndependentCode.hs r1
     M ./compiler/nativeGen/PprMach.hs r1
     M ./compiler/nativeGen/RegAllocInfo.hs r1
 
 Wed Aug 22 16:41:58 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * ListGraph is now a newtype, not a synonym
   The resultant bookkeepping is unenviable, but the change
   greatly simplifies our ability to make Cmm things propertly
   Outputable for both list-graph and zipper-graph representations.
 
     M ./compiler/cmm/Cmm.hs -5 +3
     M ./compiler/cmm/CmmCPS.hs -2 +2
     M ./compiler/cmm/CmmCPSGen.hs -1 +1
     M ./compiler/cmm/CmmContFlowOpt.hs -3 +3
     M ./compiler/cmm/CmmCvt.hs -2 +2
     M ./compiler/cmm/CmmInfo.hs -2 +3
     M ./compiler/cmm/CmmLint.hs -1 +1
     M ./compiler/cmm/CmmOpt.hs -2 +2
     M ./compiler/cmm/PprC.hs -1 +1
     M ./compiler/cmm/PprCmm.hs -5 +8
     M ./compiler/cmm/PprCmmZ.hs -7 +1
     M ./compiler/codeGen/CgMonad.lhs -1 +1
     M ./compiler/nativeGen/AsmCodeGen.lhs -15 +15
     M ./compiler/nativeGen/MachCodeGen.hs -2 +2
     M ./compiler/nativeGen/PositionIndependentCode.hs -6 +6
     M ./compiler/nativeGen/PprMach.hs -3 +2
     M ./compiler/nativeGen/RegAllocColor.hs +1
     M ./compiler/nativeGen/RegAllocLinear.hs -4 +5
     M ./compiler/nativeGen/RegCoalesce.hs -6 +6
     M ./compiler/nativeGen/RegLiveness.hs -12 +12
 
 Thu Aug 23 13:44:49 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * diagnostic assistance in case fromJust fails
 
     M ./compiler/nativeGen/MachCodeGen.hs -2 +5
 
 Thu Aug 23 14:07:28 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * give every block, even the first, a label
     With branch-chain elimination, the first block of a procedure
     might be the target of a branch.  This actually happens to 
     a dozen or more procedures in the run-time system.
 
     M ./compiler/nativeGen/PprMach.hs -8 +3
 
 Fri Aug 24 17:27:04 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * clean up the code in PprMach
 
     M ./compiler/nativeGen/PprMach.hs -16 +14
 
 Fri Aug 24 19:35:03 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * a bunch of impedance matching to get the compiler to build, plus 
    * the plus is diagnostics for unreachable code, which required
      moving a lot of prettyprinting code
 
     M ./compiler/cmm/Cmm.hs -7 +5
     M ./compiler/cmm/CmmCPSZ.hs -1 +1
     M ./compiler/cmm/CmmCvt.hs -8 +8
     M ./compiler/cmm/CmmParse.y -4 +3
     M ./compiler/cmm/MkZipCfg.hs -19 +9
     M ./compiler/cmm/PprCmmZ.hs -118 +4
     M ./compiler/cmm/ZipCfg.hs -1 +13
     M ./compiler/cmm/ZipCfgCmm.hs -10 +129
     M ./compiler/main/HscMain.lhs -4 +4
     M ./compiler/nativeGen/NCGMonad.hs -2 +2
     M ./compiler/nativeGen/RegAllocInfo.hs -3 +3
 
 Fri Aug 31 14:38:02 BST 2007  Norman Ramsey <[EMAIL PROTECTED]>
   * fix a warning about an import
 
     M ./compiler/nativeGen/RegAllocColor.hs -1 +1
 
] 
[Make installPackage install settings from the [package].buildinfo file.
[EMAIL PROTECTED]
 
 M ./libraries/installPackage.hs -1 +14
] 
[Wibble some variable definitions to fix installation of bindists
Ian Lynagh <[EMAIL PROTECTED]>**20070906140430] 
[Remove hardtop_plat/FPTOOLS_TOP_ABS_PLATFORM
Ian Lynagh <[EMAIL PROTECTED]>**20070906122036
 They are now the same as hardtop/FPTOOLS_TOP_ABS, so use those instead.
 
 Also removed some substitutions of / for \, as we now use a Haskell
 program to find the top path, and it only makes paths with /s in.
] 
[Cure space leak in coloring register allocator
[EMAIL PROTECTED]
 
 We now do a deep seq on the graph after it is 'built', but before coloring.
 Without this, the colorer will just force bits of it and the heap will
 fill up with half evaluated pieces of graph from previous build/spill
 stages and zillions of apply thunks.
 
] 
[Small improvement to GraphColor.selectColor
[EMAIL PROTECTED]
 
 When selecting a color for a node, try and avoid using colors that
 conflicting nodes prefer. Not sure if this'll make much difference,
 but it was easy enough to add..
 
] 
[Set GhcBootLibs=YES in mk/validate-settings.mk
Ian Lynagh <[EMAIL PROTECTED]>**20070906113629] 
[Quote all the arguments to installPackage
Ian Lynagh <[EMAIL PROTECTED]>**20070905232959
 Makes it obvious what's going on if any are empty.
] 
[warning police
Pepe Iborra <[EMAIL PROTECTED]>**20070906102417] 
[Cleanup of equality rewriting and no swapInsts for wanteds
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070906115818
 - Removed code duplication
 - Added comments
 - Took out swapInsts for wanteds.  With the recent extension to swapInsts
   it does mess up error messages if applied to wanteds and i should not be
   necessary.
 NB: The code actually shrunk.  Line increase is due to comments.
] 
[Remove EqInsts from addSCs to avoid -DDEBUG warnings
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070906095102] 
[EqInst related clean up
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070906095018
 - Remove some unused and some superflous functions
 - Add comments regarding ancestor equalities
 - Tidied ancestor equality computation
 - Replace some incorrect instToId by instToVar (but there are still some
   bad ones around as we still get warnings with -DDEBUG)
 - Some cleaned up layout
 NB: Code growth is just due to more comments.
] 
[Remove dead code in TcSimplify
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070906031719] 
[Fix -DDEBUG warning
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070906023914] 
[also swap for variables in completion algorithm
Tom Schrijvers <[EMAIL PROTECTED]>**20070905134426] 
[FIX #1465, error messages could sometimes say things like "A.T doesn't match A.T"
Simon Marlow <[EMAIL PROTECTED]>**20070906093744
 This turned out to be a black hole, however we believe we now have a
 plan that does the right thing and shouldn't need to change again.
 Error messages will only ever refer to a name in an unambiguous way,
 falling back to <package>:<module>.<name> if no unambiguous shorter
 variant can be found.  See HscTypes.mkPrintUnqualified for the
 details.
 
 Earlier hacks to work around this problem have been removed (TcSimplify).
] 
[fix error in .hi-boot-6
Simon Marlow <[EMAIL PROTECTED]>**20070905112503] 
[Improve GraphColor.colorScan
[EMAIL PROTECTED]
 
 Testing whether a node in the conflict graph is trivially 
 colorable (triv) is still a somewhat expensive operation.
 
 When we find a triv node during scanning, even though we remove
 it and its edges from the graph, this is unlikely to to make the
 nodes we've just scanned become triv - so there's not much point
 re-scanning them right away.
 
 Scanning now takes place in passes. We scan the whole graph for
 triv nodes and remove all the ones found in a batch before rescanning
 old nodes.
 
 Register allocation for SHA1.lhs now takes (just) 40% of total
 compile time with -O2 -fregs-graph on x86
 
] 
[Fix OS X warnings
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070906004831] 
[Declare ctime_r on Mac OS
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070906001613
 
 On Mac OS, ctime_r is not declared in time.h if _POSIX_C_SOURCE is defined. We
 work around this by providing a declaration ourselves.
 
] 
[FIX #1651: use family instances during interactive typechecking
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070905130244] 
[Add an OPTIONS -w pragma to utils/genprimopcode/Lexer.xx
Ian Lynagh <[EMAIL PROTECTED]>**20070905184808
 SPJ reports that it has warnings (=> errors with -Werror) on Windows.
] 
[Build settings for validation are now in mk/validate-settings.mk
Ian Lynagh <[EMAIL PROTECTED]>**20070905184614] 
[Don't give warnings in compat
Ian Lynagh <[EMAIL PROTECTED]>**20070905182923
 There are lots of warnings in here due to things like modules being
 imported that, in some versions of GHC, aren't used. Thus we don't
 give any warnings in here, and therefore validating with -Werror won't
 make the build fail.
 
 An alternative would be to do
 SRC_HC_OPTS := $(filter-out -Werror,$(SRC_HC_OPTS))
 but if warnings are expected then there is little point in spewing them
 out anyway.
 
 On the other hand, there aren't any warnings for me (GHC 6.6 on Linux/amd64),
 so perhaps it would be worth fixing them instead.
] 
[Typo
Ian Lynagh <[EMAIL PROTECTED]>**20070905161402] 
[Fix bindist creation on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20070905161354] 
[Fix up bindist creation and publishing
Ian Lynagh <[EMAIL PROTECTED]>**20070905160641] 
[Refactor, improve, and document the deriving mechanism
[EMAIL PROTECTED]
 
 This patch does a fairly major clean-up of the code that implements 'deriving.
 
 * The big changes are in TcDeriv, which is dramatically cleaned up.
   In particular, there is a clear split into
 	a) inference of instance contexts for deriving clauses
 	b) generation of the derived code, given a context 
   Step (a) is skipped for standalone instance decls, which 
   have an explicitly provided context.
 
 * The handling of "taggery", which is cooperative between TcDeriv and
   TcGenDeriv, is cleaned up a lot
 
 * I have added documentation for standalone deriving (which was 
   previously wrong).
 
 * The Haskell report is vague on exactly when a deriving clause should
   succeed.  Prodded by Conal I have loosened the rules slightly, thereyb
   making drv015 work again, and documented the rules in the user manual.
 
 I believe this patch validates ok (once I've update the test suite)
 and can go into the 6.8 branch.
 
] 
[Further documentation about mdo, suggested by Benjamin Franksen
[EMAIL PROTECTED] 
[Refactor MachRegs.trivColorable to do unboxed accumulation
[EMAIL PROTECTED]
 
 trivColorable was soaking up total 31% time, 41% alloc when
 compiling SHA1.lhs with -O2 -fregs-graph on x86.
 
 Refactoring to use unboxed accumulators and walk directly
 over the UniqFM holding the set of conflicts reduces this 
 to 17% time, 6% alloc.
] 
[change of representation for GenCmm, GenCmmTop, CmmProc
Norman Ramsey <[EMAIL PROTECTED]>**20070905164802
 The type parameter to a C-- procedure now represents a control-flow
 graph, not a single instruction.  The newtype ListGraph preserves the 
 current representation while enabling other representations and a
 sensible way of prettyprinting.  Except for a few changes in the
 prettyprinter the new compiler binary should be bit-for-bit identical
 to the old.
] 
[enable and slay warnings in cmm/Cmm.hs
Norman Ramsey <[EMAIL PROTECTED]>**20070905164646] 
[fix warnings
Simon Marlow <[EMAIL PROTECTED]>**20070905114205] 
[FIX #1650: ".boot modules interact badly with the ghci debugger"
Simon Marlow <[EMAIL PROTECTED]>**20070905104716
 
 In fact hs-boot files had nothing to do with it: the problem was that
 GHCi would forget the breakpoint information for a module that had
 been reloaded but not recompiled.  It's amazing that we never noticed
 this before.
 
 The ModBreaks were in the ModDetails, which was the wrong place.  When
 we avoid recompiling a module, ModDetails is regenerated from ModIface
 by typecheckIface, and at that point it has no idea what the ModBreaks
 should be, so typecheckIface made it empty.  The right place for the
 ModBreaks to go is with the Linkable, which is retained when
 compilation is avoided.  So now I've placed the ModBreaks in with the
 CompiledByteCode, which also makes it clear that only byte-code
 modules have breakpoints.
 
 This fixes break022/break023
 
] 
[Fix boot: it was avoiding autoreconfing
Simon Marlow <[EMAIL PROTECTED]>**20070905101419
 Two problems here: find needs to dereference symbolic links (-L
 option, I really hope that's portable), and we need to notice when
 aclocal.m4 is updated.  
 
 Somehow I think this was easier when it just always ran
 autoreconf... what was wrong with that?
] 
[don't generate .hi-boot/.o-boot files in GHCi
Simon Marlow <[EMAIL PROTECTED]>**20070904141231] 
[refactoring only
Simon Marlow <[EMAIL PROTECTED]>**20070904141209] 
[completion for modules in 'import M'
Simon Marlow <[EMAIL PROTECTED]>**20070904104458] 
[make the GhcThreaded setting lazy, because GhcUnregisterised might not be set yet
Simon Marlow <[EMAIL PROTECTED]>**20070904101729] 
[{Enter,Leave}CriticalSection imports should be outside #ifdef __PIC__
Simon Marlow <[EMAIL PROTECTED]>**20070905084941] 
[warning police
[EMAIL PROTECTED] 
[Do conservative coalescing in register allocator
[EMAIL PROTECTED]
 
 Avoid coalescing nodes in the register conflict graph if the
 new node will not be trivially colorable. Also remove the
 front end aggressive coalescing pass.
   
 For typical Haskell code the graph coloring allocator now does
 about as well as the linear allocator.
   
 For code with a large amount of register pressure it does much
 better, but takes longer.
   
 For SHA1.lhs from darcs on x86
    
           spills    reloads    reg-reg-moves
           inserted   inserted  left in code   compile-time
   linear    1068      1311        229            7.69(s)
   graph      387       902        340           16.12(s)
 
] 
[Use dlsym on OS X if available
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070905052213
 
 On OS X 10.4 and newer, we have to use dlsym because the old NS* interface has
 been deprecated. The patch checks for HAVE_DLFCN_H instead of switching on
 the OS version.
 
 There is one additional quirk: although OS X prefixes global symbols with an
 underscore, dlsym expects its argument NOT to have a leading underscore. As a
 hack, we simply strip it off in lookupSymbol. Something a bit more elaborate
 might be cleaner.
] 
[bug fix in Decomp step of completion algorithm for given equations
Tom Schrijvers <[EMAIL PROTECTED]>**20070904123945] 
[fix of wanted equational class context
Tom Schrijvers <[EMAIL PROTECTED]>**20070904080014
 
 Previously failed to account for equational
 class context for wanted dictionary contraints, e.g. wanted C a
 in 
 
 	class a ~ Int => C a
 	instance C Int
 
 should give rise to wanted a ~ Int and consequently discharge a ~ Int by
 unifying a with Int and then discharge C Int with the instance.
 
 All ancestor equalities are taken into account.
 
 
] 
[Set datarootdir to the value configure gives us (if any) so datadir works
Ian Lynagh <[EMAIL PROTECTED]>**20070905013239
 We then set datarootdir to something else later on so that things still
 work when configure doesn't set it.
] 
[FIX: Correct Leave/EnterCriticalSection imports
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070905010217] 
[Don't hardwire the build path into the Haddock docs
[EMAIL PROTECTED]
 Formerly, the ghc-pkg was called to get the HTML dirs for other packages, but
 of course doing this at *build* time is totally wrong. Now we use a relative
 path, just like before. This is probably not perfect, but much better than
 before.
 
 As a sidenote: Cabal calls the relevant flag "html-location", ghc-pkg calls the
 field "haddock-html", and Haddock itself uses it as part of "read-interface".
 Too much creativity is sometimes a bad thing...
] 
[put the @N suffix on stdcall foreign calls in .cmm code
Simon Marlow <[EMAIL PROTECTED]>**20070904142853
 This applies to EnterCriticalSection and LeaveCriticalSection in the RTS
] 
[Add a -Warn flag
Ian Lynagh <[EMAIL PROTECTED]>**20070904141028] 
[Always turn on -Wall -Werror when compiling the compiler, even for stage 1
Ian Lynagh <[EMAIL PROTECTED]>**20070904140324] 
[Fix CodingStyle#Warnings URLs
Ian Lynagh <[EMAIL PROTECTED]>**20070904140115] 
[OPTIONS_GHC overrides the command-line, not the other way around
Simon Marlow <[EMAIL PROTECTED]>**20070904100623] 
[fix cut-and-pasto
Simon Marlow <[EMAIL PROTECTED]>**20070904100526] 
[FIX #1651: unBox types when deferring unification
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070904072542
 - This fixes the first part of #1651; ie, the panic in ghci.
] 
[Better error message for unsolvable equalities
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070903074528] 
[Use := rather than = when assigning make variables to avoid cycles
Ian Lynagh <[EMAIL PROTECTED]>**20070903235117] 
[Don't use autoconf's datarootdir as <2.60 doesn't have it
Ian Lynagh <[EMAIL PROTECTED]>**20070903234504] 
[Use OPTIONS rather than OPTIONS_GHC for pragmas
Ian Lynagh <[EMAIL PROTECTED]>**20070903233903
 Older GHCs can't parse OPTIONS_GHC.
 This also changes the URL referenced for the -w options from
 WorkingConventions#Warnings to CodingStyle#Warnings for the compiler
 modules.
] 
[Fix building RTS with gcc 2.*; declare all variables at the top of a block
Ian Lynagh <[EMAIL PROTECTED]>**20070903165847
 Patch from Audrey Tang.
] 
[fix build (sorry, forgot to push with previous patch)
Simon Marlow <[EMAIL PROTECTED]>**20070903200615] 
[remove debugging code
Simon Marlow <[EMAIL PROTECTED]>**20070903200003] 
[NCG space leak avoidance refactor
[EMAIL PROTECTED] 
[Do aggressive register coalescing
[EMAIL PROTECTED]
 Conservative and iterative coalescing come next.
] 
[Add coalescence edges back to the register graph
[EMAIL PROTECTED] 
[FIX #1623: disable the timer signal when the system is idle (threaded RTS only)
Simon Marlow <[EMAIL PROTECTED]>**20070903132523
 Having a timer signal go off regularly is bad for power consumption,
 and generally bad practice anyway (it means the app cannot be
 completely swapped out, for example).  Fortunately the threaded RTS
 already had a way to detect when the system was idle, so that it can
 trigger a GC and thereby find deadlocks.  After performing the GC, we
 now turn off timer signals, and re-enable them again just before
 running any Haskell code.
] 
[FIX #1648: rts_mkWord64 was missing
Simon Marlow <[EMAIL PROTECTED]>**20070903131625
 Also noticed a few others from RtsAPI were missing, so I added them all
] 
[FIX for #1080
Ross Paterson <[EMAIL PROTECTED]>**20070903141044
 
 Arrow desugaring now uses a private version of collectPatBinders and
 friends, in order to include dictionary bindings from ConPatOut.
 
 It doesn't fix arrowrun004 (#1333), though.
] 
[Fix space leak in NCG
[EMAIL PROTECTED] 
[GhcThreaded was bogusly off by default due to things being in the wrong order
Simon Marlow <[EMAIL PROTECTED]>**20070903103829] 
[bump MAX_THUNK_SELECTOR_DEPTH from 8 to 16
Simon Marlow <[EMAIL PROTECTED]>**20070903101912
 this "fixes" #1038, in that the example runs in constant space, but
 it's really only working around the problem.  I have a better patch,
 attached to ticket #1038, but I'm wary about tinkering with this
 notorious bug farm so close to the release, so I'll push it after
 6.8.1.
] 
[comments only
Simon Marlow <[EMAIL PROTECTED]>**20070831092224
 I had planned to do findEnclosingDecl a different way, so add a ToDo
 as a reminder.
] 
[Suppress some warnings on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20070902222048] 
[Fix warnings in ghc-pkg on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20070902221442] 
[Fix and supress some warnings, and turn on -Werror when validating
Ian Lynagh <[EMAIL PROTECTED]>**20070902193918] 
[Explicitly set "docdir" when calling make, configure's --docdir seems to be ignored
[EMAIL PROTECTED] 
[Use DESTDIR for installation
[EMAIL PROTECTED] 
[Fixed TeX syntax
[EMAIL PROTECTED] 
[Set -Wall -fno-warn-name-shadowing in compiler/ when stage /= 2
Ian Lynagh <[EMAIL PROTECTED]>**20070901113018] 
[Add {-# OPTIONS_GHC -w #-} and some blurb to all compiler modules
Ian Lynagh <[EMAIL PROTECTED]>**20070901112130] 
[Add a --print-docdir flag
Ian Lynagh <[EMAIL PROTECTED]>**20070831231538] 
[Follow Cabal module movements in installPackage
Ian Lynagh <[EMAIL PROTECTED]>**20070831181359] 
[Follow Cabal's move Distribution.Program -> Distribution.Simple.Program
Ian Lynagh <[EMAIL PROTECTED]>**20070831175217] 
[Don't use the --docdir etc that autoconf provides
Ian Lynagh <[EMAIL PROTECTED]>**20070831173903
 Older autoconfs (<2.60?) don't understand them.
] 
[Don't try to copy haddock index files if we haven't built the docs.
[EMAIL PROTECTED]
 
 M ./libraries/Makefile +2
] 
[Use cp -R instead of cp -a (it's more portable).
[EMAIL PROTECTED]
 
 M ./libraries/Makefile -3 +3
] 
[Fix installing the libraries when there is no DESTDIR
Ian Lynagh <[EMAIL PROTECTED]>**20070831015442] 
[Make the doc index page obey DESTDIR
Ian Lynagh <[EMAIL PROTECTED]>**20070831014537] 
[Make rts docs obey DESTDIR
Ian Lynagh <[EMAIL PROTECTED]>**20070831014346] 
[Make the manpage obey DESTDIR
Ian Lynagh <[EMAIL PROTECTED]>**20070831014253] 
[Obey DESTDIR when installing library docs
Ian Lynagh <[EMAIL PROTECTED]>**20070831012351] 
[typo in DLL code
Simon Marlow <[EMAIL PROTECTED]>**20070830143105] 
[Windows: give a better error message when running out of memory
Simon Marlow <[EMAIL PROTECTED]>**20070830135146
 I think this fixes #1209
 
 Previously:
 
 outofmem.exe: getMBlocks: VirtualAlloc MEM_RESERVE 1025 blocks failed: Not enoug
 h storage is available to process this command.
 
 Now:
 
 outofmem.exe: out of memory
] 
[Remove NDP-related stuff from PrelNames
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831045411
 
 We don't need fixed Names for NDP built-ins. Instead, we can look them up
 ourselves during VM initialisation.
] 
[Vectorisation of enumeration types
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831041822] 
[Number data constructors from 0 when vectorising
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831032528] 
[Rename functions
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831032125] 
[Refactoring
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831015312] 
[Refactoring
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831012638] 
[Fix vectorisation of nullary data constructors
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070831005912] 
[Do not unnecessarily wrap array components
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830062958] 
[Remove dead code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830055444] 
[Fix vectorisation of unary data constructors
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830040252] 
[Fix vectorisation of sum type constructors
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830035225] 
[Track changes to package ndp (use PArray_Int# instead of UArr Int)
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830032104] 
[Find the correct array type for primitive tycons
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830025224] 
[Add code for looking up PA methods of primitive TyCons
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070830014257] 
[Delete dead code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070829145630] 
[Rewrite vectorisation of product DataCon workers
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070829145446] 
[Rewrite generation of PA dictionaries
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070829064258] 
[Complete PA dictionary generation for product types
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824230152] 
[Simplify generation of PR dictionaries for products
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824071925] 
[Remove unused vectorisation built-in
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824051524] 
[Adapt PArray instance generation to new scheme
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824051242] 
[Add UArr built-in
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824051213] 
[Modify generation of PR dictionaries for new scheme
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824043144] 
[Refactoring
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824040901] 
[Remove dead code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824035751] 
[Fix buildFromPRepr
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824035700] 
[Move code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824032930] 
[Move code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824032743] 
[Delete dead code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824031504] 
[Change buildToPRepr to work with the new representation scheme
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824031407] 
[Remove Embed and related stuff from vectorisation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824023030] 
[Encode generic representation of vectorised TyCons by a data type
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070824012140] 
[Remove dead code
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070823135810] 
[Conversions to/from generic array representation (not finished yet)
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070823135649] 
[Use n-ary sums and products for NDP's generic representation
Roman Leshchinskiy <[EMAIL PROTECTED]>**20070823060945
 
 Originally, we wanted to only use binary ones, at least initially. But this
 would a lot of fiddling with selectors when converting to/from generic
 array representations. This is both inefficient and hard to implement.
 Instead, we will limit the arity of our sums/product representation to, say,
 16 (it's 3 at the moment) and initially refuse to vectorise programs for which
 this is not sufficient. This allows us to implement everything in the library.
 Later, we can implement the necessary splitting.
] 
[Fix where all the documentation gets installed
Ian Lynagh <[EMAIL PROTECTED]>**20070830223740
 The paths can also now be overridden with the standard configure flags
 --docdir=, --htmldir= etc. We were always advertising these, but now we
 actually obey them.
] 
[Added decidability check for type instances
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070830144901] 
[Warning police
Pepe Iborra <[EMAIL PROTECTED]>**20070829183155] 
[Use a Data.Sequence instead of a list in cvReconstructType
Pepe Iborra <[EMAIL PROTECTED]>**20070829175119
 
 While I was there I removed some trailing white space
] 
[Fix a bug in RtClosureInspect.cvReconstructType.
Pepe Iborra <[EMAIL PROTECTED]>**20070829174842
 Test is print025
] 
[Warning police
Pepe Iborra <[EMAIL PROTECTED]>**20070829165653] 
[UNDO: Extend ModBreaks with the srcspan's of the enclosing expressions
Pepe Iborra <[EMAIL PROTECTED]>**20070829102314
 
 Remnants of :stepover
 
] 
[remove "special Ids" section, replace with a link to GHC.Prim
Simon Marlow <[EMAIL PROTECTED]>**20070830112139
 This documentation was just duplicating what is in GHC.Prim now.
] 
[expand docs for unsafeCoerce#, as a result of investigations for #1616
Simon Marlow <[EMAIL PROTECTED]>**20070830111909] 
[Remove text about ghcprof.  It almost certainly doesn't work.
Simon Marlow <[EMAIL PROTECTED]>**20070829122126] 
[fix compiling GHC 6.7+ with itself - compat needs -package containers now
Simon Marlow <[EMAIL PROTECTED]>**20070829113500] 
[fix typo
Simon Marlow <[EMAIL PROTECTED]>**20070824141039] 
[no -auto-all for CorePrep
Simon Marlow <[EMAIL PROTECTED]>**20070829092414] 
[improvements to findPtr(), a useful hack for space-leak debugging in gdb
Simon Marlow <[EMAIL PROTECTED]>**20070829092400] 
[fix up some old text, remove things that aren't true any more
Simon Marlow <[EMAIL PROTECTED]>**20070828125821] 
[Windows: remove the {Enter,Leave}CricialSection wrappers
Simon Marlow <[EMAIL PROTECTED]>**20070829104811
 The C-- parser was missing the "stdcall" calling convention for
 foreign calls, but once added we can call {Enter,Leave}CricialSection
 directly.
] 
[Wibble
Pepe Iborra <[EMAIL PROTECTED]>**20070829085305] 
[FIX: Remove accidential change to darcs-all in type families patch
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070829010011
 - The type families patch includes a change to darcs-all that breaks it for
   ssh repos at least for Perl 5.8.8 (on MacOS).
 - My Perl-fu is not sufficient to try to fix the modification, which was
   supposed to improve darcs-all on windows, so I just revert to the old
   code.
] 
[Remove INSTALL_INCLUDES; no longer used
Ian Lynagh <[EMAIL PROTECTED]>**20070828205636] 
[Use DESTDIR when installing
Ian Lynagh <[EMAIL PROTECTED]>**20070828205119] 
[Copy LICENSE files into the bindist, as Cabal now installs them
Ian Lynagh <[EMAIL PROTECTED]>**20070828130428] 
[TAG 2007-08-28
Ian Lynagh <[EMAIL PROTECTED]>**20070828215445] 
Patch bundle hash:
a93d0a352e520b32339b12852811323aac1f858a
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to