
New patches:

[Make installPackage install settings from the [package].buildinfo file.
judah.jacobson@gmail.com**20070906010044
 
 M ./libraries/installPackage.hs -1 +14
] {
hunk ./libraries/installPackage.hs 8
+import Distribution.Simple.Utils
hunk ./libraries/installPackage.hs 45
-          lbi <- getPersistBuildConfig
+          lbi <- getConfig verbosity
hunk ./libraries/installPackage.hs 88
+-- Get the build info, merging the setup-config and buildinfo files.
+getConfig :: Verbosity -> IO LocalBuildInfo
+getConfig verbosity = do
+    lbi <- getPersistBuildConfig
+    maybe_infoFile <- defaultHookedPackageDesc
+    case maybe_infoFile of
+        Nothing -> return lbi
+        Just infoFile -> do
+            hbi <- readHookedBuildInfo verbosity infoFile
+            return lbi { localPkgDescr = updatePackageDescription hbi (localPkgDescr lbi)}
+
+
}

Context:

[FIX #1651: use family instances during interactive typechecking
Manuel M T Chakravarty <chak@cse.unsw.edu.au>**20070905130244] 
[Add an OPTIONS -w pragma to utils/genprimopcode/Lexer.xx
Ian Lynagh <igloo@earth.li>**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 <igloo@earth.li>**20070905184614] 
[Don't give warnings in compat
Ian Lynagh <igloo@earth.li>**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 <igloo@earth.li>**20070905161402] 
[Fix bindist creation on Windows
Ian Lynagh <igloo@earth.li>**20070905161354] 
[Fix up bindist creation and publishing
Ian Lynagh <igloo@earth.li>**20070905160641] 
[Refactor, improve, and document the deriving mechanism
simonpj@microsoft.com**20070905170730
 
 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
simonpj@microsoft.com**20070829083349] 
[Refactor MachRegs.trivColorable to do unboxed accumulation
Ben.Lippmeier@anu.edu.au**20070905125219
 
 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 <nr@eecs.harvard.edu>**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 <nr@eecs.harvard.edu>**20070905164646] 
