Sun Jan 16 03:20:12 UTC 2011  [email protected]
  * Add warning that GHC.CoreSyn.Expr is based on Appendix C of TLDI'07 paper, 
not the body of the paper.
New patches:

[Add warning that GHC.CoreSyn.Expr is based on Appendix C of TLDI'07 paper, not the body of the paper.
[email protected]**20110116032012
 Ignore-this: c216a9509d901778bb5203855a838b6d
] hunk ./compiler/coreSyn/CoreSyn.lhs 111
 -- | This is the data type that represents GHCs core intermediate language. Currently
 -- GHC uses System FC <http://research.microsoft.com/~simonpj/papers/ext-f/> for this purpose,
 -- which is closely related to the simpler and better known System F <http://en.wikipedia.org/wiki/System_F>.
+-- IMPORTANT NOTE: GHC uses the simplified system described in the post-publication Appendix C of the
+-- paper "System F with Type Equality Coercions", not the more complex system described in the body
+-- of the paper.
 --
 -- We get from Haskell source to this Core language in a number of stages:
 --

Context:

[Fix Trac #4874: specialisation of INLINABLE things
[email protected]**20110114163227
 Ignore-this: b90543117ebddaf3bbeeaf0af0c18699
 
 Johan discovered that when INLINABLE things are specialised
 bad things can happen. This patch implements a hack -- but
 it's a simple hack and it solves the problem.
 
 See Note [Inline specialisations]. 
 
 The hack part is that really INLINABLE should not cause *any* loss
 optimisation, and it does; see Note [Don't w/w INLINABLE things] in
 WorkWrap.
] 
[Comments only
[email protected]**20110114162959
 Ignore-this: f76d4d8f527c3fcd2598ec8cc5fd3049
] 
[Fix a buglet in postInlineUnconditionally
[email protected]**20110114162927
 Ignore-this: 7a7b8610ef863907843d4ae36a8a1a3c
 
 Under obscure circumstances (actually only shown up when fixing something
 else) it was possible for a variable binding to be discarded although
 it was still used.  See Note [Top level and postInlineUnconditionally]
] 
[cope with empty libraries/stamp directory (in git repo)
Simon Marlow <[email protected]>**20110114142406
 Ignore-this: 6e95c44368d784f86a0c1c1d1e24d810
] 
[add .gitignore
Simon Marlow <[email protected]>**20110114142353
 Ignore-this: 23d7cabd2b04eedfe4c33ad94a120474
] 
[Fix longstanding bug in C-- inlining for functions calls.
Edward Z. Yang <[email protected]>**20110113130654
 Ignore-this: 79001003b1f3cc5005207ccfed980c21
] 
[fix for remote repos without -r
Simon Marlow <[email protected]>**20110113131147
 Ignore-this: 3ddd8a4c616cad01a2dbdb500fb54279
] 
[add a version of packages that stores all the repos in git
Simon Marlow <[email protected]>**20110113111733
 Ignore-this: fcca2eb2e753ee20bb5abce7f30f5205
] 
[add the -r flag from darcs-all
Simon Marlow <[email protected]>**20110113111654
 Ignore-this: ada88377bd95ebb9c668dd48954f321e
] 
[Make Template Haskell classInstances function return [ClassInstance]
[email protected]**20110113111421
 Ignore-this: d14381f0a94170965414dd8724188356
 
 This is a recently-introduce function, which was returning
 a [Name], being the names of the dfuns.  But what you really
 want (obviously!) is the ClassInstances, and we have a TH type
 for that.
 
 This is an API change, so don't merge into GHC 7.0.  But it's
 a new part of TH which is still settling down.
 
 Fixes Trac #4863.
] 
[Improve the finder's error messages
[email protected]**20110113111233
 Ignore-this: ec4819b0a44af9fd03dc0a8b8e13699d
 
 I'd done all the work to add fuzzy-match suggestions, but they
 weren't really being used!  Here's what you get now
 
    module Foo where
     import Data.Lst
 
 Foo.hs:3:1:
     Failed to load interface for `Data.Lst'
     Perhaps you meant
       Data.List (from base)
       Data.List (needs flag -package haskell2010-1.0.0.0)
       Data.Int (needs flag -package haskell2010-1.0.0.0)
     Use -v to see a list of the files searched for.
] 
[White space only
[email protected]**20110113093931
 Ignore-this: 4e46acca5241615a3283996052a634a
] 
[Produce an error message, not a crash, for HsOpApp with non-var operator
[email protected]**20110112170719
 Ignore-this: df0f6f2e3318f9c33a714609019b0262
 
 Fixes Trac #4877.
] 
[update to work with current packages file format
Simon Marlow <[email protected]>**20110112160224
 Ignore-this: da73498734aadbfbf0a31389a9dc44d
] 
[In configure, test that GHC generates code for the correct platform (#4819)
Simon Marlow <[email protected]>**20110107163541
 Ignore-this: 29541d3896f9c9bcf791510edae70254
 Patch supplied by the bug reporter, tidied up by me.
 
 $ ./configure --with-ghc=$HOME/fp/bin/i386-unknown-linux/ghc --build=x86_64-unknown-linux
 checking for gfind... no
 checking for find... /usr/bin/find
 checking for sort... /usr/bin/sort
 checking for GHC version date... inferred 7.1.20110107
 checking version of ghc... 7.0.1
 checking build system type... x86_64-unknown-linux-gnu
 checking host system type... x86_64-unknown-linux-gnu
 checking target system type... x86_64-unknown-linux-gnu
 Host platform inferred as: i386-unknown-linux
 Target platform inferred as: i386-unknown-linux
 This GHC (/home/simonmar/fp/bin/i386-unknown-linux/ghc) does not generate code for the build platform
    GHC target platform    : i386-unknown-linux
    Desired build platform : x86_64-unknown-linux
] 
[Major refactoring of the type inference engine
[email protected]**20110112145604
 Ignore-this: 6a7fc90c9b798e89505606726cc8090e
 
 This patch embodies many, many changes to the contraint solver, which
 make it simpler, more robust, and more beautiful.  But it has taken
 me ages to get right. The forcing issue was some obscure programs
 involving recursive dictionaries, but these eventually led to a
 massive refactoring sweep.
 
 Main changes are:
  * No more "frozen errors" in the monad.  Instead "insoluble
    constraints" are now part of the WantedConstraints type.
 
  * The WantedConstraint type is a product of bags, instead of (as
    before) a bag of sums.  This eliminates a good deal of tagging and
    untagging.
 
  * This same WantedConstraints data type is used
      - As the way that constraints are gathered
      - As a field of an implication constraint
      - As both argument and result of solveWanted
      - As the argument to reportUnsolved
 
  * We do not generate any evidence for Derived constraints. They are
    purely there to allow "impovement" by unifying unification
    variables.
 
  * In consequence, nothing is ever *rewritten* by a Derived
    constraint.  This removes, by construction, all the horrible
    potential recursive-dictionary loops that were making us tear our
    hair out.  No more isGoodRecEv search either. Hurrah!
 
  * We add the superclass Derived constraints during canonicalisation,
    after checking for duplicates.  So fewer superclass constraints
    are generated than before.
 
  * Skolem tc-tyvars no longer carry SkolemInfo.  Instead, the
    SkolemInfo lives in the GivenLoc of the Implication, where it
    can be tidied, zonked, and substituted nicely.  This alone is
    a major improvement.
 
  * Tidying is improved, so that we tend to get t1, t2, t3, rather
    than t1, t11, t111, etc
 
    Moreover, unification variables are always printed with a digit
    (thus a0, a1, etc), so that plain 'a' is available for a skolem
    arising from a type signature etc. In this way,
      (a) We quietly say which variables are unification variables,
          for those who know and care
      (b) Types tend to get printed as the user expects.  If he writes
              f :: a -> a
              f = ...blah...
          then types involving 'a' get printed with 'a', rather than
          some tidied variant.
 
  * There are significant improvements in error messages, notably
    in the "Cannot deduce X from Y" messages.
] 
[Fix installation on cygwin
Ian Lynagh <[email protected]>**20110111194838
 Ignore-this: fe923d0619da3bd3a34968106c92fdab
] 
[Do dependency analysis when kind-checking type declarations
[email protected]**20110110110351
 Ignore-this: 17a8dee32694d3e1835cf7bb02d3abb5
 
 This patch fixes Trac #4875.  The main point is to do dependency
 analysis on type and class declarations, and kind-check them in
 dependency order, so as to improve error messages.
 
 This patch means that a few programs that would typecheck before won't
 typecheck any more; but before we were (naughtily) going beyond
 Haskell 98 without any language-extension flags, and Trac #4875
 convinces me that doing so is a Bad Idea.
 
 Here's an example that won't typecheck any more
        data T a b = MkT (a b)
        type F k = T k Maybe
 
 If you look at T on its own you'd default 'a' to kind *->*;
 and then kind-checking would fail on F.
 
 But GHC currently accepts this program beause it looks at
 the *occurrences* of T.
] 
[Move imports around (no change in behaviour)
[email protected]**20110110105647
 Ignore-this: d618cabbc52be7d7968de1e0bdd44082
] 
[Make fuzzy matching a little less eager for short identifiers
[email protected]**20110107102855
 Ignore-this: a753643e88433d74b44a480cc0f4170c
 
 For single-character identifiers we now don't make any suggestions
 See comments in Util.fuzzyLookup
] 
[Fix Trac #4870: get the inlining for an imported INLINABLE Id
[email protected]**20110105002712
 Ignore-this: 60c0192eb48590c2e6868d15ba8f84ce
 
 We need the unfolding even for a *recursive* function (indeed
 that's the point) and I was using the wrong function to get it
 (idUnfolding rather than realIdUnfolding).
] 
[Rejig the includes/ installation rules
Ian Lynagh <[email protected]>**20110109181158
 They're a little nicer now, and a regression in the cygwin build is
 fixed (the $i in the destination wasn't surviving being passed through
 cygpath).
] 
[Make DESTDIR an absolute path when installing; fixes #4883
Ian Lynagh <[email protected]>**20110108171635] 
[Add utils/ghc-cabal/Makefile
Ian Lynagh <[email protected]>**20110108144049] 
[Remove redundant import
Ian Lynagh <[email protected]>**20110108130047
 Ignore-this: 1c7fdec77b48319c845c9593b5fb94af
] 
[Improve error message of :set in ghci (ticket #4190).
Michal Terepeta <[email protected]>**20101130211505
 Ignore-this: ccc8a0816a900ba8c4a966285a465b23
] 
[Improve error message when importing data constructors (ticket #4058).
Michal Terepeta <[email protected]>**20101127211338
 Ignore-this: 3289a08f0391dd90dfef2e0403a04ccd
] 
[catch SIGTSTP and save/restore terminal settings (#4460)
Simon Marlow <[email protected]>**20110107124042
 Ignore-this: 38f7f27bf75178899f466404c048241d
 As far as I can tell, it is the responsibility of the program to save
 and restore its own terminal settings across a suspend/foreground, the
 shell doesn't do it (which seems odd).  So I've added a signal handler
 for SIGTSTP to the RTS which will save and restore the terminal
 settings iff we modified them with hSetBuffering or hSetEcho (we
 already restore them at exit time in these cases).
] 
[comment updates
Simon Marlow <[email protected]>**20110107094236
 Ignore-this: c2b30b0c98645e2847a2749c7fdc167f
] 
[On Cygwin, use a Cygwin-style path for /bin/install's destination
Ian Lynagh <[email protected]>**20110106223030
 
 cygwin's /bin/install doesn't set file modes correctly if the
 destination path is a C: style path:
 
 $ /bin/install -c -m 644 foo /cygdrive/c/cygwin/home/ian/foo2
 $ /bin/install -c -m 644 foo c:/cygwin/home/ian/foo3
 $ ls -l foo*
 -rw-r--r-- 1 ian None 0 2011-01-06 18:28 foo
 -rw-r--r-- 1 ian None 0 2011-01-06 18:29 foo2
 -rwxrwxrwx 1 ian None 0 2011-01-06 18:29 foo3
 
 This causes problems for bindisttest/checkBinaries.sh which then
 thinks that e.g. the userguide HTML files are binaries.
 
 We therefore use a /cygdrive path if we are on cygwin
] 
[Fix mkUserGuidePart program name on Windows
Ian Lynagh <[email protected]>**20110106143707] 
[add comment to remind people to update driver/gcc/gcc.c
Simon Marlow <[email protected]>**20110106152402
 Ignore-this: c07d7ac11eb9221ef821f78aab1807cb
] 
[use Win32 CreateProcess() rather than mingw spawnv() (#4531)
Simon Marlow <[email protected]>**20110106133834
 Ignore-this: 4c0947853549dad034622c044391af6c
] 
[update paths now that we upgraded gcc to 4.5.0
Simon Marlow <[email protected]>**20110106133729
 Ignore-this: f8f9bcad984fdd472e0ae958b66bea9d
] 
[fix markup
Simon Marlow <[email protected]>**20110106093152
 Ignore-this: 555b6e39ae6b5a177b03c5edffc169ab
] 
[fix up multi-line GHCi patch (#4316)
Simon Marlow <[email protected]>**20110105154548
 Ignore-this: 53d5d489bd2a792c01f2cc56a11f3ce6
] 
[multiline commands in GHCi #4316
Vivian McPhail <[email protected]>**20101105051308
 This patch adds support for multiline commands in GHCi.
 
 The first line of input is lexed.  If there is an active
 layout context once the lexer reaches the end of file, the
 user is prompted for more input.
 
 Multiline input is exited by an empty line and can be escaped 
 with a user interrupt.
 
 Multiline mode is toggled with `:set +m`
] 
[Replace a #if with a Haskell conditional
Ian Lynagh <[email protected]>**20110105183011
 Ignore-this: f08f3a4356586efab2725ad8704b2eba
] 
[Whitespace only in X86.Ppr
Ian Lynagh <[email protected]>**20110105171124] 
[Fix error compiling AsmCodeGen.lhs for PPC Mac (unused makeFar addr)
[email protected]**20101219213555
 Ignore-this: ab25d5f2e2ebe163547d5babaf4b1dbf
] 
[Define cTargetArch and start to use it rather than ifdefs
Ian Lynagh <[email protected]>**20110104220013
 Using Haskell conditionals means the compiler sees all the code, so
 there should be less rot of code specific to uncommon arches. Code
 for other platforms should still be optimised away, although if we want
 to support targetting other arches then we'll need to compile it
 for-real anyway.
] 
[Fix error compiling AsmCodeGen.lhs for PPC Mac (rtsPackageId)
[email protected]**20101219212530
 Ignore-this: 946f6d3e0d3c3ddf2dc07b85e1f82d85
] 
[Rename the c*Platform variables to c*PlatformString
Ian Lynagh <[email protected]>**20110104210250] 
[Fix #4829 (build does not respect --with-gcc option)
[email protected]**20101221133233
 Ignore-this: 37918feb82f911c2beb75915b6e8b97b
 
 This patch fixes what seems to be the last problem with the --with-gcc
 option.  On OS X, we need to pass the path to gcc to dtrace as the
 preprocessor.  (Internally, dtrace on OS X sets the default preprocessor
 to /usr/bin/gcc.)  ATM, dtrace is only supported on OS X, so we don't
 need any conditionalization.  If dtrace is ported to other platforms,
 we might need to change this. However, usage on other platforms will
 probably be similar to OS X, since many of Apple's changes are to
 use the gnu toolchain instead of the Sun toolchain.
   
] 
[Drop a seven years old workaround for happy
Matthias Kilian <[email protected]>**20101231192343
 Ignore-this: a9348c91292c113bd967464fbe859f1f
] 
[Add gcc and ld flags to --info output
Ian Lynagh <[email protected]>**20101220173520] 
[Fix Trac #4525: report type errors in terms of the immediate type synonym
[email protected]**20101224082520
 Ignore-this: a3bd076bfe0e1c6f575b106f77f326c6
 
 This small change means that if you have
      type Age = Int
 and you try to unify Age and Bool, you'll get a complaint about
 not matching Age and Bool, rather than Int and Bool.  See the notes
 with Trac #4525
] 
[Comments only
[email protected]**20101224082310
 Ignore-this: 1f69fa3244663b653607093efcdf7b0
] 
[Implement fuzzy matching for the Finder
[email protected]**20101222175400
 Ignore-this: 4dfbbc07bcb59c5f4cee9a902c89d63e
 
 ..so that you get a more helpful message when
 you mis-spell a module name in an 'import'.
 
 Validates, but not fully tested.
 
 Based on Max's patch in Trac #2442, but heavily refactored.
] 
[Implement fuzzy matching for the renamer
[email protected]**20101222175306
 Ignore-this: 66478736249de793a61612f184d484b0
 
 ...so that you get helpful suggestions when you mis-spell a name
 Based on Max's patch in Trac #2442, but heavily refactored.
] 
[Add fuzzyLookup, a variant of fuzzyMatch
[email protected]**20101222175124
 Ignore-this: f0eafaf275b9edffee176f2fb4effe2f
 
 Plus, I changed quite a bit of layout to make the lines shorter.
] 
[White space only
[email protected]**20101222175001
 Ignore-this: ddabada2042f4529e83d1c1ecb052306
] 
[Layout and white space only
[email protected]**20101222174950
 Ignore-this: bf4e4fd9d39714d0461ab799d6b8ed91
] 
[Tidy up rebindable syntax for MDo
[email protected]**20101222132210
 Ignore-this: b40ae8709e5a39d75f2b2813169af215
 
 For a long time an 'mdo' expression has had a SyntaxTable
 attached to it.  However, we're busy deprecating SyntaxTables
 in favour of rebindable syntax attached to individual Stmts,
 and MDoExpr was totally inconsistent with DoExpr in this
 regard.
 
 This patch tidies it all up.  Now there's no SyntaxTable on
 MDoExpr, and 'modo' is generally handled much more like 'do'.
 
 There is resulting small change in behaviour: now MonadFix is
 required only if you actually *use* recursion in mdo. This
 seems consistent with the implicit dependency analysis that
 is done for mdo.
 
 Still to do:
   * Deal with #4148 (this patch is on the way)
   * Get rid of the last remaining SyntaxTable on HsCmdTop
] 
[Make the occurrence analyser track preInlineUnconditionally
[email protected]**20101222131156
 Ignore-this: 82edb06bcca6106327c2cce9d78c4e61
 
 This fixes a somewhat obscure situation in which an
 over-optimistic use of "occurs once" led to an infinite
 sequence of simplifier iterations.  Se Note [Cascading inlines]
 for the details.
 
 This showed up when compiling rather large DPH programs, which
 run lots of iterations of the simplifier, which in turn made
 compilation take much longer than necessary.
] 
[Make mkDFunUnfolding more robust
[email protected]**20101222130854
 Ignore-this: 10bb4168a7080c843f6613043354151b
 
 It now uses tcSplitDFunTy, which is designed for the purpose and
 allows arbitrary argument types to the dfun, rather than
 tcSplitSigmaTy.  This generality is used in DPH, which has
 internally-generated dfuns with impliciation-typed arguments.
 
 To do this I had to make tcSplitDFunTy return the number of
 arguments, so there are some minor knock-on effects in other
 modules.
] 
[Count allocations more accurately
Simon Marlow <[email protected]>**20101221152956
 Ignore-this: 33a4ed3a77bf35f232aa5c9078e8e380
 The allocation stats (+RTS -s etc.) used to count the slop at the end
 of each nursery block (except the last) as allocated space, now we
 count the allocated words accurately.  This should make allocation
 figures more predictable, too.
 
 This has the side effect of reducing the apparent allocations by a
 small amount (~1%), so remember to take this into account when looking
 at nofib results.
] 
[Add a simple arity analyser
[email protected]**20101221165800
 Ignore-this: d5f3a9f56404d61bb7f374c875b42c49
 
 I've wanted to do this for ages, but never gotten around to
 it.  The main notes are in Note [Arity analysis] in SimplUtils.
 
 The motivating example for arity analysis is this:
 
   f = \x. let g = f (x+1)
           in \y. ...g...
 
 What arity does f have?  Really it should have arity 2, but a naive
 look at the RHS won't see that.  You need a fixpoint analysis which
 says it has arity "infinity" the first time round.
 
 This makes things more robust to the way in which you write code.  For
 example, see Trac #4474 which is fixed by this change.
 
 Not a huge difference, but worth while:
 
         Program           Size    Allocs   Runtime   Elapsed
 --------------------------------------------------------------------------------
             Min          -0.4%     -2.2%    -10.0%    -10.0%
             Max          +2.7%     +0.3%     +7.1%     +6.9%
  Geometric Mean          -0.3%     -0.2%     -2.1%     -2.2%
 
 I don't really believe the runtime numbers, because the machine was
 busy, but the bottom line is that not much changes, and what does
 change reliably (allocation and size) is in the right direction.
] 
[Miscellaneous tidying up and refactoring
[email protected]**20101221161931
 Ignore-this: 7706d3065e6fc1defafe1cb8975b9969
] 
[Comments only
[email protected]**20101221161918
 Ignore-this: 3e269a62da5cbec72d3e4b8328689628
] 
[Single-method classes are implemented with a newtype
[email protected]**20101221161911
 Ignore-this: 4ca00f0b367fbeb8146146bc53116eb7
 
 This patch changes things so that such classes rely on the coercion
 mechanism for inlining (since the constructor is really just a cast)
 rather than on the dfun mechanism, therby removing some needless
 runtime indirections.
] 
[For single-method classes use newtypes
[email protected]**20101101080736
 Ignore-this: d3851f92eb2385501411da57066b775e
 
 This clears up an awkward hack for exprIsConApp_maybe, and
 works better too.  See Note [Single-method classes] in
 TcInstDcls.
] 
[boundTaskExiting: don't set task->stopped unless this is the last call (#4850)
Simon Marlow <[email protected]>**20101221115807
 Ignore-this: 7e1b990aa08b3ea9cdaa9385d8e41e48
 The bug in this case was that we had a worker thread making a foreign
 call which invoked a callback (in this case it was performGC, I
 think).  When the callback ended, boundTaskExiting() was setting
 task->stopped, but the Task is now per-OS-thread, so it is shared by
 the worker that made the original foreign call.  When the foreign call
 returned, because task->stopped was set, the worker was not placed on
 the queue of spare workers.  Somehow the worker woke up again, and
 found the spare_workers queue empty, which lead to a crash.
 
 Two bugs here: task->stopped should not have been set by
 boundTaskExiting (this broke when I split the Task and InCall structs,
 in 6.12.2), and releaseCapabilityAndQueueWorker() should not be
 testing task->stopped anyway, because it should only ever be called
 when task->stopped is false (this is now an assertion).
] 
[releaseCapabilityAndQueueWorker: task->stopped should be false (#4850)
Simon Marlow <[email protected]>**20101221114911
 Ignore-this: b9c430a4bc9d2e0c7f4140d6d6971eae
] 
[Fix Windows build
Simon Marlow <[email protected]>**20101221102101
 Ignore-this: f4773e06d030a335c9ac721af193b8d2
] 
[raiseExceptionHelper: update tso->stackobj->sp before calling threadStackOverflow (#4845)
Simon Marlow <[email protected]>**20101221101411
 Ignore-this: 48495131fcc8c548882a470c2509f9f5
] 
[add 'make re2' for rebuilding stage2 (similarly re1 and re3)
Simon Marlow <[email protected]>**20101221100254
 Ignore-this: 5c0afe3810b66a5b6e53a3a0fe933945
] 
[fix warning
Simon Marlow <[email protected]>**20101216160415
 Ignore-this: 54a0eedfa5b7fc15c31dffffb1b10aad
] 
[Small improvement to CorePrep
[email protected]**20101220123715
 Ignore-this: d0490225ed1895a1a5b97d786ed44260
 
 This change avoids unnecessary bindings. Example
 
      foo (let fn = \x.blah in
           in fn)
 
 We were generating something stupid like
 
     let fn = \x.blah in
     let fn' = \eta. fn eta
     in foo fn
 
 Now we don't.  The change is quite small.
 
 Thanks to Ben for showing me an example of this happening.
] 
[Fix warnings
Ian Lynagh <[email protected]>**20101219202711
 Ignore-this: 898015b086f684de5371bf97a23b9e2e
] 
[Small refactoring
Ian Lynagh <[email protected]>**20101219194032] 
[Drop GhcWithLlvmCodeGen configuration bits
Matthias Kilian <[email protected]>**20101219180239
 Ignore-this: 815ed46be7650792f85807c232edfcc
 The LLVM code generator is always built unconditionally, so both the
 configuration variable in mk/config.mk.in as well as the string in
 compilerInfo can be removed.
] 
[Pass --hoogle to haddock; fixes trac #4521
Ian Lynagh <[email protected]>**20101219125243] 
[vectoriser: don't always pass superclass dictionaries to PA dfuns
Roman Leshchinskiy <[email protected]>**20101218234838
 Ignore-this: 77c71976db8fc63aeb83f4abdba994d8
 
 This is just a guess at how this should work.
] 
[vectoriser: delete dead code
Roman Leshchinskiy <[email protected]>**20101218125350
 Ignore-this: 437eea71ad15ad5dc7902e596597c577
] 
[vectoriser: adapt to new superclass story part I (dictionary construction)
Roman Leshchinskiy <[email protected]>**20101218114953
 Ignore-this: 29c9aa46a1622beaae1dcefc4c482a30
] 
[Replace uses of the old try function with the new one
Ian Lynagh <[email protected]>**20101218230827
 Ignore-this: 5dd6c1a4142405aa1aab3fc4ec07eea6
] 
[Replace uses of the old catch function with the new one
Ian Lynagh <[email protected]>**20101218213350] 
[Create ~/.ghc/ if it doesn't already exist; fixes trac #4522
Ian Lynagh <[email protected]>**20101218184925] 
[Document GADTSyntax extension
Ian Lynagh <[email protected]>**20101218150121] 
[Implement GADTSyntax extension
Ian Lynagh <[email protected]>**20101218144550] 
[Whitespace-only in rts/Linker.c
Ian Lynagh <[email protected]>**20101217234124] 
[Add some casts to fix warnings; patch from Greg Wright
Ian Lynagh <[email protected]>**20101217223811] 
[Put an up-to-date Makefile in docs/Makefile
Ian Lynagh <[email protected]>**20101217223707
 It doesn't do anything useful yet, but it works with the new build system
] 
[do not compile part of shared lib RTS with -fno-PIC on Solaris
Karel Gardas <[email protected]>**20101217085133
 Ignore-this: 8c8dbb45cac0578a58a3557f1e03c66
] 
[provide shared libraries support on i386-unknown-solaris2 platform
Karel Gardas <[email protected]>**20101217084617
 Ignore-this: b6079c6a39a71200a1ee863573e40828
] 
[fix CPP detection of Solaris in NCG
Karel Gardas <[email protected]>**20101217084510
 Ignore-this: 9d1ce59d469294eab1f0cbc697e48d69
] 
[Fix checkBinaries on OS X
Ian Lynagh <[email protected]>**20101216201121] 
[Remove redundant HpcMap and HpcSet wrappers around Data.{Map,Set}
Ian Lynagh <[email protected]>**20101216190605] 
[Use "-perm -u+x" rather than "-executable" to find executables
Ian Lynagh <[email protected]>**20101216145235
 On Windows, -executable is matching the html docs.
] 
[Remove a debugging print
Ian Lynagh <[email protected]>**20101216011459] 
[__GLASGOW_HASKELL__ >= 604 is now always true
Ian Lynagh <[email protected]>**20101215214656] 
[Remove more dead code now we require GHC >= 6.12
Ian Lynagh <[email protected]>**20101215213715] 
[refactor and tidy up the section on RTS options
Simon Marlow <[email protected]>**20101216123151
 Ignore-this: 9cdafd687351d8a3ff879b64347f85d3
] 
[Related to #4826: Some minor tweaks to the wording of the User Guide, section 4.16
Orphi <[email protected]>**20101209170440
 Ignore-this: c3d942d58594be7d4c2eb4dc3a22f19
] 
[FIX #4826 partial: Add -rtsopts and -with-rtsopts to User Guide section 4.11.6
Orphi <[email protected]>**20101209165152
 Ignore-this: 2fc1c0abbb783695773ab0f9c013bbaa
] 
[FIX #4826 partially: Change -f to -? in User Guide section F4.16
Orphi <[email protected]>**20101209144148
 Ignore-this: 73410b350e80c8943ae722dec8dea44b
] 
[fix #3910
Simon Marlow <[email protected]>**20101216114452
 Ignore-this: 410e95e188344a523520e192a3fb58ea
] 
[remove an optimisation that wasn't
Simon Marlow <[email protected]>**20101215152656
 Ignore-this: e8413f58e8292c6e7463087d885b3a7d
] 
[fix a warning
Simon Marlow <[email protected]>**20101216105723
 Ignore-this: ed6024378021a698ce638267ed3e21ab
] 
[use EXTERN_INLINE instead of STATIC_INLINE to avoid some gcc warnings
Simon Marlow <[email protected]>**20101216105709
 Ignore-this: d4e1586cf318883a8e611b55df7fbf10
] 
[remove dead code
Simon Marlow <[email protected]>**20101216104944
 Ignore-this: 97a04a3e37c1b28abc222a28bab3d17d
] 
[fix retainer profiling: add missing case for TSO
Simon Marlow <[email protected]>**20101216103900
 Ignore-this: 11bda81ac159f638d719c1f6177702fb
] 
[add a missing STACK case
Simon Marlow <[email protected]>**20101216102100
 Ignore-this: ac1c036b5cbf4209b1d10b6ab1c83f27
] 
[Remove code that is dead now that we need >= 6.12 to build
Ian Lynagh <[email protected]>**20101215201006] 
[fix for large stack allocations
Simon Marlow <[email protected]>**20101215152419
 Ignore-this: d9aca17d68bd99214c126989a2318e79
] 
[Implement stack chunks and separate TSO/STACK objects
Simon Marlow <[email protected]>**20101215120843
 Ignore-this: 73fa9460314d4a4e54456af12bef7960
 
 This patch makes two changes to the way stacks are managed:
 
 1. The stack is now stored in a separate object from the TSO.
 
 This means that it is easier to replace the stack object for a thread
 when the stack overflows or underflows; we don't have to leave behind
 the old TSO as an indirection any more.  Consequently, we can remove
 ThreadRelocated and deRefTSO(), which were a pain.
 
 This is obviously the right thing, but the last time I tried to do it
 it made performance worse.  This time I seem to have cracked it.
 
 2. Stacks are now represented as a chain of chunks, rather than
    a single monolithic object.
 
 The big advantage here is that individual chunks are marked clean or
 dirty according to whether they contain pointers to the young
 generation, and the GC can avoid traversing clean stack chunks during
 a young-generation collection.  This means that programs with deep
 stacks will see a big saving in GC overhead when using the default GC
 settings.
 
 A secondary advantage is that there is much less copying involved as
 the stack grows.  Programs that quickly grow a deep stack will see big
 improvements.
 
 In some ways the implementation is simpler, as nothing special needs
 to be done to reclaim stack as the stack shrinks (the GC just recovers
 the dead stack chunks).  On the other hand, we have to manage stack
 underflow between chunks, so there's a new stack frame
 (UNDERFLOW_FRAME), and we now have separate TSO and STACK objects.
 The total amount of code is probably about the same as before.
 
 There are new RTS flags:
 
    -ki<size> Sets the initial thread stack size (default 1k)  Egs: -ki4k -ki2m
    -kc<size> Sets the stack chunk size (default 32k)
    -kb<size> Sets the stack chunk buffer size (default 1k)
 
 -ki was previously called just -k, and the old name is still accepted
 for backwards compatibility.  These new options are documented.
] 
[comments on SRC_HC_OPTS (#4829)
Simon Marlow <[email protected]>**20101214101340
 Ignore-this: e2bdec00f07b68e82837e77a4faf6514
] 
[fix another sanity error, and refactor/tidy up
Simon Marlow <[email protected]>**20101209163919
 Ignore-this: d5ce953ac78e90fc0e22cd9848d26e2e
] 
[Fix a bug in functorLikeTraverse, which was giving wrong answer for tuples
[email protected]**20101215123725
 Ignore-this: 560220e92429b5b1a6197a62f94a4ff2
 
 This bug led to Trac #4816, which is hereby fixed
] 
[Improve printing for -ddump-deriv
[email protected]**20101215121955
 Ignore-this: 3181c948c4c2471bd99b32c5ee487a1e
] 
[Tighten up what it means to be an "enumeration data constructor"
[email protected]**20101215121927
 Ignore-this: 459b3f9f7994a13094ed87b0768b33a8
 
 See Note [Enumeration types] in TyCon, and comments in Trac #4528
] 
[Allow enumerations to have phantom arguments.
[email protected]**20101215121817
 Ignore-this: 32ef8cb869e6e38c2e43b3ae87b1b9a8
 
 The bytecode generator was being too eager.
 Fixes Trac #4528, or rather, a near variant.
] 
[Instance declaration overlap allowed if *either* has -XOverlappingInstances
[email protected]**20101214180500
 Ignore-this: f1b1492541a7e0464ebc6adb45510a2e
 
 This satisfies Trac #3877.  Documentation is changed too.
 I'm not sure if this should go in 7.0.2.
] 
[Fix Trac #4841: behave right with TypeSynonymInstances and NoFlexibleInstances
[email protected]**20101214174755
 Ignore-this: dccd707fdca84904b7885170a296ecb6
 
 When we have TypeSynonymInstances without FlexibleInstances we should still
 insist on a H98-style instance head, after looking through the synonym.
 
 This patch also make FlexibleInstances imply TypeSynonymInstances.  Anything
 else is a bit awkward, and not very useful.
 
] 
[Fix Trac #3731: more superclass subtlety (sigh)
[email protected]**20101214180344
 Ignore-this: f4168e59f3164303ba7be022ba19c37b
 
 I will add more comments, but I want to commit this tonight,
 so the overnight builds get it.
] 
[Less verbose debug print
[email protected]**20101214180248
 Ignore-this: e405e8545763e913155abe43daf7e36c
] 
[Wibble to InstEnv.instanceHead
[email protected]**20101214082939
 Ignore-this: 851db517f8638a0aeb7ad461298f7e9f
 
 Fixes an accidental glitch in T1835
] 
[Remove dead code now that we require the bootstrapping compiler be >= 6.12
Ian Lynagh <[email protected]>**20101214011011] 
[GHC 6.12 is now needed to build the HEAD
Ian Lynagh <[email protected]>**20101214010923] 
[Add libstdc++-4.5.0-1-mingw32-dll-6.tar.lzma to mingw tarballs
Ian Lynagh <[email protected]>**20101213223153] 
[Fix recursive superclasses (again).  Fixes Trac #4809.
[email protected]**20101213171511
 Ignore-this: b91651397918fd8f0183812f9a070073
 
 This patch finally deals with the super-delicate question of
 superclases in possibly-recursive dictionaries.  The key idea
 is the DFun Superclass Invariant (see TcInstDcls):
 
      In the body of a DFun, every superclass argument to the
      returned dictionary is
        either   * one of the arguments of the DFun,
        or       * constant, bound at top level
 
 To establish the invariant, we add new "silent" superclass
 argument(s) to each dfun, so that the dfun does not do superclass
 selection internally.  There's a bit of hoo-ha to make sure that
 we don't print those silent arguments in error messages; a knock
 on effect was a change in interface-file format.
 
 A second change is that instead of the complex and fragile
 "self dictionary binding" in TcInstDcls and TcClassDcl,
 using the same mechanism for existential pattern bindings.
 See Note [Subtle interaction of recursion and overlap] in TcInstDcls
 and Note [Binding when looking up instances] in InstEnv.
 
 Main notes are here:
 
   * Note [Silent Superclass Arguments] in TcInstDcls,
     including the DFun Superclass Invariant
 
 Main code changes are:
 
   * The code for MkId.mkDictFunId and mkDictFunTy
 
   * DFunUnfoldings get a little more complicated;
     their arguments are a new type DFunArg (in CoreSyn)
 
   * No "self" argument in tcInstanceMethod
   * No special tcSimplifySuperClasss
   * No "dependents" argument to EvDFunApp
 
 IMPORTANT
    It turns out that it's quite tricky to generate the right
    DFunUnfolding for a specialised dfun, when you use SPECIALISE
    INSTANCE.  For now I've just commented it out (in DsBinds) but
    that'll lose some optimisation, and I need to get back to
    this.
] 
[Doing the smart canonicalization only if we are not simplifying a Rule LHS.
[email protected]**20101210132221
 Also, same thing now applies for adding superclasses.
 
] 
[Moved canonicalisation inside solveInteract
[email protected]**20101209141215
 
 Moreover canonicalisation now is "clever", i.e. it never canonicalizes a class 
 constraint if it can already discharge it from some other inert or previously
 encountered constraints. See Note [Avoiding the superclass explosion]
 
] 
[GHCi linker: Assume non-Haskell libraries are dynamic libs
Ian Lynagh <[email protected]>**20101213124930
 Ignore-this: aa153a8f6e309c7b3dae7e46bb7a9583
 This works around a segfault we get when trying to load libiconv.a on
 some platforms.
] 
[Add --version support to ghc-cabal
Ian Lynagh <[email protected]>**20101212213600
 Ignore-this: ef696dcb1b96a23765f9f18e75a56f5
] 
[Don't link the GHC RTS into our C-only programs
Ian Lynagh <[email protected]>**20101210185402
 Ignore-this: 56f620f7eb16a03e7497a161bc48458e
] 
[Build a copy of ghc-cabal with the in-tree compiler, for the bindist
Ian Lynagh <[email protected]>**20101210181123] 
[Add a test that all programs in the bindist were built with the right GHC
Ian Lynagh <[email protected]>**20101210161218
 They should use the GHC from the build tree, not the bootstrapping compiler.
] 
[Fix Trac #4534: renamer bug
[email protected]**20101210084530
 Ignore-this: 8163bfa3a56344cfe89ad17c62e9655d
   
 The renamer wasn't attaching the right used-variables to a
 TransformStmt constructor.
 
 The real modification is in RnExpr; the rest is just
 pretty-printing and white space.
] 
[White space only
[email protected]**20101210084255
 Ignore-this: 3fcf8a4fc8c15052c379a135951d53ea
] 
[Comments only
[email protected]**20101210084116
 Ignore-this: 55bb1de129b1c9513751885eaa84b884
] 
[Make the case-to-let transformation a little less eager
[email protected]**20101208172251
 Ignore-this: 55eaa1b5753af31aeb32ec792cb6b662
 
 See Note [Case elimination: lifted case].
 Thanks to Roman for identifying this case.
] 
[warning fix: don't redefine BLOCKS_PER_MBLOCK
Simon Marlow <[email protected]>**20101210094002
 Ignore-this: cadba57f1c38f5e2af1de37d0a79c7ee
] 
[Only reset the event log if logging is turned on (addendum to #4512)
Simon Marlow <[email protected]>**20101210093951
 Ignore-this: c9f85f0de2b11a37337672fba59aecc6
] 
[allocate enough room for the longer filename (addendum to #4512)
Simon Marlow <[email protected]>**20101210093906
 Ignore-this: 270dc0219d98f1e0f9e006102ade7087
] 
[Fix Windows build: move rtsTimerSignal to the POSIX-only section
Simon Marlow <[email protected]>**20101210090045
 Ignore-this: aa1844b70b9f1a44447787c4bbe10d44
] 
[Default the value of -dppr-cols when the static flags aren't initialised yet
Ben Lippmeier <[email protected]>**20101210060154
 Ignore-this: 4cea29085ef904f379a8829714c9e180
 If GHC's command line options are bad then the options parser uses the
 pretty printer before the -dppr-cols flag has been read.
] 
[Defensify naked read in LLVM mangler
Ben Lippmeier <[email protected]>**20101210045922
 Ignore-this: 1373f597863851bd03e7a7254558ed04
] 
[Formatting only
Ben Lippmeier <[email protected]>**20101210042600
 Ignore-this: 20bbcd95c70b59094d0bb8a63e459103
] 
[Always ppr case alts on separate lines
Ben Lippmeier <[email protected]>**20101208070508
 Ignore-this: 7e2edd57a61427621aeb254aef84f0f7
] 
[Add -dppr-colsN to set width of dumps
Ben Lippmeier <[email protected]>**20101208070245
 Ignore-this: edc64fee6c373b895bb80b83b549ce1a
] 
[Add -dppr-case-as-let to print "strict lets" as actual lets
Ben Lippmeier <[email protected]>**20101208065548
 Ignore-this: eb1d122dbd73b5263cae3a9f8259a838
] 
[Suppress more info with -dsuppress-idinfo
Ben Lippmeier <[email protected]>**20101208063037
 Ignore-this: 5e8213d7b8d2905e245917aa3e83efc5
] 
[Implement -dsuppress-type-signatures
Ben Lippmeier <[email protected]>**20101208062814
 Ignore-this: 34dbefe5f8d7fe58ecb26d6a748d1c71
] 
[Add more suppression flags
Ben Lippmeier <[email protected]>**20101208020723
 Ignore-this: b010ba9789a2fde6b815f33494fcc23c
  -dsuppress-all
  -dsuppress-type-applications
  -dsuppress-idinfo
] 
[fix ticket number (#4505)
Simon Marlow <[email protected]>**20101209120404
 Ignore-this: 5769c5ce2a8d69d62d977a9ae138ec23
] 
[fix warnings
Simon Marlow <[email protected]>**20101209115844
 Ignore-this: ffff37feb2abbfc5bd12940c7007c208
] 
[Catch too-large allocations and emit an error message (#4505)
Simon Marlow <[email protected]>**20101209114005
 Ignore-this: c9013ab63dd0bd62ea045060528550c6
 
 This is a temporary measure until we fix the bug properly (which is
 somewhat tricky, and we think might be easier in the new code
 generator).
 
 For now we get:
 
 ghc-stage2: sorry! (unimplemented feature or known bug)
   (GHC version 7.1 for i386-unknown-linux):
         Trying to allocate more than 1040384 bytes.
 
 See: http://hackage.haskell.org/trac/ghc/ticket/4550
 Suggestion: read data from a file instead of having large static data
 structures in the code.
] 
[Export the value of the signal used by scheduler (#4504)
Dmitry Astapov <[email protected]>**20101208183755
 Ignore-this: 427bf8c2469283fc7a6f759440d07d87
] 
[Tweak the "sorry" message a bit
Simon Marlow <[email protected]>**20101208163212
 Ignore-this: aa1ce5bc3c27111548204b740572efbe
 
 -		"sorry! (this is work in progress)\n"
 +		"sorry! (unimplemented feature or known bug)\n"
] 
[:unset settings support
Boris Lykah <[email protected]>**20101123190132
 Ignore-this: 5e97c99238f5d2394592858c34c004d
 Added support for settings [args, prog, prompt, editor and stop].
 Now :unset supports the same set of options as :set.
] 
[Fix Windows memory freeing: add a check for fb == NULL; fixes trac #4506
Ian Lynagh <[email protected]>**20101208152349
 Also added a few comments, and a load of code got indented 1 level deeper.
] 
[Fixes for #4512: EventLog.c - provides ability to terminate event logging, Schedule.c - uses them in forkProcess.
Dmitry Astapov <[email protected]>**20101203133950
 Ignore-this: 2da7f215d6c22708a18291a416ba8881
] 
[Make CPPFLAGS variables, as well as CFLAGS and LDFLAGS
Ian Lynagh <[email protected]>**20101207010033
 Ignore-this: 2fc1ca1422aae1988d0fe1d29a8485d9
 This fixes the "does unsetenv return void" test in the unix package on
 OS X, if I tell it to make 10.4-compatible binaries. The test uses
 CPPFLAGS but not CFLAGS, so it thought it returned int (as it was
 in 10.5-mode), but the C compiler (using CFLAGS, so in 10.4 mode)
 thought it returned void.
 
 I also added CONF_LD_OPTS_STAGE$3 to the list of things in LDFLAGS,
 which looks like an accidental ommission.
] 
[Add a configure message
Ian Lynagh <[email protected]>**20101206215201] 
[Link even programs containing no Haskell modules with GHC
Ian Lynagh <[email protected]>**20101206203329
 I don't remember why we made it use gcc instead, but going back to
 using ghc doesn't seem to break anything, and should fix the build
 on OS X 10.6.
] 
[Correct the stage that the includes/ tools are built in
Ian Lynagh <[email protected]>**20101206203125] 
[Tweak the cleaning of inplace/; fixes trac #4320
Ian Lynagh <[email protected]>**20101205212048] 
[Close .ghci files after reading them; fixes trac #4487
Ian Lynagh <[email protected]>**20101205205301] 
[Fix the behaviour of :history for ticks surrounding top level functions
[email protected]**20101203202346
 Ignore-this: 8059d4859c52c0c9a235b937cb8cde1d
] 
[Don't warn of duplicate exports in case of module exports.
Michal Terepeta <[email protected]>**20101127212116
 Ignore-this: ea225d517826f971c400bbb68d1405b8
 
 But only when the module exports refer to different modules.
 See ticket #4478.
] 
[Fix whitespace/layout in RnNames.
Michal Terepeta <[email protected]>**20101030171303
 Ignore-this: 707a7955fc4fc51683cc5a1dfe57f93
] 
[Tell gcc to support back to OS X 10.5
Ian Lynagh <[email protected]>**20101203201558
 Ignore-this: f02d70e5b9cce50137981c6cb2b62a18
] 
[Make RelaxedLayout off by default
Ian Lynagh <[email protected]>**20101202140808
 I suspect this is a vary rarely used extension to the official layout
 rule.
] 
[Fix up TcInstDcls
[email protected]**20101203180758
 Ignore-this: 9311aeb4ee67c799704afec90b5982d0
 
 I really don't know how this module got left out of my last
 patch, namely
   Thu Dec  2 12:35:47 GMT 2010  [email protected]
   * Re-jig simplifySuperClass (again)
 
 I suggest you don't pull either the patch above, or this
 one, unless you really have to.  I'm not fully confident
 that it works properly yet.  Ran out of time. Sigh.
] 
[throwTo: report the why_blocked value in the barf()
Simon Marlow <[email protected]>**20101203094840
 Ignore-this: 3b167c581be1c51dfe3586cc6359e1d0
] 
[handle ThreadMigrating in throwTo() (#4811)
Simon Marlow <[email protected]>**20101203094818
 Ignore-this: 8ef8cb7fd3b50a27f83c29968131d461
 If a throwTo targets a thread that has just been created with
 forkOnIO, then it is possible the exception strikes while the thread
 is still in the process of migrating.  throwTo() didn't handle this
 case, but it's fairly straightforward.
] 
[removeThreadFromQueue: stub out the link field before returning (#4813)
Simon Marlow <[email protected]>**20101202160838
 Ignore-this: 653ae17bc1120d7f4130da94665002a1
] 
[small tidyup
Simon Marlow <[email protected]>**20101126140620
 Ignore-this: 70b1d5ed4c81a7b29dd5980a2d84aae1
] 
[Fix a recomp bug: make classes/datatypes depend directly on DFuns (#4469)
Simon Marlow <[email protected]>**20101202122349
 Ignore-this: 61c765583bb1d97caa88cf9b4f45b87c
 And remove the old mechanism of recording dfun uses separately,
 because it didn't work.
 
 This wiki page describes recompilation avoidance and fingerprinting.
 I'll update it to describe the new method and what went wrong with the
 old method:
 
 http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/RecompilationAvoidance
] 
[make a panic message more informative and suggest -dcore-lint (see #4534)
Simon Marlow <[email protected]>**20101201151706
 Ignore-this: 2a10761925d6f9f52675948baa30f7a
] 
[Re-jig simplifySuperClass (again)
[email protected]**20101202123547
 Ignore-this: fe4062b8988258f6748ebd8fbd6515b5
 
 This fixes the current loop in T3731, and will fix other
 reported loops.  The loops show up when we are generating
 evidence for superclasses in an instance declaration.
 
 The trick is to make the "self" dictionary simplifySuperClass
 depend *explicitly* on the superclass we are currently trying
 to build.  See Note [Dependencies in self dictionaries] in TcSimplify.
 
 That in turn means that EvDFunApp needs a dependency-list, used
 when chasing dependencies in isGoodRecEv.
] 
[A little refactoring (remove redundant argument passed to isGoodRecEv)
[email protected]**20101202123110
 Ignore-this: e517c5c12109a230f08dafb4d1e386df
] 
[Make rebindable if-then-else a little more permissive
[email protected]**20101202122540
 Ignore-this: ddb552cfe307607b42d1e4baf4e3bf21
 
 See Note [Rebindable syntax for if].  Fixes Trac #4798.
 Thanks to Nils Schweinsberg <[email protected]>
] 
[Improve error message (Trac #4799)
[email protected]**20101202102706
 Ignore-this: d9896e4d182936de1f256c820b96a8cf
] 
[Fix a nasty bug in RULE matching: Trac #4814
[email protected]**20101202102618
 Ignore-this: ba058ad46a02bd2faf3a14de93fd19c6
 
 See Note [Matching lets], which explains it all in detail.
 It took me a day to think of a nice way to fix the bug,
 but I think the result is quite respectable. Subtle, though.
] 
[Rename -XPArr to -XParallelArrays
Ben Lippmeier <[email protected]>**20101130075415
 Ignore-this: 21b37680a7f25800d1200b59ad0b6b39
] 
[FIX #1845 (unconditional relative branch out of range)
[email protected]**20101130143014
 Ignore-this: df234bd8ad937104c455656fe3c33732
 
 Don't use mmap on powerpc-apple-darwin as mmap doesn't support
 reallocating but we need to allocate jump islands just after each
 object images. Otherwise relative branches to jump islands can fail
 due to 24-bits displacement overflow.
] 
[rts/Linker.c (loadArchive):
[email protected]**20101130142700
 Ignore-this: bc84f9369ce5c2d289440701b7a3a2ab
 
 This routine should be aware of Mach-O misalignment of malloc'ed memory regions.
] 
[rts/Linker.c (machoGetMisalignment):
[email protected]**20101130123355
 Ignore-this: 75425600049efd587e9873578e26392f
 
 Use fseek(3) instead of rewind(3) to move the file position indicator back to the initial position. Otherwise we can't use this function in loadArchive().
] 
[rts/Linker.c (ocFlushInstructionCache):
[email protected]**20101130121425
 Ignore-this: 1e2c207e4b1d17387617ec5d645204b7
 
 I found this function causes a segfault when ocAllocateSymbolExtras() has allocated a separate memory region for jump islands.
] 
[Remove NewQualifiedOperators
Ian Lynagh <[email protected]>**20101201181117
 The extension was rejected by Haskell', and deprecated in 7.0.
] 
[fix ref to utils/ext-core, which moved to Hackage (extcore package)
Simon Marlow <[email protected]>**20101201092147
 Ignore-this: 272a7daaa335ef60bcc645db70b4d68b
] 
[fix floating-point/FFI section: fenv is C99, not POSIX
Simon Marlow <[email protected]>**20101201092119
 Ignore-this: ce8b3edd428e4f77691dd739b5b4ae73
] 
[Fixed some 'unused vars' warnings
[email protected]**20101130013425
 Ignore-this: 35790d443faa23b87e4ba442e62376a3
] 
[vectScalarLam handles int, float, and double now
[email protected]**20101129231043
 Ignore-this: 6d67bdc8dd8577184040e791e6f3d0
] 
[Handling of lets, letrec and case when checking if a lambda expr needs to be vectorised
[email protected]**20101115051225
 Ignore-this: 1db6ed63d7b3f6d093e019322b407ff7
] 
[Document the behaviour of fenv.h functions with GHC (#4391)
Simon Marlow <[email protected]>**20101126125336
 Ignore-this: bc4eab49428d567505a28add6fed90f1
] 
[Remove the no-ghci-lib warning in ghc-pkg
Ian Lynagh <[email protected]>**20101127235805
 GHCi libs are no longer necessary, as we can use the .a or .so versions
 instead.
] 
[Add GNU-variant support to the .a parser, and other improvements/tidyups
Ian Lynagh <[email protected]>**20101127223945] 
[Re-indent only
Ian Lynagh <[email protected]>**20101127191646] 
[Improve linker debugging for archive files
Ian Lynagh <[email protected]>**20101127190907] 
[Always enable the archive-loading code
Ian Lynagh <[email protected]>**20101127173000
 If the GHCi .o lib doesn't exist, load the .a instead
] 
[Inherit the ForceSpecConstr flag in non-recursive nested bindings
Roman Leshchinskiy <[email protected]>**20101127125025
 Ignore-this: 401391eae25cefcb4afaba2e357decc1
 
 This makes sure that join points are fully specialised in loops which are
 marked as ForceSpecConstr.
] 
[Document -ddump-rule-firings and -ddump-rule-rewrites
Roman Leshchinskiy <[email protected]>**20101127123528
 Ignore-this: beade2efe0cd767c0ce9d4f45a3380ba
] 
[New flag -dddump-rule-rewrites
Roman Leshchinskiy <[email protected]>**20101127122022
 Ignore-this: c0ef5b8a199fbd1ef020258d2cde85a3
 
 Now, -ddump-rule-firings only shows the names of the rules that fired (it would
 show "before" and "after" with -dverbose-core2core previously) and
 -ddump-rule-rewrites always shows the "before" and "after" bits, even without
 -dverbose-core2core.
] 
[Acutally, wild-card variables *can* have occurrences
[email protected]**20101126162409
 Ignore-this: 544bffed75eeccef03a1097f98524eea
 
 This patch removes the Lint test, and comments why
] 
[Tidy up the handling of wild-card binders, and make Lint check it
[email protected]**20101126133210
 Ignore-this: 9e0be9f7867d53046ee5b0e478a0f433
 
 See Note [WildCard binders] in SimplEnv.  Spotted by Roman.
] 
[Substitution should just substitute, not optimise
[email protected]**20101125172356
 Ignore-this: 657628d9b6796ceb5f915c43d56e4a06
 
 This was causing Trac #4524, by optimising
      (e |> co)  to   e
 on the LHS of a rule.  Result, the template variable
 'co' wasn't bound any more.
 
 Now that substition doesn't optimise, it seems sensible to call
 simpleOptExpr rather than substExpr when substituting in the
 RHS of rules.  Not a big deal either way.
] 
[Make SpecConstr "look through" identity coercions
[email protected]**20101125172138
 Ignore-this: c1cc585ed890a7702c33987e971e0af6
] 
[Comment only
[email protected]**20101125172011
 Ignore-this: 3c7be8791badd00dcca9610ebb8981d1
] 
[White space only
[email protected]**20101101080748
 Ignore-this: f7133fc6b22ae263c6672543a8534a6f
] 
[Keep a maximum of 6 spare worker threads per Capability (#4262)
Simon Marlow <[email protected]>**20101125135729
 Ignore-this: a020786569656bf2f3a1717b65d463bd
] 
[Unicide OtherNumber category should be allowed in identifiers (#4373)
Simon Marlow <[email protected]>**20101115095444
 Ignore-this: e331b6ddb17550163ee91bd283348800
] 
[vectoriser: fix warning
Ben Lippmeier <[email protected]>**20101126044036
 Ignore-this: e1a66bb405bf2f3f56b42c3b13fd4bf3
] 
[vectoriser: fix warning
Ben Lippmeier <[email protected]>**20101126042950
 Ignore-this: df8dd25bcfb3946c2974b13953a2f2c7
] 
[vectoriser: take class directly from the instance tycon
Ben Lippmeier <[email protected]>**20101126042900
 Ignore-this: 626a416717a5a059f39e53f4ec95fc66
] 
[vectoriser: comments only
Ben Lippmeier <[email protected]>**20101125073201
 Ignore-this: 8846ea8895307083bd1ebbc5d7fb1c5
] 
[vectoriser: follow changes in mkClass
Ben Lippmeier <[email protected]>**20101125062349
 Ignore-this: d5018cc022686d4272e126ca9a12283a
] 
[vectoriser: tracing wibbles
Ben Lippmeier <[email protected]>**20101125062332
 Ignore-this: c2024d8f03bc03bee2851f4f1c139fd5
] 
[mkDFunUnfolding wants the type of the dfun to be a PredTy
[email protected]**20100914062939
 Ignore-this: 7aa6e6b140746184cf00355b50c83b66
] 
[vectoriser: fix conflicts
Ben Lippmeier <[email protected]>**20101125060904
 Ignore-this: cc3decab1affada8629ca3818b76b3bf
] 
[Comments and formatting only
[email protected]**20100914062903
 Ignore-this: b0fc25f0952cafd56cc25353936327d4
] 
[Comments and formatting to type environment vectoriser
[email protected]**20100909080405
 Ignore-this: ab8549d53f845c9d82ed9a525fda3906
] 
[Don't mix implicit and explicit layout
Ian Lynagh <[email protected]>**20101124231514] 
[Whitespace only
Ian Lynagh <[email protected]>**20101124230655] 
[Separate NondecreasingIndentation out into its own extension
Ian Lynagh <[email protected]>**20101124220507] 
[Add another GHC layout rule relaxation to RelaxedLayout
Ian Lynagh <[email protected]>**20101124205957] 
[Remove an unused build system variable: GhcDir
Ian Lynagh <[email protected]>**20101124140455] 
[Remove unused build system variable: GhcHasEditline
Ian Lynagh <[email protected]>**20101124140415] 
[Remove unused variables from the build system: HBC, NHC, MKDEPENDHS
Ian Lynagh <[email protected]>**20101124140052] 
[Remove references to Haskell 98
Ian Lynagh <[email protected]>**20101123233536
 They are no longer right, as we have Haskell' generating new Haskell

 standards.
] 
[Tweak a configure test
Ian Lynagh <[email protected]>**20101123170621] 
[Add a configure test for the visibility hidden attribute
Ian Lynagh <[email protected]>**20101123170541] 
[sanity: fix places where we weren't filling fresh memory with 0xaa
Simon Marlow <[email protected]>**20101029092843
 Ignore-this: 2cb18f7f5afcaf33371aeffce67e218f
] 
[Just some alpha renaming
Ian Lynagh <[email protected]>**20101121144455
 Ignore-this: d5e807c5470840efc199e29f7d50804c
] 
[Fix bug #3165 (:history throws irrefutable pattern failed)
[email protected]**20101115223623
 Ignore-this: 73edf56e502b4d0385bc044133b27946
 
 I ran across this bug and took the time to fix it, closing
 a long time due TODO in InteractiveEval.hs
 
 Instead of looking around to find the enclosing declaration
 of a tick, this patch makes use of the information already collected during the
 coverage desugaring phase
] 
[For bindists, build ghc-pwd with stage 1
Ian Lynagh <[email protected]>**20101121183520
 Ignore-this: a3b5c8b78c81ec1b6d5fbf23da346ff5
 rather then the bootstrapping compiler. This fixes problems where the
 bootstrapping compiler dynamically links against libraries not on the
 target machine.
] 
[Makefile tweak
Ian Lynagh <[email protected]>**20101121183342
 Ignore-this: cd55a2819c1a5fd36da1bc7a75d2ded1
] 
[Fix a makefile include ordering sanity check
Ian Lynagh <[email protected]>**20101121174916
 Ignore-this: d0bdd41c4b618944d04ecb4f54fdd0f1
] 
[Add an extension for GHC's layout-rule relaxations
Ian Lynagh <[email protected]>**20101120215340
 Still TODO: Add the other relaxation (#1060) and update the alternative
 layout rule to use the extension.
] 
[Tweak the bindist configure.ac.in
Ian Lynagh <[email protected]>**20101120173735] 
[configure.ac tweaks
Ian Lynagh <[email protected]>**20101120170245] 
[When testing the bindist, tell it where gcc is
Ian Lynagh <[email protected]>**20101120155920
 The location isn't baked into the bindist, as it may differ from
 machine to machine.
] 
[Comments only
[email protected]**20101119100153
 Ignore-this: 7abd5d965ea805770449d6f8dadbb921
] 
[ForceSpecConstr now forces specialisation even for arguments which aren't scrutinised
Roman Leshchinskiy <[email protected]>**20101118212839
 Ignore-this: db45721d29a694e53746f8b76513efa4
] 
[Move the superclass generation to the canonicaliser
[email protected]**20101118120533
 Ignore-this: 5e0e525402a240b709f2b8104c1682b2
 
 Doing superclass generation in the canonicaliser (rather than
 TcInteract) uses less code, and is generally more efficient.
 
 See Note [Adding superclasses] in TcCanonical.
 
 Fixes Trac #4497.
] 
[Fix the generation of in-scope variables for IfaceLint check
[email protected]**20101118090057
 Ignore-this: bbcdba61ddf89d07fe69ca99c2017e3f
] 
[Comments only
[email protected]**20101118090034
 Ignore-this: fa2936d35a0f7be4e4535ea9e2b7bf7b
] 
[Omit bogus test for -XDeriveFunctor
[email protected]**20101118090028
 Ignore-this: a534243011809ebbb788b910961601c5
 
 It was duplicated in the case of 'deriving( Functor )'
 and wrong for 'deriving( Foldable )'
] 
[Improve error message on advice from a user
[email protected]**20101118085306
 Ignore-this: bd4f3858ff24e602e985288f27d536f3
 
 See Trac #4499
] 
[TAG 2010-11-18
Ian Lynagh <[email protected]>**20101118011554
 Ignore-this: ccadbe7fadd1148d2ee3caa8c8821ec5
] 
Patch bundle hash:
6a28d23e129efae6dd77cc16711ceff41a4293ce
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to