[commit: ghc] ghc-lwc2's head updated: Renamed Thread-local storage to SCont-local storage (0839ba5)

Ian Lynagh igloo at earth.li
Thu Feb 28 15:20:54 CET 2013


Repository : http://darcs.haskell.org/ghc.git/

Branch 'ghc-lwc2' now includes:

     dea4ee1 Fix build on Windows: Configure packages in the right order
     1d15ada Fix whitespace only in cmm/SMRep.lhs
     f95ced2 Tweak the HC_OPTS generation
     c9733e2 Add flag to disable rule shadowing warning.
     6a43840 Refactor PrelRules and add more rules (#7014)
     4b18cc5 We no longer need to build utf8-string
     cb054f5 Refactor prel rules: always return a single rule.
     229e9fc Make -fscc-profiling a dynamic flag
     fecb6af Remove some old temporary warning suppression for hoopl warnings
     bd0649f Add a comment about the units of platformWordSize
     cd22c00 Remove unnecessary Platform arguments in nativeGen/PPC/Ppr.hs
     55881ff Remove pprNatCmmDecl's Platform argument
     5d2a1e6 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     c859d17 Merge taskId and serialisableTaskId
     c833546 Merge commit 'c859d17f9b0ae8559dac4f7e5cb8521e7ab5f0fb'
     4f811e1 Migrate more rules to PrelRules.
     949081a Merge PrelRules refactoring (#7014)
     74fb5c4 Fix typo in warning message
     2c82539 Re-enable inline-rule-shadowing warning.
     24387e6 Fix warning on x86-64
     873f7b2 Fix dfun unfolding of PA instances generated by the vectoriser
     1d094f9 Remove nativeGen/PprInstruction.hs
     c7a7c49 typo
     ab14d99 GHCConstants.h should not contain preprocessor definitions
     93c03f8 typos
     cc3d982 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     6c2c07c bugfix: cope when a source reg is dead at a join point
     f68b427 Fixes for the stack layout algorithm to handle join points
     fe3753e Merge sinking and inlining to get better results.
     f1ed6a1 New codegen: do not split proc-points when using the NCG
     1cea9a5 optimise away some unnecessary stack checks
     a4b249c Small optimisation to the code generated for CAFs
     e26161f no need to removeUnreachableBlocks
     9388337 bug fixes for the sinker
     a2e0fbe bug fix for control-flow optimisation
     a0020c1 fix merge bugs
     8b31090 fix warnings
     a25c974 fix haddock parse error
     6f346d4 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     9e7acbe Fix compile on linux-powerpc64. (#7084).
     598ee1a Fix #7087 (integer overflow in getDelayTarget())
     d236142 Improve code generated when real registers are clobbered
     6ede006 Explicitly share some return continuations
     7930221 Don't shortcut call-returns when not splitting proc points
     dae976c add a sinking pass before stack layout (currently disabled)
     08c16ba Code reformatting
     a915d9b Inline into the last node
     40b6598 Improve accuracy of memory conflict tracking
     325f2f3 Disable the mini-inliner when using the new codegen
     9568636 No need to do removeDeadAssignments, just do cmmLiveness instead
     3ae875c Eliminate "r = r" assignments.
     4aaa3c1 fix a bug in the inliner
     46adcee comment wibble
     15e4f93 applying simonpj's fix from #7022 (with 80-col reformatting)
     4200c4a FloutOut.wrapTick: don't forget to tick the args of a constructor app
     b11a5ef comments and refactoring
     7974afb Fix references to repositories in the user guide
     89900ff Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     0e7aad2 De-orphan the Outputable Char instance
     14b05c0 Whitespace only in hsSyn/HsSyn.lhs
     5ae0cea Whitespace only in utils/Outputable.lhs
     be691e1 Remove another unnecessary Platform argument
     e9a587a De-orphan the Outputable Fingerprint instance
     541cc50 Remove an unsafe use of head (#7118)
     ecc43c1 Convert prefix uses of (<>) to infix <>
     2d2650b Move linker flags into the settings file; fixes #4862
     c17f301 Remove LD_X; it's no longer used
     ddf9d40 Build fix
     34b2906 Whitespace only in compiler/simplCore/Simplify.lhs
     52307c1 Rename trace_dump to dump
     13f3a31 Remove pprDefiniteTrace
     c9820b2 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     1235c27 Improve some code layout in SysTools
     668151c More more ld-related settings into the settings file
     c7c2d6c Whitespace only in UniqFM
     4cdfe67 Define LdCmd in the bindist configure.ac
     5620662 finish a comment
     290ec75 Add a comment to explain why the FCode monad is lazy
     6228e31 Use "ReturnedTo" when generating safe foreign calls
     22d5822 Foreign calls may clobber caller-saves registers
     f67a8b8 Continue by jumping to the top-of-stack after a safe foreign call
     82fa790 Fix two bugs in the sinker.
     cf3fb95 MO_F_Mul and MO_F_Add are commutative
     7db26e0 comment
     190c555 fix warning
     6997bb5 Don't define STOLEN_X86_REGS in Cmm.h
     8e7fb28 Start separating out the RTS and Haskell imports of MachRegs.h
     e6ef5ab Make tablesNextToCode "dynamic"
     f917eeb Add "Unregisterised" as a field in the settings file
     46b5c19 Define callerSaves for all platforms
     8d3e9fd small cleanup
     0b75e45 Generate one fewer temps per heap allocation
     b534f42 Make lint check for undefined variables in Cmm
     149e04b A closure with void args only should be a function, not a thunk
     ddd6af0 Cleanup and fixes to profiling
     5c3f13f Fix update frames for profiling
     3cf6050 fix maybeSaveCostCentre: cases were reversed
     bccd9e8 Add missing cases in hand-coded instance Eq GlobalReg
     1469a12 Node calling convs should use R1 even if it isn't a register
     df7a20c Eliminate "r = r" in mkAssign
     313740e fix a warning
     ef58afe Small optimisation
     babe3c6 entryHeapCheck: fix calls to stg_gc_fun and stg_gc_enter_1
     69cda9e maybeInvertComparison: remove floating-point comparisons
     396f090 Fix a bug in the handling of recent_activity
     62ab993 fix warning
     1edad87 Add missing flag for respecting EXTRA_LIBDIR
     c2a532a Set the value of Unregisterised in the bindist configure.ac
     415598b Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     50f5016 Add cast to placate gcc 4.6 on linux-powerpc (#7113).
     3a5788c a couple of small optimisations
     74d5dde Only run the second round of control-flow optimisations when -O is on
     09afcc9 Remove uses of fixC from the codeGen, and make the FCode monad strict
     d801c96 Fix build failure on OS X (#7119)
     cb07cb7 Always define startProfTimer and stopProfTimer
     c4d75a7 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     7299487 Follow RTS symbol changes in Linker.c
     4e6bd65 Use the right arch name in the Windows installer filename
     a0e308d Don't pass -Wimplicit to the C++ compiler.
     7473c3d Update 'unboxed tuples' section of users guide.
     f78b31a Fix ambiguous flag resolution (#7138)
     8240843 Respect verbosity for "flags changed" message (#7139)
     82373c7 Give suggestions for unrecognised command line arguments
     700d287 Fix environment update for type instance declarations in GHCi (#7117)
     3e6c930 Fix GHCi segfault during startup on linux-powerpc (#2972).
     e6fa845 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     e949162 Fix Trac #7128, by zonking kind varaibles more assiduously when typechecking a class declaration
     111ff8c Comments
     b10eb00 Better debug printing
     3fabf48 Document -fdefer-type-errors
     ca9986a Improve documentation of the way that defaulting to IO happens in GHCi
     55cdcc9 Make .t files when running haddock
     1993ee4 TH: Pragmas refactoring.
     af9dd9d Comments about shadowing
     10377bb Fix Trac #7145, by recording uses of constructor "children" in export lists
     c848891 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     bdce8f0 Put kind variables before type variables when quantifying
     72e7f57 Require DataKinds for promoted list/tuple syntax in types
     f7b096e Test FlexibleInstance not UndecidableInstances in the ambiguity check
     de07bf2 Use TcMType.growThetaTyVars (which works) rather than TcSimplify.growPreds (which doesn't)
     41c7342 Allow a vew pattern or bang pattern in a record pattern.
     4c93c8b Tabs -> spaces (and some other formatting)
     2a7217e Formatting wibbles
     00a2104 Improve documentation for rank-1 types (Trac #7137)
     3eb6e21 When pattern matching against a constructor with equalities, require either -XGADTs *or* -XTypeFamilies (rather than only the former)
     4e0a957 Profiling: open .prof when -hr<cc> is specified
     a874dd8 Export startProfTimer and stopProfTimer symbols.
     d421b16 Avoid the quadratic append trap in flattenCmmAGraph
     0ca7574 remove tabs
     9825f86 remove tabs
     2fe4dbc remove tabs
     cec899d Retain ordering of finalizers during GC (#7160)
     106f043 add X86_64_GOTTPOFF relocation for errno
     bb120df move startProfTimer() and stopProfTimer() to the public headers
     bbb5843 Fix a discrepancy between two calculations of which generation to collect
     0a7c5b8 improve debug output
     a68df77 Reduce fragmentation when using +RTS -H (with or without a size)
     4752385 Improve compile times by enabling +RTS -H for GHC (only when bootstrapped)
     397606d tidy up
     d4ac7d8 Fix inverted test for platformUnregisterised (should fix the optllvm breakage)
     2f7c578 Reduce the likelihood of x64/x86-64 changes breaking the build on other arches (#7083).
     2c6d11f Re-jig the reporting of names bound multiple times
     1a591a0 Refactor the way we infer types for functions in a mutually recursive group
     68a1393 Annotate code in {-# LINE #-} pragmas as well
     2c60015 fix warning
     e590ad7 OS X: use mmap() instead of malloc for allocating the bss (#7040)
     6d3fb1b Fix the generation of CallerSaves; fixes #7163
     07295e9 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     7570064 Move activeStgRegs into CodeGen.Platform
     15856e9 Add haveRegBase to CodeGen.Platform
     80a72da CgUtils no longer needs to #include HaskellMachRegs.h
     cacae06 Whitespace only in StgCmmUtils
     dbc0560 Use haveRegBase in StgCmmUtils too
     d182285 StgCmmUtils no longer needs to include HaskellMachRegs.h
     ac21fdb Pass platform down to lastxmm
     b6b6311 Pass platform down to lastint
     eb9b4e5 Remove unused 'targetWordSize'
     7252309 Whitespace only in nativeGen/RegAlloc/Linear/X86/FreeRegs.hs
     98c29f9 Whitespace only in compiler/nativeGen/PPC/Regs.hs
     a3d77e8 Make the PPC globalRegMaybe more similar to the other platforms'
     23efe66 Remove some CPP in nativeGen/X86/Regs.hs
     f1f1659 More CPP removal in nativeGen/X86/Regs.hs
     f26027e More CPP removal in nativeGen/X86/Regs.hs
     a0788a8 Fix missing case in coVarsOfTcCo
     61cc04d A bit more debug output
     6f96bc4 Tab elimination
     948be9c Add mapTM to TrieMap
     2b5b178 Improve Safe Haskell warn/error output.
     93e8ae2 Fix :issafe command (#7172).
     e8e9d09 Minor refactoring
     9a3c8bd Emit a warning for -rtsopts -shared, as well as -rtsopts -no-hs-main
     d6918e9 Don't assume that coercion variables have (~) types
     b4b7863 Fix for optimizer bug on linux-powerpc (#6156).
     da9a330 Merge ../HEAD
     0440d8a Follow changes in Cabal
     ad33998 Fix to-iface conversion of RULES involving coercions in argument pattterns
     b04ff2f Two small fixes to SpecConstr for functions with equality-proof args
     2f08f70 Don't specialise on implicit-parameter arguments in Specalise
     336a769 Merge branch 'master' of http://darcs.haskell.org/ghc
     cc1cc09 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     75f2e87 Fix build with FreeBSD versions earlier than 9.0
     8413d83 Make a function for get_itbl, rather than using a CPP macro
     6252300 Convert a couple more macros to inline functions
     9959dee More CPP macro -> inline function
     773570e More CPP macros -> inline functions
     0ab537c More CPP macros -> inline functions
     3d7c81a Make badImportItem into a warning (#7167)
     4eb02c1 Update documentation for -fwarn-dodgy-imports.
     d82cecb Fix return type of FUN_INFO_PTR_TO_STRUCT.
     1d36d88 Fix callerSaves, activeStgRegs, haveRegBase when unregisterised
     c0849d8 Fix -fPIC with the new code generator
     0e7d290 generalise the type of eqStableName#
     b2e8bed Fix Trac #7092, involving Template Hsakell and name shadowing
     ab2fe55 Comments in CoreSyn only
     7dfbed2 Fix pretty-printing for GADTs in infix form
     1bbdbe5 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     7babb1b Big changes on tc-untouchables branch
     5b4fef6 When floating constraints outwards, promote the floated type variables
     c0907ed Move more code into codeGen/CodeGen/Platform.hs
     dae766b Remove some old commented-out code
     152f1eb Remove some CPP from nativeGen/PPC/Regs.h
     6a43ff8 Remove some CPP from llvmGen/LlvmCodeGen/Ppr.hs
     a94b80b Remove Util.{isDarwinTarget,isWindowsTarget}
     350b5c4 Remove some CPP from compiler/ghci/Linker.lhs
     ed8d7a1 Remove some CPP from nativeGen/X86/Instr.hs
     737e444 Whitespace only in cmm/CmmParse.y
     915c372 Remove CPP from cmm/CmmParse.y
     baa7c0f Add DynFlags to the CorePrepEnv
     4144896 Remove CPP from coreSyn/CoreUtils.lhs
     72e46ba Merge branch 'master' of http://darcs.haskell.org/ghc
     f27c631 Fix Trac #7196 by adding a case to the desugarer
     0d55e1e Avoid emitting Given constraints for spontaneous unifications. Instead keep spontaneous unifications /only/ in the TcS tybinds. Relevant note is Note [Spontaneously solved in TyBinds] in TcInteract.
     ee578b6 Merge branch 'tc-untouchables' of http://darcs.haskell.org/ghc into tc-untouchables
     d0ddde5 Fail earlier if there's an error in a type declaration
     bcef1e2 v7.4.1 is required for building, so we can drop the v7.2.1 workaround
     34be452 Minor fixes, mostly simplificaitons
     f5216cd Merge remote-tracking branch 'origin/HEAD' into tc-untouchables
     b660cc0 make sure to remove the right link before calling 'ln -s' (could we use 'ln -sf'?)
     2b69233 A raft more changes,  * simplifying and tidying up canonicalisation,  * removing the flat cache altogether  * making the FunEq worklist into a deque
     b737a45 More simplifications to the constraint solver
     8aabe8d Fix fencepost and byte/word bugs in cloneArray/copyArray (#7185)
     de3a8f7 Cleanup: add mkIntExpr and zeroExpr utils
     832077c enable -fnew-codegen by default
     4f656e8 disable -fregs-graph (#7192)
     6dd55e8 Fix a bug in foldExpDeep
     d9c0276 small improvements to findPtr() and the closure printer
     7eff304 debug printing of the CAFEnv
     08042a5 fix the name of an SCC
     fad7453 Narrow the arg of popCnt# to the correct width
     111edd8 Add -fcmm-sink to avoid the register allocator failing on x86
     db5c6ad Load the PIC base register on every entry point
     4026038 Nicer pretty printing for tuple kinds
     fe6ddf0 A bunch more simplification and refactoring to the constraint solver
     740cbdf Merge branch 'tc-untouchables', remote branch 'origin' into tc-untouchables
     ff32f97 Wibbles to fe6ddf00, fixing infelicities
     6def8bc Disable the MR by default in GHCi (#3202)
     494eb3d Refactor the ways code a bit
     46258b4 Make the ways dynamic
     4f15146 Define initial buildTag and rtsBuildTag
     da33622 Remove doingTickyProfiling
     92f0991 Remove the way-related CPP frmo DynFlags
     3b56334 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     d37deb7 Some comments and false starts to do with ArrForm
     82ace67 Comments only
     d4fa711 Remove historical Unique parameter from pushUntouchables
     ed7538b Move inert_insols into the InertCans record
     64d07ab Make kickOutRewritable kick out insolubles
     b493d39 When defaulting, check for *meta* tyvars
     7560dd6 Some refactoring; removes simplifyCheck
     61d41b9 Move ldInputs into DynFlags
     3d3fef8 Remove the unused opt_StubDeadValues
     892d862 Make -fhistory-size dynamic
     056b27b Remove -dstub-dead-values from flag list
     af4f987 Remove unused -dopt-fuel
     7b11baa Make -fhpc a dynamic flag
     e641139 Narrow the args of the popCnt# primitives (new codegen)
     bd5354e Fix -split-objs with the new code generator
     7d847e8 Add "remote set-branches" support to sync-all
     ccf44d8 A further fix for -split-objs with the new codegen
     c655913 remove $(GhcStage1DefaultNewCodegen) etc.
     583c87d Fix #7215: we weren't calculating the hashes correctly for sub-binders
     633dd55 Moved solving of type families to zonkWC and a few simplifications in TcSimplify. Now unflattening does not happen recursively inside solveWanteds which should be a good performance win.
     62da65a Fail nicely when encountering an invalid bang annotation (#7210)
     d8b48ba Typo fix in deferred type errors docs.
     8224ee1 Fix the PPC and SPARC NCGs to handle multiple info tables in a proc
     d68865d memInventory(): tweak pretty-printing
     4d208ae When using -H with -M<size>, don't exceed the maximum heap size
     abb875d some nats should be lnats
     a817962 Some further tweaks to reduce fragmentation when allocating the nursery
     41737f1 Deprecate lnat, and use StgWord instead
     06b4e78 Handle II16 size value in PowerPC code generator.
     0550bcb comment updates
     bf2d58c Lots of nat -> StgWord changes
     c32bb5d Remember to zonk the skolems of an implication
     c3b6b3f Update dependency on directory.
     0ee44de Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     c855396 Remove some CPP
     77b63e7 Two fixes to kind unification
     da5b7ba Remove some more CPP
     26ebd1b Pass Platform down to halfWordWidth
     94dbd65 Pass Platform down to halfWordMask
     00e4140 Whitespace only in cmm/CmmExpr.hs
     ad779f5 Whitespace only in cmm/CmmUtils.hs
     6986eb9 Whitespace only in codeGen/CgProf.hs
     f611396 Pass DynFlags down to bWord
     44b5f47 Pass DynFlags down to gcWord
     2b7319a Pass DynFlags down to wordWidth
     86054b4 Use conditionals rather than CPP in mkDerivedConstants
     f89b73e Add more modes to mkDerivedConstants
     72d3f4b Make the Windows-specific part of mkDerivedConstants.c conditional
     6154cfa We need to install the platformConstants file
     07c3777 Add a couple more mkDerivedConstants modes
     4279ab5 Use sIZEOF_* from platformConstants rather than Constants
     568fdb1 Use oFFSET_* from platformConstants rather than Constants
     a7a91cd Remove the --gen-haskell mode of mkDerivedConstants
     6e1107b Remove some unused HaskellConstants entries
     3f39164 Use intptr_t for offset values in mkDerivedConstants
     f4c327a When allocating a new kind variable, do so with newMetaUnique
     f4d0e62 Fix build on OS X
     9b0c4ed Start moving other constants from (Haskell)Constants to platformConstants
     291da8a Check for Int constants that are too large in mkDerivedConstants
     c38794d More OS X build fixes
     041e832 Move some more constants fo platformConstants
     6f3be2b Merge branch 'master' of mac:ghc/git/val32/.
     f203e63 Move more constants into platformConstants
     b7dd4b5 MAX_REAL_LONG_REG is always defined, so no need to test it
     a22a9c2 Move more constants to platformConstants
     2115585 Whitespace only in nativeGen/RegAlloc/Linear/State.hs
     2e3c925 Put DynFlags into the RegM monad
     69e5f31 Remove a load of Platform arguments from RegM functions
     71f4b80 Remove more Platform arguments
     0692f7e Whitespace only in nativeGen/RegAlloc/Linear/JoinToTargets.hs
     43e09ac Remove more Platform arguments
     6dd23e6 Move some more constants into platformConstants
     c3f4c6f Move wORD_SIZE_IN_BITS to DynFlags
     7d83fde Bind "given" evidence to a variable, always
     cf02909 Merge remote branch 'origin/master'
     84bb854 Fix Trac #7237; mixup with empty tuples
     f33327a Comments and laout only
     5bae803 Fix UNPACK with -fomit-interface-pragmas.
     7b8a17a Print literal integers in External Core.
     7f5af24 Windows build fix
     a62b56e Pass DynFlags down to llvmWord
     1791089 Move wORD_SIZE into platformConstants
     7ecefb6 Move more constants to platformConstants
     b0f4c44 Move tAG_BITS into platformConstants
     8c3b9ac Merge branch 'master' of http://darcs.haskell.org/ghc
     79ee264 Pass DynFlags to the ru_try functions of built-in rules
     ad0139a Merge branch 'master' of http://darcs.haskell.org/ghc
     b0db930 Merge remote-tracking branch 'origin/master' into tc-untouchables
     8a9a7a8 Add type "holes", enabled by -XTypeHoles, Trac #5910
     5f312c8 Spelling in comments only
     8089391 Comments about how the untouchables stuff works
     0683258 Improve the binding location of class methods (I think)
     d30b9cf Another refactoring of constraints
     1a6ab64 Remove cc_ty from CIrredCan and cc_hole_ty from CHoleCan
     bd6b183 Tidy up and simplify TcMType.zonkFlats (discussion between DV and SLPJ)
     510f439 Tidy up and simplify simplifyRule, pls adding some other comments
     af7cc99 Implement 'left' and 'right' coercions
     0678289 typo
     10cc422 Move tARGET_* out of HaskellConstants
     f21dabc Remove the Target* types from HaskellConstants
     ba8fd08 Make the call to chooseBoxingStrategy lazy again
     998a633 Remove unused import
     e76fa69 Merge the remainder of HaskellConstants into Constants
     9224e48 Remove some CPP
     9615222 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     027a654 Small parallel GC improvement
     3f2eeee Declare SRT labels correctly in the via-C backend
     16cc37f make some debug output conditional on -ddump-cmmz
     98903b9 Give packHalfWordsCLit a more specific type
     58470fb Make a start towards eta-rules and injective families
     1b5c833 Undo making Any into a type family, for now
     19dd108 Be careful about kinds when eta-expanding AppCo
     09a0670 Signatures and comments
     9429190 Make sure that even insoluble constraints are fully substituted
     8e7d415 Merge remote-tracking branch 'origin/master' into tc-untouchables
     b44db6f Remove some uses of the WORDS_BIGENDIAN CPP symbol
     8244ec3 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     3a4c64c Make StgHalfWord a portable type
     a9b986e Make StgWord a portable type too
     0176c3f Remove a little more CPP
     62bb618 Add some LDV_* constants to platformConstants
     f1e3729 Remove redundant #includes
     20670cc Make the StgWord/StgHalfWord types more similar
     6a4d60a Add the necessary REP_* constants to platformConstants
     fe58212 Make some uses of minBound/maxBound use the target Int/Word sizes
     54affce Fix litFitsInChar
     aa6bc70 Remove a couple of unneccesary Platform arguments
     05a0a64 Change some "else return ()"s to use when/unless
     448ad24 We don't actually need a Show instance for the PlatformConstants type
     08167ac Merge remote-tracking branch 'origin/master' into tc-untouchables
     a6c06bd Whitespace only in nativeGen/RegAlloc/Graph/Stats.hs
     616524d Fix warnings in RegAlloc.Graph.Stats
     33a6df9 Make addSRM to strict additions
     85a8f79 Remove redundant pragmas from RegAlloc.Liveness
     987710c non-tablesNextToCode fix for returns in the new codegen
     7bff9fa refactor flattenCmmAGraph
     0b0a41f Teach the linear register allocator how to allocate more stack if necessary
     096396d fix warning
     c90d45f fix warnings
     2e8f08c splitAtProcPoints: jump to the right place when tablesNextToCode == False
     a910970 add a missing entryCode
     23db38b Comments only
     b00c29d Fix an outright bug in my "left/right" stuff, and refactor canEqLeafTyVarEq along the same lines as our earlier refactoring of canEqLeafFunEq
     b92c76e Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     9e05651 Don't put unused constants in platformConstants
     a7147df Add missing dataCast1 method to the Data Bag instance
     a17da16 FIX #7255: print tyConTyVars tc, not tc_args
     1f5d836 Allow allocNursery() to allocate single blocks (#7257)
     016fd74 Cache the result of countOccupied(gen->large_objects) as gen->n_large_words (#7257)
     c19f2e3 Include pinned memory in the stats for allocated memory
     5f01b6d Fix off-by-one (#7227)
     3f2bd36 Fiddling with kind errors
     ef3339c Convert more RTS macros to functions
     c88fe39 Convert more RTS macros to functions
     ed6a7e4 Fix the profiling build
     118a09e Remove a redundant cast
     6cf0e21 Whitespace only in rename/RnSource.lhs
     4bda967 Don't warn about defining deprecated class methods
     ca64cee Use finiteBitSize rather than bitSize when it is available
     096c29d Ignore deprecation warnings for bitSize in libs when validating
     673b6f5 Revert "Disable the timer signal while blocked in select() (#5991)"
     0b79d5c Another overhaul of the recent_activity / idle GC handling (#5991)
     acdebbb no functional changes
     b482966 Generate better code for "if (3 <= x) then ..."
     3596d5d whitespace only
     254f1a6 whitespace and panic message fixup
     5cf7182 Misc tidyup
     93faddc fix panic message typo
     3473e21 When -split-objs is on, make one SRT per split, not one per module
     16206a6 Remove some old-codegen cruft
     9c15249 fix stage2 compilation
     2145ffc Build old-time with stage2
     d3128bf Partially fix #367 by adding HpLim checks to entry with -fno-omit-yields.
     aa2d5b5 Remove an unused bit from the Lexer bitmap
     7724ecb Remove a stray " in the build system
     6e6da3a Tweak the build system handling of shell wrappers
     155e9e1 Document that we don't warn about defining deprecated class methods
     42cb30b Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     4e339e0 Improve pretty printing for coercions
     f18c188 Wibble to debug print
     39f0bd0 Comments only
     e7279ac Fix kind unification in the special rule for ($)
     444577a Comments only
     6a9542a Better ASSERT message
     9a058b1 Refactor the handling of kind errors
     6e3e64a Merge remote-tracking branch 'origin/master' into tc-untouchables
     7fdc2a3 Add missing case in TcUnify.matchExpectedFunKind
     f6983ef Change how we handle options required by 'way's
     c35c5d0 Improve pretty printing for coercions (exp transistivity chains)
     bd2aef6 Comment out a particularly verbose trace
     2b523dc Use System Names for evidence variables
     adb6bcb Fix an ASSERT
     7fdcf2c Simplify the reOrient function (no change in behaviour)
     453e0ce Modest refactoring in TcCanonical (and TcSMonad)
     b3f2f73 Modest refactoring (put bumpStepCounter into traceFireTcS, and other simple things)
     935fa10 Comments about silent superclasses
     316d3ed Tracing in TcUnify
     fd3bd41 Merge branch 'tc-untouchables' of http://darcs.haskell.org/ghc into tc-untouchables
     29ee75a Remove some old, commented out bits
     cddbf86 Allow -static to be used after -dynamic
     29f6b87 Do flag consistency checks at the end of flag parsing
     d106284 Put libexec binaries in lib/bin/ rather than just lib/
     483c763 Refactor the shell-wrapper-creation logic
     522a155 Comments, and unused import
     902a863 Improve (and simplify) the short-circuiting of Refl coercions
     fc8f9c1 Fix typo in the documentation of CApiFFI
     2d96202 -fhpc is no longer a static flag (fixes hpc tests)
     815dcff A few more constraint solver improvements
     74d6511 Merge remote-tracking branch 'origin/master'
     4708d38 Merge branch 'tc-untouchables'
     2c207b6 Compare the kinds of type variables when comparing types
     a501c95 Make sure that we check for type errors strictly in a Template Haskell splice, even if -fdefer-type-errors is on
     419af69 Give PrimOps a NOINLINE pragma, to suppress silly warnings from dsRule
     58eaacc Add a flag to tell ghc to use $ORIGIN when linking program dynamically
     0b06d68 Improve constraint solver depth error slightly
     baab120 Fix type error in 2c207b6f (Compare the kinds of type variables)
     3b980d0 Typo
     ba56d20 This big patch re-factors the way in which arrow-syntax is handled
     65e6470 Merge branch 'master' of http://darcs.haskell.org/ghc
     898cb09 Build the dynamic way by default on Linux/amd64
     7c0b518 The non-dynamic ways now need to explicitly use -static
     1b3f274 Add a couple more RTS ways
     a6b0ab2 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     30b0871 Add a "Dynamic by default" field to the ghc --info output
     d1c8731 Fix the recompilation check for dynamic libraries
     6aed04f Fix Windows build
     911bc5c Windows install fix
     16a8414 Actually build things the dynamic way
     56a8c8a Comments only
     eb6c3ee Improve pretty-printing for holes
     00cb878 Improve debug tracing slighty
     b442ad9 Do not create extra evidence given/derived variables in the Refl case of rewriteCtFlavor
     629d1f4 Improve erorr location for Given errors
     b9fccbc Do not do type-class defaulting if there are insoluble constraints
     ed5ebee Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     b49ad6b Load the right object files in ghci
     6784ddd Make adjust_ul handle BCOs
     4a138b7 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     aed37ac Add a ToDo comment
     a7c0387 Produce new-style Cmm from the Cmm parser
     620d885 expand tabs
     6e95114 fix a warning
     e1846d7 Fix a dependency bug in the build system
     a94144b untab
     f7cd14f Put the DynFlags in a global variable for tracing; fixes #7304
     1406483 Fix copyArray# bug in old code generator
     5cff4fb Fix copyArray# bug in new code generator
     2a53408 Merge ../ghc
     c3939fd Make the -ferror-spans flag dynamic
     9c6223d Remove unnecessary warning suppression
     70765e8 Fix comment
     cc2a4d5 profiling fixes
     0a768bc Make the opt_UF_* static flags dynamic
     879aae1 -fliberate-case-threshold is already a dynamic flag
     ef786b6 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     f89ce06 Make the -dsuppress-* flags dynamic
     1255ff1 Make -fmax-worker-args a dynamic flag
     30e7b73 Make -fsimple-list-literals a dynamic flag
     577f50f Whitespace only in simplCore/SimplEnv.lhs
     d131d66 Whitespace only in simplCore/SimplUtils.lhs
     a327c14 Whitespace only in simplCore/SimplMonad.lhs
     e731cb1 Make -f(no-)pre-inlining a dynamic flag
     70c6416 Make -fexcess-precision a fully-dynamic flag
     80fcdd6 Put the generated Parser.y under compiler/stage<n>/build; fixes #7195
     5041a26 Move the primop bits into the compiler/stage<n>/build directories
     87e8c55 Remove distrib/Mac*; fixes #7136
     e84dc37 Remove the distrib/prep-bin-* scripts
     2f40085 Remove cvs-build; it's no longer used
     fe0efaa Remove fake-happy; it's no longer useful
     b921de7 Fix build on Windows
     bc6a2cc Whitespace only in typecheck/TcGenDeriv.lhs
     a49580f Whitespace only in typecheck/TcDeriv.lhs
     74ae9bb Add an "Outputable (InstInfo a)" instance
     e9b1256 Whitespace only in types/FamInstEnv.lhs
     55478b1 ghc-pkg: Print something when no packages are found; fixes #6119
     9991890 Ensure we produce a FunTy for functions (Trac #7312)
     beb2f74 Be lazier when typechecking data type contexts (Trac #7321)
     b285ae1 Fix error in tidying the type variables of a TyCon when building an interface file
     b7fbf3a fix obvious typos
     25dc200 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     5c43947 Don't build the HS*.o files when DYNAMIC_BY_DEFAULT
     4780cbc Add a type signature needed when using GADTs
     83f5c6c When dynamic-by-default, don't use the GHCi linker
     56a2003 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     76410f7 Fix typo
     be497c2 Keep the list of DLLs that we dlopen
     22df953 Fix test for GHCi lib building
     5f3c105 rts: Ignore signal before deleting timer. Fixes #7303.
     3c45e5a Fix installing when dynlibs-by-default
     817e1d5 Add TRANSITIVE_DEPS variables to package-data.mk files
     a7c70e9 Move the RPATH computation into the build rules
     b3dacbd Don't set dynlib install names when building
     8c24ab9 Double a couple of $s for consistency
     0271742 Get dynamic-by-default mostly working on OS X
     bbd9139 Use Cabal to build hpc-bin
     70a76bf Use Cabal to build ghctags
     7da6555 Fix copy/paste-o
     0af4562 Fix some dependencies
     8f4cb4d Default to dynamic-by-default on OSX/64
     8af2d94 Merge branch 'master' of http://darcs.haskell.org/ghc
     c8bac7c Elaborate the typechecker's trace slightly
     7435825 Add kind-defaulting in simplifyInfer (fixes Trac #7332)
     9ab868e Comments only
     81594da Use isCheapApp in exprIsWorkFree
     a609027 Add a new traceMarker# primop for use in profiling output
     0b2a6a0 Wrap a bracket quotation in a coercion that makes it have the right type
     6976210 Refactor the type of tcBracked (no change in behaviour)
     92916e0 Move occurCheckExpand from TcCanonical to TcType
     8691041 Improve error reporting for kind occurs-checks
     9f3b927 Use -O0 -g C flags when compiling a debug way
     ad94e00 Make -ddump-cmmz-cfg turn on the right flag
     bb8cb0e Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     81f43eb Remove unused dumpIfSet_dyn_or
     5cd52bf Build system fix for building a profiling GHC
     86f6acd Rename DynFlag to GeneralFlag
     d5ab88c Rename setDynFlag, unSetDynFlag following the DynFlag->GeneralFlag rename
     4d4797d Whitespace only in simplStg/SimplStg.lhs
     6759e5a Remove a copy of foldM, and use the standard function instead
     cd33eef Some alpha renaming
     f934258 Fix build on OS X (fix from Duncan Coutts)
     6e771fa Remove unused -ddump flags
     51da4ee Put header and timestamp in dump files
     d4a1964 Refactor the way dump flags are handled
     21e5b61 Turn DYNAMIC_BY_DEFAULT off in mk/build.mk.sample
     660dc69 Follow 'flags' -> 'generalFlags' rename
     5e54d55 Fix conversion of HsRule to TH syntax
     984676d Deprecate Rank2Types and PolymorphicComponents, in favour of RankNTypes
     b597182 Fix a long-standing bug in tidying
     a351361 Comments and debug tracing only
     e252bb6 Improve error reporting for kind errors
     0001f51 Whitespace only in nativeGen/PIC.hs
     6a58aa0 In approximateWC, do not float contraints out of an implication with equalities
     242fc56 Some refactoring of the occurs check in TcUnify
     5381000 profiling fixes
     2726033 Improve reporting of duplicate signatures
     6fbd46b Remove the old codegen
     8019bc2 Only promote *non-existential* data constructors
     c6f4f8a Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     6c54727 Set the way when loading dynamic objects for GHCi
     d277031 Suppress deprecation warnings for Rank2Types in libraries that use the flag
     827598e Wibbles in TcErrors
     1152f94 An accidentally-omitted part of commit 8019bc2c, about promoting data constructors
     4a738e1 Simplify and clean up kind-checking of type/class declarations
     8e189a7 Simplify code slightly; no change in behaviour
     429c81c Merge branch 'master' of http://darcs.haskell.org/ghc
     bca2e47 Whitespace only in simplCore/OccurAnal.lhs
     176a360 Fix typo
     e3d7889 Add some more primop rules; fixes #7286
     fc5a6e2 Whitespace only in hsSyn/HsExpr.lhs
     2cf9093 Add some more PrimOp rules
     b093521 Add a rule for (plusAddr# x 0) == x; fixes #7284
     9f9bb2b Add the p_dyn and thr_p_dyn ways
     4f83f54 Set V = 1 by default, and add info about turning it off to build.mk.sample
     771d376 add GHC.Float.rationalToFloat, rationalToDouble (fixes #7295)
     6bb741b Use fromRational when pre-computing fromRational literals
     82879d9 Be careful when combining two CFunEqCans, in the case where one has a unification variable on the right.
     cd51b9c In lookupFlatEqn, look in the flat-cache *last*
     b243d30 Merge branch 'master' of http://darcs.haskell.org/ghc
     49108c3 typo
     412af8c Foreign calls can clobber heap & stack memory too
     14ddde0 When DYNAMIC_BY_DEFAULT, make inplace wrappers for everything
     5f37e0c Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     82ab12a October 2012 stats
     2c2be63 comments only
     c7942f9 Fix a silly bug that would cause -xc to print less than useful information
     d81d70b fix a warning
     2471a6b Use canned heap checks to save a few bytes of code
     dc7a936 Avoid calling toInfoLbl on the entry label (#7313)
     bba7621 Fix -fPIC on OS X x86
     a5bf0d5 Merge branch 'master' of http://darcs.haskell.org/ghc
     2324b40 removeWay should also unset the wayGeneralFlags
     a7e0d44 a small -fPIC optimisation
     88a6f86 Small optimisation: always sink/inline reg1 = reg2 assignments
     a58b2d0 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     a299f10 Use Cabal to build mkUserGuidePart
     fb41ac5 extend LD_LIBRARY_PATH instead of replacing it
     09209de Add a case for CmmLabelDiffOff to cmmOffsetLit
     65fec07 Comment to explain why we need to split proc points on x86/Darwin with -fPIC
     61bf570 fix bug in heap check in putMVar#
     0b3811c typo
     935bf7c Merge branch 'master' of http://darcs.haskell.org/ghc
     b8da5dd Remove the kludgy TH dependencies
     68ae113 Make it possible to build with only way dyn
     b01edb0 Merge branch 'master' of http://darcs.haskell.org/ghc
     c67b431 Always use --force when registering packages
     df2bcd8 Set the default way correctly when dynamic-by-default
     820134a remove unused sched_shutting_down
     afbceef delete old comments
     24b4bfb Fix bug in 88a6f863d9f127fc1b03a1e2f068fd20ecbe096c (#7366)
     9008ae0 declare stg_gc_prim and stg_killMyself (#7350)
     cdf1389 fix off-by-one-column in showRichTokenStream (#7351)
     467e1a6 fprintCCS_stderr: untag the exception (#7319)
     b54318d Remove an outdated comment
     38aeca2 Make "ghc-pkg check" check for prof and dyn ways, as well as vanilla
     86e2479 Fix the transformers-building code, and move it from validate to ghc.mk
     6e28baa Make DefaultFastGhcLibWays be just "dyn" when we are dynamic by default
     9a2f777 Merge branch 'master' of http://darcs.haskell.org/ghc
     c588395 Fix a bug in CmmSink exposed by a recent optimisation (#7366)
     c03a899 Fix installation of vanilla libraries
     8d8af5e Revert "Always use --force when registering packages"
     f3115bd Fix the haddocking build system rules when dynamic is the default way
     93d4539 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     e0c77c9 Fix doc typo; fixes #7318
     615268a Tweak build.mk.sample
     edb5303 Fix installation
     9246f7c Improve trace
     b6acaf0 Comments in Note [Efficient orientation] about interacting CFunEqCans
     66ec09b Merge branch 'master' of http://darcs.haskell.org/ghc
     3406c06 More info on a Core Lint failure
     ec0d62c Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     788cead Revert "Suppress deprecation warnings for Rank2Types in libraries that use the flag"
     26b2caf Make Rank2Types and PolymorphicComponents into a synonym for RankNTypes (no deprecation)
     84d527b Improve the GhcLibWays sanity checking
     0c7f0c2 Add some missing parentheses to mkDerivedConstants.c
     fb1b2c7 Fix a couple of format strings
     3a0a315 Fix build on platforms on which we don't have register info
     1b02de8 Remove some old .gitignore entries
     d24ffd6 Remove some more unused .gitignore entries
     0c4ed55 Move ghc-pkg's generated Version.hs inside the dist directories
     5558bea Rearrange .gitignore a little
     795a3fd More .gitignore updates
     5956473 Fix a makefile rule
     f8c23ff Fix bug with reporting deprecated use of flag (Trac #7349)
     910a642 Do not treat a constructor in a *pattern* as a *use* of that constructor
     11aa737 Fix dependency generation when GhcLibWays = dyn p
     4444dd8 INFO_TABLE_RET should generate a CmmRetInfoLabel, not a CmmInfoLabel
     092c0bd Make DYNAMIC_BY_DEFAULT=NO when GhcUnregisterised
     8e81684 Cmm jumps always have live register information.
     f9265dd Attach proper jump liveness information to generated C-- code.
     3db0254 Save and restore registers across calls to unlockClosure.
     6a68507 Generalize register sets and liveness calculations.
     82ede42 Properly mark C-- calls to _assertFail as "never returns".
     5ee08dd Attach global register liveness info to Cmm procedures.
     e2f6bbd Draw STG F and D registers from the same pool of available SSE registers on x86-64.
     dcf88e6 Generate correct LLVM for the new register allocation scheme.
     a50cd57 Get ride of the -fregs-liveness flag.
     8c7dc71 Change how touchy sets the file time
     8d226e2 Improve touchy
     8623be0 Merge branch 'master' of http://darcs.haskell.org/ghc
     a44a5e3 Clean some old files that we no longer generate
     4baebfa Comments only
     10f8342 Do not instantiate unification variables with polytypes
     7e255c5 Merge branch 'master' of http://darcs.haskell.org/ghc
     ab5008d Retainer prof: immutable arrays are not retainers, and fix the docs
     984149b Fix C macro bug that was causing some stack checks to erroneously succeed
     2677e42 Wibble to recent changes to TcErrors
     33d0f49 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     232f1a2 Add notes about type-family overlap in GHCi (see Trac #7102)
     d7ca7af Whitespace only in nativeGen/NCGMonad.hs
     2073e3e Don't clearNurseries() in parallel with -debug
     d28a722 A couple of W_s should be P_s (not an actual bug, I think)
     26e576c Fix bug in stg_ctoi_R1n (could cause GHCi crashes)
     ee43ad5 turn off cmm optimisation for the debug way
     3a6b1bf Turn on -O2 for the RTS by default
     458ee4f Add -fghci-hist-size=N to set the number of previous steps stored by :trace
     8703bbc The shape of StgTVar should not depend on THREADED_RTS
     225172e Fix bug in stg_enter_checkbh
     dba4fa5 Fix typos
     7706bee Whitespace only in codeGen/StgCmmPrim.hs
     2293238 Fix popcnt calls
     d163845 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     095b9bf Don't put uniqs in ghc wrapper function names; part of #4012
     7c4157a Whitespace only in basicTypes/Name.lhs
     f416129 Don't use a unique in the stable name of a foreign export
     0a7c4ef Whitespace only in typecheck/TcRnTypes.lhs
     fb31191 Refactoring: Make a HasModule class for getModule
     d868491 Remove unused function fmapM_maybe
     af072fc Change how dependency generation works; fixes #7381
     f2b953f Remove an -fno-cse flag
     bc4580c Whitespace only in specialise/SpecConstr.lhs
     ede3bd9 Whitespace only in basicTypes/Id.lhs
     ba38f99 Avoid putting uniqs in specconstr rules; part of #4012
     680dca1 typo
     8b25d39 Save R1/R2/.. across foreign calls
     811a19c fix 'return' in cmm code when tablesNextToCode==False
     a307ad5 small optimisation: inline stmNewTVar()
     9f68cce loadThreadState should set HpAlloc=0
     699f8e1 Remove getModuleDs; we now just use getModule
     6ca4616 Comments only
     acbe526 Fix the instantiation of data constructors in the GHCi debugger
     4dade85 Make rewriteCtFlavor lazy in the coercion for Derived evidence
     545bb79 Refine the "kick-out" predicate for CTyVarEq
     2e43779 Merge branch 'master' of http://darcs.haskell.org/ghc
     3ca7260 typos
     50728d0 another typo
     3862220 fix typo, courtesy of Jon Cave, thanks!
     f5e5316 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     1a0af0e Add a comment about why we use nextWrapperNum rather than a unique
     7dd7008 Give dynamic libraries, as well as programs, RPATHs
     71f7ab6 define own version of PRIdPTR on platform where its not available
     c2b5698 Give an error if we can't find a suitable value for PRIdPTR
     b78b6b3 add note about compilation safety to safe haskell docs
     df04d2d Allow '-' to be used as an infix type constructor.
     121768d Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     d92bd17 Remove OldCmm, convert backends to consume new Cmm
     9295780 Fix warnings
     4dc7d04 replaceLabels: null out the cml_cont field of CmmCall
     a1ebe37 handle MO_Touch, and generate no code for it.
     e15981a some W_s should be P_s
     afd7e22 assert HpAlloc == 0
     65e46f1 a fix for checkTSO(): the TSO could be a WHITEHOLE
     2ef95e8 remove some unused variables
     1c160e5 ASSERT(HpAlloc==0) in the update code, to catch HpAlloc bugs
     f49271c Replace mkDerivedConstants.c with DeriveConstants.hs
     0564a63 Add some more flags to includes_CC_OPTS
     37710de Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     30b7eba Fix build on Windows
     4270d7e Fix the Slow calling convention (#7192)
     e86dee3 Fix installing on Windows
     4aa921e Don't include a (void *) cast in BLOCK_ROUND_UP
     53e9916 Fix the OFFSET macro
     958faee Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     9756690 Tell the compiler about alpha, mipseb and mipsel again; fixes #7339
     a9ec8ec Remove the inline primop
     9d7182f Remove the nonexistent lazy primop, and follow move from GHC.Base to GHC.Magic
     7ea4966 Update the "Special built-in functions" docs
     e407935 Remove the HAVE_SETITIMER_VIRTUAL configure test
     244882d Remove unused FPTOOLS_GREENCARD configure macro
     f871ac9 Remove unused FP_EVAL_STDERR configure macro
     ea301fa Remove unused FP_GEN_FO and FP_PROG_FOP configure macros
     e605c3e Simplify BOOTSTRAPPING_GHC_INFO_FIELD
     70a0dd6 Remove unused FP_PROG_SORT / SortCmd / SORT
     da3b7cc Remove unused FPTOOLS_SHEBANG_PERL
     c0017bd Fix FP_CHECK_TIMER_CREATE when cross-compiling
     7b41a69 Remove redundant configure check for timer_create
     f0f63a5 De-tabify register allocator code
     b13ebb6 Comments and formatting to register allocators
     cace1ca Comments and formatting to spill cleaner
     a157ea7 Comments and formatting to spill cost code
     0b436ae Comments and formatting to register allocator stats
     fb50847 Haddoc fix
     3f99654 Improve documentation about instance resolution following suggestions from Mike Sperber
     234fd08 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     6e4f6c6 typos in comments
     97dc57c fix bug in previous commit, 65e46f144f3d8b18de7264b0b099086153c68d6c
     6d784c4 Add a write barrier for TVAR closures
     1437590 Document -XTypeHoles
     4ee5e3b Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     80269ef fix syntax error in generated C (#7407)
     a70e45f C backend: ignore MO_Touch
     dfb8d40 We now assume that offsetof() is always defined
     cf939b3 Add a stddef.h #include to C file generated by DeriveConstants
     5874a66 Remove some dependencies
     7da1376 Code-size optimisation for top-level indirections (#7308)
     31c0717 C backend: put the entry block first
     6486213 Reject promoted constructors when -XDataKinds is not enabled (FIX #7433)
     704f802 fix some typos
     c22850f Enable dynamic-by-default for unregisterised arches
     91c6593 Enable GhcWithInterpreter when DYNAMIC_BY_DEFAULT is on
     951e28c Unconditionally disable DYNAMIC_BY_DEFAULT for now
     d94250e add embedded vendor
     64efee6 Add fixity information to primops (ticket #6026)
     359efbf typo
     eb5196c Move seq's fixity declaration info primops.txt.pp
     9ef4d48 Fix building on Sparc/Solaris with non-GNU linker; fixes #5407
     b350ac5 Use the right environment for tidying the types of a data constructor
     e1dbabb Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     b610a84 "hpc version" now shows the version number from the .cabal file
     c04a984 Separate warning flags from other flags in validate-settings.mk
     95027b8 de-tab hpc
     39f2737 Add a --reset-hpcdirs flag to hpc
     464646d Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     6eb0341 Revert "Move seq's fixity declaration info primops.txt.pp"
     2334112 Fix broken -fPIC on Darwin/PPC (#7442)
     948f101 Normalise command names differently in sync-all
     f73d60b Use submodules for repositories with upstreams
     c2430f0 Make Constraint and * look identical in Core (System FC)
     c8f4f50 Accurately report usage of newtype data constructors in FFI declarations
     1135c84 Improve kind inference for tuple types
     661c1c1 Improve error message when a variable is used both as kind and type variable
     6960556 Merge branch 'master' of http://darcs.haskell.org/ghc
     3a82618 typos in note
     086d7c5 Fix #7231: don't unload stable modules when there is an error later
     77ef6ca Replace all uses of ghcError with throwGhcException and purge ghcError.
     10edb42 Whitespace only in compiler/ghci/LibFFI.hsc
     c2f9b74 Small refactoring
     bd9e029 Remove a use of printf
     3005e90 Add configure option to use system provided libffi; fixes #5743
     2ec32a8 Add ":info!" to GHCi.  This shows all instances without filtering first.
     c793cc3 libffi build system tweaks
     e9f38cb Remove accidentally-commited testing aid
     495ef78 Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     779f10f Extend parser to allow specification of RULES that never fire. #7162
     2c6939a Make ghc-pkg print less on error.
     0bb2274 Remove unused PYTHON in build system
     7ee5bed Link in-tree libffi to rts. Fixes trac #5743.
     7009f58 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     e305fc7 Detab
     d53e222 typo
     2332b4b Remove case from coreLintExpr dealing with types, as it is not used.
     d2ff25f Update dependencies
     4ef1bd4 Update submodules
     cfb9696 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     81b7e58 Added GHC formalism to the GHC source tree.
     959d5a9 Added the docs/core-spec README
     fe1fce8 Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     b5ce9de Remove dead code predTreePredType
     61f770f isTauTy should be True for LitTy (see Trac #7459)
     0cb35b5 Mac OS X 10.6 needed for pthread_threadid_np(), fixes #7356
     45e70a1 Merge branch 'ticket-7442' of git://github.com/phonohawk/ghc
     d6d1559 Tweak comments
     56240c1 Update haskeline submodule
     691c8a8 Don't get submodules when 'get'ing
     8fd3f3c Use a submodule for the time package
     ccce9fe When pulling, only 'fetch' in submodules
     4b4f014 Add a check for old time packaes
     c3db2b2 Tweak sync-all
     31d771b Use -e rather than -f when checking for libraries/time/.git
     3a40456 Make "sync-all pull --rebase" work
     156d30d Fix buglet in -ddump-minimal-imports (Trac #7476)
     9467f73 Merge branch 'master' of http://darcs.haskell.org/ghc
     e6ce335 Fix pprPanic so that it doesn't throw away the SDoc part of the error.
     88eeabc Merge branch 'master' of http://darcs.haskell.org/ghc
     70c4e4b Rearrange configure.ac a bit
     3c06c09 Rearrange configure.ac a bit
     50905e1 Revert "Fix pprPanic so that it doesn't throw away the SDoc part of the error."
     b77da25 Rewrote vectorisation avoidance (based on the HS paper)
     895ff21 Vectoriser: fix vectorisation avoidance for case expressions
     c0d8469 Allow existential data constructors to be promoted
     431e804 Merge branch 'master' of http://darcs.haskell.org/ghc
     bb2f56a Add comment
     f971e75 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     95d8658 In FP_GCC_VERSION, test $CC not $GCC
     3fc453a Don't define DYNAMIC when compiling the dyn way
     57d6798 When using a GHC plugin, load its interface file very partially: just enough that it can be used, without its rules and instances affecting (and being linked from!) the module being compiled.
     b0626b6 Document promotion of existential data types
     5b746f5 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     3864da2 Typo
     71b5ca5 Refactor findAndReadIface; no functional changes
     ccdccee Whitespace only in iface/IfaceType.lhs
     b25d709 Add the beginnings of support for building vanilla and dynamic at the same time
     d842dff Use a MonadIO instance instead of an 'io' function
     9a20e54 Stop attempting to "trim" data types in interface files
     8a0534f Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     6bdac1c Make nativeCodeGen return the rest of its UniqSupply
     9b2882c Merge branch 'master' of mac:ghc/git/val64/.
     566920c Add -funbox-strict-primitive-fields
     e4feb52 fix description of ghci instance env bug
     250f026 fix code in library initialisation example (#7471)
     27770ae Invalidate the ModSummary cache in setSessionDynFlags (#7478)
     b85a849 Pessimistically assume that unknown arches can't do unaligned loads
     e415777 Detabbing
     4f7027d Document -funbox-strict-primitive-fields
     86e2a2a Don't set "-O0 -g" C flags when -debug is given
     c1c2d84 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     7bf6eb9 Minor twiddle to -funbox-strict-primitive-fields docs
     1435eef Refactor primitive field unpacking check
     609aecb Tweaks to dynamic-too code
     713c514 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     d7d25db Merge branch 'master' of http://darcs.haskell.org/ghc
     cea7aa3 Merge branch 'master' of http://darcs.haskell.org/ghc
     e5182b7 Add replaceDynFlags to the ContainsDynFlags class
     0c4a9f3 Add a function to change DynFlags to be suitable for compiling for way=dynamic
     ecd9676 Fix loading dynamic interfaces when using -dynamic-too
     a33dddc Vectoriser: distinguish vectorised from parallel types and functions
     87c0a59 Vectoriser: don't include scalar types in base set of parallel tycons
     b339dd4 Change how sync-all handles directory changes
     3558690 Vectoriser: enable encapsulation of scalar functional expression of arbitrary form
     332e681 Add -funbox-strict-primitive-fields example
     f184d9c Fix a bug in the handling of nested orElse
     31d8900 Fix #7487
     b0339aa document special "this" syntax for PackageImports (#7409)
     d684114 add enabled_capabilities (#7491)
     497cb61 Merge branch 'master' of http://darcs.haskell.org/ghc
     48bb69a Small refactoring: Use more idiomatic strictness forcing in AsmCodeGen
     d23148a Package the NativeGen state up into a named type
     8246c7a Tweak how 'count' is handled in the nativeCodeGen
     8685535 Add more plumbing to the nativeCodeGen
     bd8f7fc Implement the -dynamic-too optimised path for the NCG
     40614d8 Vectoriser: improve top-level check and vectFnExpr
     2af1895 Vectoriser: VECTORISE pragma assumes parallel values
     5d0d1d9 typo
     750a34b Small code tidy-up
     7df6d78 Add a comment
     d5b5d48 Use ByteString rather than FastBytes inside FastZString
     589b628 Merge ../bs
     7651b67 Make FastBytes a synonym for ByteString
     2e8c769 Implement word2Float# and word2Double#
     e2564ce Merge ../bs
     ab9de78 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     2b977d9 Remove most of TailCalls.h
     265af43 Make enabled_capabilities visible (fixes dynamic linking)
     c79f733 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     7085b84 Inline some FastBytes/ByteString wrappers
     fae0d4c Whitespace only in hsSyn/Convert.lhs
     3c17143 Use BS.pack instead of mkFastBytesByteList
     80a3a15 Remove a couple more FastBytes functions
     faa8ff4 Major refactoring of the way that UNPACK pragmas are handled
     96acba6 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     a243fa7 Use ByteString rather than FastBytes in Binary
     ca56668 Remove the trivial mkFastStringFastBytes wrapper
     6409ba5 Rename remaining FastBytes usages to ByteString
     bcf7123 Implement the slow mode of -dynamic-too
     551472b Vectoriser: don't pack free *scalar* variables
     eec4c10 Call gcc with '-x assembler-with-cpp' instead of '-x assembler'.
     6a990ac De-tab compiler/nativeGen/PPC/Instr.hs.
     51d3645 PPC: Implement stack resizing for the linear register allocator.
     f8fb4a4 Vectoriser: depending set of a vectorised tycon need only be vectorised if also parallel
     6e0d45a Small refactoring: makes it easier to see what nativeCodeGen actually does
     06a962b Remove some redundant parentheses
     55c55f1 Revert "Fix a bug in the handling of nested orElse"
     a006ecd A better fix for #7493 (see comment for details)
     90fac75 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     909d52e Document the behavior of "info!".
     ea8490e Tidy up documtation of monomorphsim restriction etc
     b585312 Wibbles to faa8ff40 (UNPACK pragmas)
     650f76f Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     e3aa165 typo
     a38b832 spelling in doc
     942939c Fix Trac #7506 (missing check for form of FFI type)
     8c1aab0 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     aad93f5 Move the kind Nat and Symbol out of TysPrim and into TysWiredIn
     a62c437 Add some ASSERTs to calls of zipTopTvSubst
     3394d49 Pass the correct inst_tys argument to dataConCannotMatch, in mkRecSelBinds
     be5cc2e Fix TcUnify.matchExpectedTyConApp so that it returns types of compatible kinds
     9429d79 Merge branch 'master' of http://darcs.haskell.org/ghc
     f6f881f Rename all of the 'cmmz' flags and make them more consistent.
     54a3963 'sync-all get -q' also passes -q to 'git submodule'
     02c4ab0 Redirect asynchronous exceptions to the sandbox thread in runStmt (#1381)
     1353d1e Fix over-zealous ASSERT in TcUnify
     866d28d Merge branch 'master' of http://darcs.haskell.org/ghc
     b8739b2 Allow newtypes to be promoted
     40ef925 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     66fa188 Likely fix to uninitialized DynFlags in plugins.
     6290c7b Clarify promotion rules for newtypes in the documentation
     c56c355 Only allow special NeverActive syntax for RULES.
     d3e2912 Clarify documentation of [~] syntax on RULE activations
     52e4300 Use expectP in deriving( Read )
     8366792 Implement overlapping type family instances.
     d2a5a9c rename do_map_arrow as do_premap (no semantic change)
     1ee1cd4 Make {-# UNPACK #-} work for type/data family invocations
     e5ccb4e Merge branch 'master' of http://darcs.haskell.org/ghc
     e9e650d A bit more tracing
     1d07cc0 Remember to zonk when taking free variables in simpl_top
     7cc8a3c Merge branch 'master' of http://darcs.haskell.org/ghc
     e661e29 Comment typo only
     9ea2b66 Simplify the binder-swap transformation
     89eb9e9 Add traceSmpl for simplifier tracing, now that the simplifier has the IO monad
     bacf7ca Make combine-identical-alternatives work again (Trac #7360)
     545fd8b Make the treatment of addAltUnfoldings handle casts
     4527991 Fix dictionaries for SingI.
     db9c062 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     9929172 Remove references to GHC 6.6 in docs
     18003c9 Fix typo in comment (Trac #7526)
     5efe9b1 Refactor the invariants for ClsInsts
     b43fdcf Comments and white space only
     215cf42 Make the comments about SingI and EvLit match current reality
     e89f3ba In type or data instances, check that all variables are bound
     1884f81 Merge branch 'master' of http://darcs.haskell.org/ghc
     9beb615 Make the fib_tvs field of FamInstBranch into a *list* not a *set*
     243523b Merge branch 'master' of http://darcs.haskell.org/ghc
     1086bc1 Add a reference to Note [SingI and EvLit] in the new SingI stuff
     302172f Remove unnecessary import
     5a6a223 Add flag -fwarn-duplicate-constraints
     4496fda Minor refactoring plus comments
     9b9f197 Improve HsSyn pretty-printing of instance declarations (fixes Trac #7532)
     5f77b31 Update strictness documentation (Trac #7546)
     3f7b147 Fix bug in External Core pretty printer (fixes Trac #7547)
     3fa7340 De-tab PprExternalCore
     7fa2ce2 Tidy the type in badInstSigErr (fixes Trac #7545)
     b0c0cae Define ListSetOps.getNth, and use it
     d36770b Refactoring; no change in behaviour
     948c1d3 Crucial bug fix: use scrut' rather than scrut!
     6761dc2 Add an extra error check in DEBUG mode for ill-typed unfoldings
     1687a66 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     b13d546 Whitespace only in utils/MonadUtils.hs
     71feb10 Ship transformers with GHC
     6d5f25f Fix LLVM code generated for word2Float# and word2Double#.
     b9eb17c Make validating with GhcProfiled=YES Just Work
     d967432 Set DBLATEX_OPTS to -P 'filename.as.url=0' (fixes #7486)
     28d9a03 Make CaseElim a bit less aggressive
     3671e67 Allow empty case expressions (and lambda-case) with -XEmptyCase
     a8941e2 Refactor HsExpr.MatchGroup
     e52d9d4 Add an ASSERT
     74d4018 Switch on -XEmptyCase when renaming derived declarations
     fbff64a Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     49ca2a3 Changed deriving of Functor, Foldable, Traversable to fix #7436. Added foldMap to derived Foldable instance.
     3d51f27 Added note explaining the lambdas generated by functor deriving code, and how it compares to the old deriving code which used eta expansion.
     9d9d09d Add a -rpath entry for the RTS library, so that it can find libffi
     5765248 Refactor invariants for FamInsts.
     4da767e Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     7d1216a make "./sync-all -r <path> remote set-url origin" work
     03d360f Fix bugs in allocMoreStack (#7498, #7510)
     a8ea80f Rearrange the computation of unused imports; fixes Trac #7454
     afe9a3b Remove two unused imports, detected by the fix to Trac #7454
     97db0ed Re-engineer the ambiguity test for user type signatures
     7dffc18 Merge remote branch 'origin/master'
     f879703 Add missing file TcValidity.lhs
     0a24be0 Add missing import
     851e4e7 Fix Trac #7560.
     4737d64 More tidying up in FamInstBranch
     41e9276 Merge branch 'master' of http://darcs.haskell.org/ghc
     f838d2f add docs for ":showi language" (#7501)
     0c42e30 remove unnecessary size field in BCO (#7518)
     343548d fix disassembler after removal of size field in bco->instrs  (#7518)
     3af022f Fix some incorrect narrowing rules (#7361)
     35691ad Update the -no-auto-link-packages docs
     8dd2f98 Support the MergeStub phase when building with dynamic-too
     5cb0880 Make the rule for .hi files depend on the .hs/.lhs files
     1353b4a Enable the .hi file sanity check when not on Windows
     9e3088f Remove redundant rule from rules/build-package.mk
     ccd8c6f Handle -boot files properly when doing -dynamic-too
     bab8dc7 Add preprocessor defines when SSE is enabled
     35428a3 Refactoring: No functional change
     96ea76c dynamic-too progress
     fb7391a Build system: Add ExtraMakefileSanityChecks for extra safety
     8b1e30f Small build system refactoring
     77e7841 Update bytestring and terminfo repos
     b9fae0c Improve some error messages
     f3d3bae Remove checkCOrAsmOrLlvmOrDotNetOrInterp
     49e6c96 Update a comment
     de373f9 Whitespace only in nativeGen/SPARC/Base.hs
     385dced Update a panic message
     68833e5 Make "happensBefore" take account of whether we are unregisterised
     acb0cd9 Don't make -C imply -fvia-C
     5427df8 Merge branch 'master' of https://github.com/ghc/ghc
     782faec Clarify docs on when -ddump-* imply -fforce-recomp; fixes #7406
     6387eba Fix typo in docs; spotted by Gabor Greif
     fe61599 Use a version of the coverage condition even with UndecidableInstances.
     12f3a53 Fixup comment: typos + I had the generalization rule backwards.
     deec5b7 Be willing to parse {-# UNPACK #-} without '!'
     82f81d1 Merge branch 'master' of http://darcs.haskell.org/ghc
     def97b8 Fix up comment:  I was just wrong previously, the original GHC comment on `oclose` is correct.
     152e703 When doing UNPACK pragmas, be careful to only unpack *data* types not newtypes
     29054b0 White space only
     ecddaca Tidy up FunDeps.oclose
     440a9a5 Tiny refactoring, really just white space
     a6ab0a4 Fix Trac #7585.
     f77291d Pass --with-ld=$(LD) to ghc-cabal when configuring packages (#6086)
     b06c1eb When cross-compiling, pass --host to package configure scripts
     8f731f2 Merge branch 'master' of http://darcs.haskell.org/ghc
     0aae1e1 Better abstraction over run queues.
     b05531b Add a 'quick-llvm' build mode to mk/build.mk.
     5cca0b4 Add -f[no-]warn-unsupported-llvm-version. Closes Trac #7579.
     25f8d04 Fix floating point constants in LLVM backend (#7600).
     aef38d1 Output LLVM version in use at -V2.
     520dc1d Rearrange includes to avoid a clash on ARM/Linux
     900e7d2 make it safe to include this after GCTDecl.h
     0831a12 Major patch to implement the new Demand Analyser
     91b44bc A simple improvement to CSE
     057384f Merge branch 'master' of http://darcs.haskell.org/ghc
     109a1e5 Tidy up cross-compiling
     81f4cd3 Merge branch 'master' of http://darcs.haskell.org/ghc
     fd3fd18 Expose the prototype for getMonotonicNSec
     b4e86fa Minor impovement to when we float a let out of a right-hand side:
     3f90064 Use pthread_kill on OS X too
     0dcccf0 Hopefully fix breakage on OS X w/ LLVM
     b7189de Clean up -msse flag handling
     571ecdd If -msse is specified, pass it to the LLVM backend
     0dc9f1c Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     b14ddb2 Expose genericRaise; fixes signals004(dyn) no OS X 32
     f61fbf3 Restore the primitive and vector submodules
     e39539d Add missing case in eqHsBang; makes rnfail055 pass again
     04abb49 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     ea53d9c Document overlapping instances more clearly
     858888e Remove unused HscStats.lhs; fixes #7605
     2c12b91 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     fb93d79 Up supported LLVM version to 3.3.
     8d01b10 Comments only (about trimming the type environment)
     927ca60 Update mailing lists in the users guide
     5d99d6a Comments only
     2ec39c7 Exploit the invariant for AxInstCo to simplify coercionKind
     2cc42db When printing types in the interactive UI, take account of free variables
     5469388 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     65e4195 Use pprTypeForUser when printing kinds in ghci
     14c01e0 Ensure the LLVM codegen correctly handles literals in a branch. #7571
     c94528a Comments only
     7a1480c Allow eta-reduction of eval'd functions if of arity 1
     35f1fc9 Allow CaseElim if the case binder is the next thing to be eval'd
     fa1e593 Fix llvm backend when 32bit build on 64bit OSX. (#7617)
     1a70306 Fix our handling of literals and types in LLVM (#7575).
     629ae2a Add support for nto-qnx (BlackBerry 10)
     39148b8 fix validate-breaking warning
     48b9589 Tidy up: move info-table related stuff to CmmInfo
     bb39e04 Solaris: do not use timer_create
     5931ee8 fix rts/Linker compilation issues on AMD64/Solaris platform
     c23faf3 ghc: mkGmpDerivedConstants binary gone away
     b479713 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     79dae93 Print infix type constructors in back-ticks
     d3b8991 Introduce CPR for sum types (Trac #5075)
     8e5313c Comments only
     0f8c6fc Use fsep, not sep, when printing lots of Core binders
     182fe6f Comments only
     ff5bea7 Merge branch 'master' of http://darcs.haskell.org/ghc
     5388919 do not use -rpath-link linker option on Solaris.
     3c9d630 Added support to cross-compile to android
     7299516 Fix various issues with a Stage1Only=NO cross-compile
     388e1e8 Allow -fllvm to be used when compiling unregisterised (#7622)
     09ff0e0 Refactor and improve the promotion inference
     829be06 Use kind 'Symbol' consistently, rather than kind 'String'
     a47ee23 Merge branch 'master' of http://darcs.haskell.org/ghc
     b4c1747 Remove unused argument
     18b106e Comments only
     82219ae The type/kind variables of a class decl scope over the associated types
     1c4e896 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     e342666 Collapse DmdResult into CPRResult
     0ab8cc1 Merge branch 'master' of http://darcs.haskell.org/ghc
     9c661e0 Remove dead code
     48a96bd Improve LLVM options for ARMv6
     351a8c6 fix ARM hard float "detection"
     a3a2348 Add support to compare for comparing whole directories
     5943a5b Use Test.Regex.PCRE instead of .Posix in compare
     d1fd45d Add a kludge to the compare tool for unicode filenames
     1095d51 Add a "Done." line to compare
     146b0ea use -e rather than -d when checking for the existence of a subrepo
     6ff3c31 Fix documentation bug: TSOs are *not* unconditionally kept on the mutable list.
     a98e51e More refactoring of FamInst/FamInstEnv; finally fixes Trac #7524
     f1fa6eb Pure refactoring
     163da7f Merge branch 'master' of http://darcs.haskell.org/ghc
     167dfe2 Minor pretty printing changes only
     2627e62 Comments only
     24644bb Fix comments on isValArg
     a7f9930 StaticFlags code cleanup (fixes #7595)
     d79c0c4 Improve consistency checking for associated type-family instances
     6464d37 When quantifying associated types, we may have TyVars involved, not just TcTyVars This required a little adjustment in zonkQuantifiedTyVars
     5943886 Merge branch 'master' of http://darcs.haskell.org/ghc
     71ae069 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     bf069cb Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     b91f3d2 hopefully fix #7620
     0375fcb ARM: infer VFPv2 presence from the C compiler
     1b7c1e5 use GhcRtsHcOpts and GhcRtsCcOpts for the debug way too
     bc31dbe Disable any  packages built with stage 2 when cross-compiling
     0768ddb Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     12e3d3f Patch for #7628: improve error message when mixing 32 and 64 bit images (on Mac OS X)
     ba47b1d Tweak the mkDocs script
     43cc231 Tweak the gen_contents_index script
     8d5bc74 Add throwGhcExceptionIO and change a few uses of throwGhcException to use it
     658817b Schedule.h: Fix path of include file in comment
     a23661d STM: Only wake up once
     dbefe7b fix warnings
     9c6dd15 Fix to 02c4ab049: use a weak pointer to the sandbox thread
     677144b Add support for *named* holes; an extension of -XTypeHoles
     dd86634 Merge branch 'master' of http://darcs.haskell.org/ghc
     6ac7bae Expand tabs
     7a6aa91 Use throwGhcExceptionIO rather than throwGhcException in ghci/Linker.lhs
     e66b09e Change a few throwGhcException uses to throwGhcExceptionIO
     2fcb295 Use throwGhcExceptionIO rather than throwGhcException in main/DriverPipeline.hs
     426b9b0 Use throwGhcExceptionIO rather than throwGhcException in main/DynFlags.hs
     1bb4913 Use throwGhcExceptionIO rather than throwGhcException in InteractiveEval.hs
     0a1b7cb Change a few throwGhcException uses to throwGhcExceptionIO
     a0c3263 Change a few throwGhcException uses to throwGhcExceptionIO
     45df026 Make MonadIO a superclass of ExceptionMonad
     e40299c Use throwIO rather than throw
     85056f0 Detect hard/soft float in the same way as other ARM features
     9c5e903 remove old cross-compilation stuff
     4909205 We should be including HaskellMachRegs.h here, not RtsMachRegs.h
     c78804d \#undef REG_R[1-10] as a precaution
     a217e7a include "stg/MachRegs.h" -> include "MachRegs.h"
     3e1745a typos
     d0b823c Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     c0f96bd Document -fvectorise and -favoid-vect. (#5801)
     b0fad0c add $(CrossCompilePrefix) to hp2ps (#7639)
     8bb9548 MachRegs.h requires ghcautoconf.h to be included before it (#7591)
     76eeef4 add CPP
     dc7549a Try to make ghc-pkg and ghc-cabal use the same flags when bootstrapping.
     8760cf3 Whitespace only
     2de4a2a A couple of small refactorings
     329c6cb Remove an out-of-date comment
     d2169af Improve an error message; fixes #984
     1ee495b Fix xhtml's entry in the packages file; fixes #7632
     d60df82 Define __GLASGOW_HASKELL_LLVM__ when using the LLVM back end.
     a544c72 Add support for LLVM vectors.
     f70b6b6 Tell LLVM that all vector stores and loads are potentially unaligned.
     515ba6f Add Cmm support for representing 128-bit-wide SIMD vectors.
     4906460 Add a bits128 type to C--.
     6480a35 Always pass vector values on the stack.
     4af6207 Add the Float32X4# primitive type and associated primops.
     3984b91 Add the Int32X4# primitive type and associated primops.
     7816845 Add the DoubleX2# primitive type and associated primops.
     1811440 Add the Int64X2# primitive type and associated primops.
     33bfc6a Add support for passing SSE vectors in registers.
     089ac71 Add a primop attribute llvm_only.
     cc56f34 Add prefetch primops.
     b39e4de Mimic OldCmm basic block ordering in the LLVM backend.
     8b64ce1 Minor documentation and indentation/layout fixes to SpecConstr
     a066844 spelling
     7d6fece some more typos
     aa1d7d3 Move AsmCodeGen.makeFarBranches to PPC.Instr (#709)
     3cedbfb AsmCodeGen.NcgImpl.ncgMakeFarBranches should take account of info tables (#709)
     40d2ec8 remove last vestiges of AlienScript, it is not used any more
     d034b5a random is a submodule
     2a06453 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     ca5d15a Follow random submodule change
     82a3037 Fix tidying of vectorised code
     f940ec5 Vectoriser: PArray may be part of identity conversions
     7cfed20 Vectoriser: binders of encapsulated lambdas need to be scalar
     ad45b9f Vectoriser: abstract arguments to scalar functions in the right order
     5389b2a Vectoriser: avoid producing (\v -> v) v in liftSimple
     8a6e330 Merge commit '3cedbfb49996da2f029b4a84ca39f4d21f309813'
     d103991 Revert random submodule back to an extant hash.
     a40e7d7 Update the random repo again, now the patch is actually pushed
     1116e3c Revert "Update the random repo again, now the patch is actually pushed"
     874bb7e Remove '-favoid-vect' and add '-fvectorisation-avoidance'
     0403da6 install ghc-pkg correctly when Stage1Only=YES (#7639)
     6a46b46 Add the new random commit again
     40e43fa Add a dependency of program modules on GHC.TopHandler
     d8bd25c Fix a typo
     0735831 Use usecs rather than msecs for microseconds
     fac50f9 Merge branch 'refs/heads/vect-avoid' into vect-avoid-merge
     8a69084 Vectoriser: merge fix
     f933d96 Merge branch 'refs/heads/vect-avoid-merge'
     9a9a2a7 Warning police
     ca106a1 Fix spelling mistake in user guide (#7657).
     b770251 Spelling in comment
     21f00c3 Better pretty-printing of types and coercions
     74f9f8f Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     8c8e959 Fix threadDelay on Windows; fixes ThreadDelay001 failures
     8253d94 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     fb4982c Fix spelling
     ec9377b Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     e705fb0 Unify interfae of both variants FP_ARG_WITH_PATH... in aclocal.m4 and document them.
     2f7044d Tidy up tso->stackobj before calling threadStackUnderflow (#7636)
     c1ae31f comments
     0af03de Require autoconf 2.60, as
     5b8dc20 Clean up AC_PREREQ.
     22b1912 Note major changes in 7.8.1 in 7.8.1 release notes file
     7b8f30d Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     b5c18c9 Fix an old and egregious specialisation bug (Trac #5113)
     d72044d Merge branch 'master' of http://darcs.haskell.org/ghc
     db9248c Don't import TypeRep
     fa86863 Add -fno-cse pragma in DynFlags.hs (fixes #7595)
     f52b4ad Split the PlatformConstants type off into its own module
     bcbfdd0 Yet more refactoring in overlapping type-family instances
     fb02fa0 Merge branch 'master' of http://darcs.haskell.org/ghc
     6d48e90 A bit more tidying up
     ae06df6 Improve sync-all's old-time-repo check
     61e8d5d Better detection of clang in ./configure. Issue #7678.
     213e1c7 Make sure ./configure tests valid C99 programs. Issue #7678.
     1affe46 Revert accidental change.
     426a027 Distinguish between llvm-gcc/gcc in compiler name detection.
     c1feb5f Fix bugs in PPC.Instr.allocMoreStack (#7498)
     33683ba Extra comment about the fix to Trac #5113
     804d8f6 Merge branch 'master' of http://darcs.haskell.org/ghc
     36d9ded Merge remote-tracking branch 'phonohawk/ticket-7498'
     e19a204 allocMoreStack: we should be retargetting table jumps too.
     03ffd5d Update random submodule
     04d7220 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     7b098b6 Fix Trac #7681.
     38a5902 Added RTS hooks for the timer manager.
     24733b8 setNumCapabilities calls GHC.Conc.IO.ioManagerCapabilitiesChanged before returning.
     1cefeee Changed ioManagerCapabilitiesChanged to take no arguments.
     fc2b87d Adding missing symbol in rts/package.conf.in.
     c51d2e5 Merge the new parallel I/O manager
     72b0ba0 Implement poly-kinded Typeable
     adbd30c Use a separate user's guide section for -XAutoDeriveTypeable
     15ccb29 Comments only
     28d99e6 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     faced9b Typeable changes to time while waiting for the upstream to update
     ef4a10c Typeable changes to vector while waiting for the upstream to update
     d595293 Typeable changes to containers while waiting for the upstream to update
     d58481f Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     503b265 Merge branch 'master' of http://darcs.haskell.org/ghc
     3fc1acd Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     7807289 Gentoo calls 'w64' a mingw flavour with mingw-w64 runtime.
     24ec956 Convert README to markdown.
     f525c0b Charge 1 for each case alternative in exprStats
     08af551 Generate better derived code for Eq
     6046b25 Add isNewtype to GHC.Generics (FIX #7631)
     abb78aa Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     c08295a Merge branch 'master' of http://darcs.haskell.org/ghc
     41288a1 Improve pretty-printing of strict lets with -dppr-case-as-let
     57e0883 Export tcIfaceExpr as requested by Trac #7683
     257b4ae Comments only
     9162d15 Simplify the base case for 'check', and thereby fix Trac #7669
     4430227 Desugar bang patterns correctly (fixes Trac #7649)
     6571f4f Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     64aaaa1 Find LLVM tools when version number at end (e.g., llc-3.0) (#7661)
     c894db1 Remove dead darcs handling from configure.
     b395872 Different layout for configure output and llvm tools.
     56d68de Fix comment to use correct option name
     e5085db Fixes to the rts C flags for the debug way
     65a0e1e Simplify the allocation stats accounting
     7e7a4e4 Separate StablePtr and StableName tables (#7674)
     88b4578 small tidyups and refactorings
     f20312f Comments only
     3234a4a Add OverloadedLists, allowing list syntax to be overloaded
     6518ebe Follow changes to HsPat
     d31036e Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     9b6e931 isAlive needs to look through BLACKHOLE indirections
     3c1fd68 removeIndirections: look through BLACKHOLE indirections
     599aaf4 Better pretty-printing for HsType, fixes Trac #7645
     30cf978 Better pretty-printing for Type
     9572477 Merge branch 'master' of http://darcs.haskell.org/ghc
     99af12a Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     c043732 Fix issues with finding llvm tools again (#7661).
     16389d1 Another go at tidying VectInfo
     1b81f15 Improve documentation of overloaded lists
     b2a9fbf Allow different customizations per cross target by obtaining GlobalCrossCompilePrefix from mk/config.mk and using that to include mk/$(GlobalCrossCompilePrefix)build.mk instead of mk/build.mk when present.
     536ee09 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     192789a Don't push to submodules on "./sync-all push"
     d8ab46d Check sub-modules are OK before pushing
     ed21082 Make :kind in GHCi do kind generalisation, always (Trac #7688)
     bc00d90 Look through type synonyms when deciding if something is a type literal.
     a187310 Squash some typos
     6c743b6 Stop using the deprecated System.Cmd
     3c839ac Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     cdf1655 Build system tweak: Do the package checks at configure time
     00a9b91 Update submodule versions
     4c821f0 Whitespace tweak
     ac5a314 Build the stage0 ghc-pkg with Cabal
     137b229 Fix build on Windows: We don't build terminfo on Windows
     9857a6a Add a missing $ to a dependency
     b893286 Define utils/ghc-pkg_dist_PROG correctly for Windows
     c39d315 Build fix for dyn way on Windows; patch from nus
     097f723 Small refactoring; patch from nus
     5855496 Update submodules
     94914b9 iOS patch no 1: Select operating system; from StephenBlackheath
     c476494 iOS patch no 2: remove obsolete CROSS_COMPILE variable; #7699
     fe46059 Add missing ;; in aclocal.m4
     6d67af9 Whitespace only
     4ebcdbe Remove support for the --enable-hc-boot flag in configure
     d227713 Layout only
     ffe795d Hardcode "BootingFromHc = NO" for now
     b8bf9a3 Finish removing BootingFromHc
     09316bc Remove utils/Makefile
     68c6d00 Fix line endings in rts/win32/ThrIOManager.c
     8d1e91a Simplify some code; patch from Bill Tutt
     b46da7c Set repositories to have core.autocrlf == false; fixes #7673
     d362d93 Fix the autocrlf test in sync-all
     cd31b29 Remove the MACOSX_DEPLOYMENT stuff; fixes #7559
     af16aba Remove utils/lndir/Makefile (part of the old build system)
     5858bb3 Update submodules
     e5e8709 Put the main ghc tree last in packages
     eaab794 Update submodules
     1bb3313 Use $(TargetPlatformFull) instead of $(GlobalCrossCompilePrefix)
     29e86f9 Primitive bitwise operations on Int# (Fixes #7689)
     391f287 fix PrimOp dependencies
     dca3a28 declare stable_ptr_table (should fix via-C compilation)
     767663b DPH: free top-level variables don't prevent encapsulation
     5700479 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     99c80a0 fix some dependencies
     a5879a6 Fix segfault in retainer profiling when using multiple cores (#5909)
     7ae0f5b Remove gblock and gunblock
     8a50e63 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     1d7cac7 Add a "deprecated in" pragma
     ffd68b4 Remove printExceptionAndWarnings (deprecated since 7.2)
     f469eff Fix bug in setNumCapabilities
     355002c Better handling of find llvm tools. Use IFS as opposed to more hacky tr approach. This way can handle spaces in paths.
     49f54dc Update submodules
     96e3ae1 Package 'binary' is not a boot package any more
     47235c3 Some -dynamic-too fixes
     e7729b4 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     84742c0 Fix #7710: do not AutoDeriveTypeable for synonyms and type families
     2e010ce Small build system refactoring; no functional changes
     676235f Rename hs-suffix-rules to hs-suffix-way-rules
     eb90651 Rename hs-suffix-rules-srcdir to hs-suffix-way-rules-srcdir
     0565f88 Split non-way-specific variables off from distdir-way-opts into distdir-opts
     f136805 Separate the non-way-specific hs-suffix rules
     807c294 Build fixes following build system refactoring
     96ce0b0 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     41c44e4 Merging master. Untested.
     ffc6e55 Pulling in latest base package
     8e97e68 Updated cabal version
     520432f Updated submodule haskeline
     68d8b2a Updated containers. Fixed typeable story in LwConc's substrate.
     1a3247f Always quote arguments to removeFiles (fixes Windows install).
     1abfa87 Fix displayed string
     8574cd3 More fixes in cmm to adhere to new calling conventions. Added some minor edits to the rts files to get them to compile.
     a019253 Added derived constants. Fixed a bug in PrimOps.
     127f73a Fixed error in Sanity.c merge. Added prototype for createUserLevelThreads in inclues/rts/Threads.h. Fixed a bug in PrimOps.cmm.
     cc29747 Fixed an error in PrimOps.cmm
     a49e9cf Add separate rules for all .hi files, rather than using %.hi style
     e2249ff Make the build system use -dynamic-too if both way v and dyn are being built
     8a6b565 Add another chapter to the hi-rule novel
     02a489e Tweak the sed command so that it works on OSX
     06edacf Turn -dynamic-too off in the build system for now
     27e7261 Fixed the data types of arguments in PrimOps.cmm:Lightweight Concurrency Primitives. Other, minor edits.
     7b98109 Fixes for atomicSwitch argument
     085e814 x86: promote arguments to C functions according to the ABI (#7383)
     5a77d33 Added missing files in base library
     106af14 Retab
     e2bea60 Use unicode quote characters in error messages etc; fixes #2507
     cb34ce9 Fix the compiler plugin example; patch from edsko; fixes #7682
     cdae665 Fix autoconf code to find LLVM tools.
     cabed55 Space edits to scheduler
     ded08e4 Merge branch 'master' into ghc-lwc2
     890f465 Split SettingsCCompilerFlags into non-link and link portions
     20b98f3 Change how unboxed tuples are lexed; fixes #7627
     b7ae3cd Only emit %write_barrier primitive for THREADED_RTS
     c68aac1 Fix parsing of pragmas containing unicode characters; fixes #7671
     9010ab9 Fix a TODO in the compiler
     11bfb4f Update submodule
     0ee3165 Clarify comment
     126de3f Merge branch 'master' into ghc-lwc2
     0839ba5 Renamed Thread-local storage to SCont-local storage



More information about the ghc-commits mailing list