[fix warnings
Simon Marlow <simonmar@microsoft.com>**20070905114205] 
[FIX #1650: ".boot modules interact badly with the ghci debugger"
Simon Marlow <simonmar@microsoft.com>**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 <simonmar@microsoft.com>**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 <simonmar@microsoft.com>**20070904141231] 
[refactoring only
Simon Marlow <simonmar@microsoft.com>**20070904141209] 
[completion for modules in 'import M'
Simon Marlow <simonmar@microsoft.com>**20070904104458] 
[make the GhcThreaded setting lazy, because GhcUnregisterised might not be set yet
Simon Marlow <simonmar@microsoft.com>**20070904101729] 
[{Enter,Leave}CriticalSection imports should be outside #ifdef __PIC__
Simon Marlow <simonmar@microsoft.com>**20070905084941] 
[warning police
Ben.Lippmeier@anu.edu.au**20070905094509] 
[Do conservative coalescing in register allocator
Ben.Lippmeier@anu.edu.au**20070903163404
 
 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 <rl@cse.unsw.edu.au>**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.
] 
[Set datarootdir to the value configure gives us (if any) so datadir works
Ian Lynagh <igloo@earth.li>**20070905013239
 We then set datarootdir to something else later on so that things still
 work when configure doesn't set it.
] 
[bug fix in Decomp step of completion algorithm for given equations
Tom Schrijvers <tom.schrijvers@cs.kuleuven.be>**20070904123945] 
[fix of wanted equational class context
Tom Schrijvers <tom.schrijvers@cs.kuleuven.be>**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.
 
 
] 
[FIX: Correct Leave/EnterCriticalSection imports
Manuel M T Chakravarty <chak@cse.unsw.edu.au>**20070905010217] 
[put the @N suffix on stdcall foreign calls in .cmm code
Simon Marlow <simonmar@microsoft.com>**20070904142853
 This applies to EnterCriticalSection and LeaveCriticalSection in the RTS
] 
[Don't hardwire the build path into the Haddock docs
sven.panne@aedion.de**20070904172855
 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...
] 
[Add a -Warn flag
Ian Lynagh <igloo@earth.li>**20070904141028] 
[Always turn on -Wall -Werror when compiling the compiler, even for stage 1
Ian Lynagh <igloo@earth.li>**20070904140324] 
[Fix CodingStyle#Warnings URLs
Ian Lynagh <igloo@earth.li>**20070904140115] 
[OPTIONS_GHC overrides the command-line, not the other way around
Simon Marlow <simonmar@microsoft.com>**20070904100623] 
[fix cut-and-pasto
Simon Marlow <simonmar@microsoft.com>**20070904100526] 
[FIX #1651: unBox types when deferring unification
Manuel M T Chakravarty <chak@cse.unsw.edu.au>**20070904072542
 - This fixes the first part of #1651; ie, the panic in ghci.
] 
[Better error message for unsolvable equalities
Manuel M T Chakravarty <chak@cse.unsw.edu.au>**20070903074528] 
[Use := rather than = when assigning make variables to avoid cycles
Ian Lynagh <igloo@earth.li>**20070903235117] 
[Don't use autoconf's datarootdir as <2.60 doesn't have it
Ian Lynagh <igloo@earth.li>**20070903234504] 
[Use OPTIONS rather than OPTIONS_GHC for pragmas
Ian Lynagh <igloo@earth.li>**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 <igloo@earth.li>**20070903165847
 Patch from Audrey Tang.
] 
[fix build (sorry, forgot to push with previous patch)
Simon Marlow <simonmar@microsoft.com>**20070903200615] 
[remove debugging code
Simon Marlow <simonmar@microsoft.com>**20070903200003] 
[NCG space leak avoidance refactor
Ben.Lippmeier@anu.edu.au**20070903132254] 
[Do aggressive register coalescing
Ben.Lippmeier@anu.edu.au**20070903115149
 Conservative and iterative coalescing come next.
] 
[Add coalescence edges back to the register graph
Ben.Lippmeier@anu.edu.au**20070828144424] 
[FIX #1623: disable the timer signal when the system is idle (threaded RTS only)
Simon Marlow <simonmar@microsoft.com>**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 <simonmar@microsoft.com>**20070903131625
 Also noticed a few others from RtsAPI were missing, so I added them all
] 
[FIX for #1080
Ross Paterson <ross@soi.city.ac.uk>**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
Ben.Lippmeier@anu.edu.au**20070831090431] 
[GhcThreaded was bogusly off by default due to things being in the wrong order
Simon Marlow <simonmar@microsoft.com>**20070903103829] 
[bump MAX_THUNK_SELECTOR_DEPTH from 8 to 16
Simon Marlow <simonmar@microsoft.com>**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 <simonmar@microsoft.com>**20070831092224
 I had planned to do findEnclosingDecl a different way, so add a ToDo
 as a reminder.
] 
[Suppress some warnings on Windows
Ian Lynagh <igloo@earth.li>**20070902222048] 
[Fix warnings in ghc-pkg on Windows
Ian Lynagh <igloo@earth.li>**20070902221442] 
[Fix and supress some warnings, and turn on -Werror when validating
Ian Lynagh <igloo@earth.li>**20070902193918] 
[Explicitly set "docdir" when calling make, configure's --docdir seems to be ignored
sven.panne@aedion.de**20070902164342] 
[Use DESTDIR for installation
sven.panne@aedion.de**20070901175124] 
[Fixed TeX syntax
sven.panne@aedion.de**20070901124615] 
[Set -Wall -fno-warn-name-shadowing in compiler/ when stage /= 2
Ian Lynagh <igloo@earth.li>**20070901113018] 
[Add {-# OPTIONS_GHC -w #-} and some blurb to all compiler modules
Ian Lynagh <igloo@earth.li>**20070901112130] 
[Add a --print-docdir flag
Ian Lynagh <igloo@earth.li>**20070831231538] 
[Follow Cabal module movements in installPackage
Ian Lynagh <igloo@earth.li>**20070831181359] 
[Follow Cabal's move Distribution.Program -> Distribution.Simple.Program
Ian Lynagh <igloo@earth.li>**20070831175217] 
[Don't use the --docdir etc that autoconf provides
Ian Lynagh <igloo@earth.li>**20070831173903
 Older autoconfs (<2.60?) don't understand them.
] 
[Fix installing the libraries when there is no DESTDIR
Ian Lynagh <igloo@earth.li>**20070831015442] 
[Make the doc index page obey DESTDIR
Ian Lynagh <igloo@earth.li>**20070831014537] 
[Make rts docs obey DESTDIR
Ian Lynagh <igloo@earth.li>**20070831014346] 
[Make the manpage obey DESTDIR
Ian Lynagh <igloo@earth.li>**20070831014253] 
[Obey DESTDIR when installing library docs
Ian Lynagh <igloo@earth.li>**20070831012351] 
[typo in DLL code
Simon Marlow <simonmar@microsoft.com>**20070830143105] 
[Windows: give a better error message when running out of memory
Simon Marlow <simonmar@microsoft.com>**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 <rl@cse.unsw.edu.au>**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 <rl@cse.unsw.edu.au>**20070831041822] 
[Number data constructors from 0 when vectorising
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070831032528] 
[Rename functions
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070831032125] 
[Refactoring
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070831015312] 
[Refactoring
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070831012638] 
[Fix vectorisation of nullary data constructors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070831005912] 
[Do not unnecessarily wrap array components
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830062958] 
[Remove dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830055444] 
[Fix vectorisation of unary data constructors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830040252] 
[Fix vectorisation of sum type constructors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830035225] 
[Track changes to package ndp (use PArray_Int# instead of UArr Int)
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830032104] 
[Find the correct array type for primitive tycons
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830025224] 
[Add code for looking up PA methods of primitive TyCons
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070830014257] 
[Delete dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070829145630] 
[Rewrite vectorisation of product DataCon workers
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070829145446] 
[Rewrite generation of PA dictionaries
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070829064258] 
[Complete PA dictionary generation for product types
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824230152] 
[Simplify generation of PR dictionaries for products
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824071925] 
[Remove unused vectorisation built-in
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824051524] 
[Adapt PArray instance generation to new scheme
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824051242] 
[Add UArr built-in
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824051213] 
[Modify generation of PR dictionaries for new scheme
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824043144] 
[Refactoring
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824040901] 
[Remove dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824035751] 
[Fix buildFromPRepr
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824035700] 
[Move code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824032930] 
[Move code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824032743] 
[Delete dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824031504] 
[Change buildToPRepr to work with the new representation scheme
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824031407] 
[Remove Embed and related stuff from vectorisation
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824023030] 
[Encode generic representation of vectorised TyCons by a data type
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070824012140] 
[Remove dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070823135810] 
[Conversions to/from generic array representation (not finished yet)
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20070823135649] 
[Use n-ary sums and products for NDP's generic representation
Roman Leshchinskiy <rl@cse.unsw.edu.au>**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.
] 
[Don't try to copy haddock index files if we haven't built the docs.
judah.jacobson@gmail.com**20070831050321
 
 M ./libraries/Makefile +2
] 
[Use cp -R instead of cp -a (it's more portable).
judah.jacobson@gmail.com**20070831050215
 
 M ./libraries/Makefile -3 +3
] 
[Fix where all the documentation gets installed
Ian Lynagh <igloo@earth.li>**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 <chak@cse.unsw.edu.au>**20070830144901] 
[Warning police
Pepe Iborra <mnislaih@gmail.com>**20070829183155] 
[Use a Data.Sequence instead of a list in cvReconstructType
Pepe Iborra <mnislaih@gmail.com>**20070829175119
 
 While I was there I removed some trailing white space
] 
[Fix a bug in RtClosureInspect.cvReconstructType.
Pepe Iborra <mnislaih@gmail.com>**20070829174842
 Test is print025
] 
[Warning police
Pepe Iborra <mnislaih@gmail.com>**20070829165653] 
[UNDO: Extend ModBreaks with the srcspan's of the enclosing expressions
Pepe Iborra <mnislaih@gmail.com>**20070829102314
 
 Remnants of :stepover
 
] 
[remove "special Ids" section, replace with a link to GHC.Prim
Simon Marlow <simonmar@microsoft.com>**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 <simonmar@microsoft.com>**20070830111909] 
[Remove text about ghcprof.  It almost certainly doesn't work.
Simon Marlow <simonmar@microsoft.com>**20070829122126] 
[fix compiling GHC 6.7+ with itself - compat needs -package containers now
Simon Marlow <simonmar@microsoft.com>**20070829113500] 
[fix typo
Simon Marlow <simonmar@microsoft.com>**20070824141039] 
[no -auto-all for CorePrep
Simon Marlow <simonmar@microsoft.com>**20070829092414] 
[improvements to findPtr(), a useful hack for space-leak debugging in gdb
Simon Marlow <simonmar@microsoft.com>**20070829092400] 
[fix up some old text, remove things that aren't true any more
Simon Marlow <simonmar@microsoft.com>**20070828125821] 
[Windows: remove the {Enter,Leave}CricialSection wrappers
Simon Marlow <simonmar@microsoft.com>**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 <mnislaih@gmail.com>**20070829085305] 
[FIX: Remove accidential change to darcs-all in type families patch
Manuel M T Chakravarty <chak@cse.unsw.edu.au>**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 <igloo@earth.li>**20070828205636] 
[Use DESTDIR when installing
Ian Lynagh <igloo@earth.li>**20070828205119] 
[Copy LICENSE files into the bindist, as Cabal now installs them
Ian Lynagh <igloo@earth.li>**20070828130428] 
[TAG 2007-08-28
Ian Lynagh <igloo@earth.li>**20070828215445] 
Patch bundle hash:
4440fa9952e42278de4aaf4f7a1da561c838bb64
