1 patch for repository http://darcs.haskell.org/ghc-7.0/ghc:

Wed Feb  9 17:24:23 EST 2011  gwri...@antiope.com
  * Fix #4867, ghci displays negative floats incorrectly
  
  This patch fixes the erroneous relocations that caused
  the bug in ticket #4867.  External addresses and global
  offset table entries were relocated correctly, but all other
  relocations were incorrectly calculated.  This caused, for
  example, bad references to constants stored in the __const
  section of the __TEXT segment.
  
  This bug only affected OS X on 64-bit platforms.
  
New patches:

[Fix #4867, ghci displays negative floats incorrectly
gwri...@antiope.com**20110209222423
 Ignore-this: 1b3279fa5f6c4849ed6311275b1a466a
 
 This patch fixes the erroneous relocations that caused
 the bug in ticket #4867.  External addresses and global
 offset table entries were relocated correctly, but all other
 relocations were incorrectly calculated.  This caused, for
 example, bad references to constants stored in the __const
 section of the __TEXT segment.
 
 This bug only affected OS X on 64-bit platforms.
 
] hunk ./rts/Linker.c 4692
         }
         else
         {
-            value = sections[reloc->r_symbolnum-1].offset
-                  - sections[reloc->r_symbolnum-1].addr
-                  + (uint64_t) image;
+	    value = relocateAddress(oc, nSections, sections, reloc->r_address);
         }
 
         IF_DEBUG(linker, debugBelch("relocateSection: value = %p\n", (void *)value));

Context:

[Fix typo in SpecConstr that made it not work at all
simo...@microsoft.com**20110203172756
 Ignore-this: b550d5c5b73ed13709ee2938c80a750f
 
 There was a terrible typo in this patch; I wrote "env"
 instead of "env1".
 
    Mon Jan 31 11:35:29 GMT 2011  simo...@microsoft.com
      * Improve Simplifier and SpecConstr behaviour
 
 Anyway, this fix is essential to make it work properly.
 Thanks to Max for spotting the problem (again).
] 
[avoid adding HPC ticks to arrow constructs (fixes #1333)
Ross Paterson <r...@soi.city.ac.uk>**20110202211425
 Ignore-this: 2938850ebbb53d1bc6bf0399f68dd8e5
] 
[Fix type checker error message
simo...@microsoft.com**20110201122920
 Ignore-this: 7369cc5f8dae3d81621f580a8ddaf41e
 
 See Trac #4940. We had a message
      The lambda expression `\ x -> x' has one argument one argument,
 repeating the "one argument" part.  Easy fix.
] 
[Fix bug in roughTopNames
simo...@microsoft.com**20110126171803
 Ignore-this: eca8b144162f1bd94e2ccb433bca1e02
 
 roughTopNames was returning a name that in fact might be
 "looked though" by the rule matcher. Result: a rule
 that should match was being pre-emptively discarded.
 
 See Note [Care with roughTopName].
 
 Fixes a bug noticed by Pedro (Trac #4918).
] 
[Fix Trac #4917: try a bit harder to unify on-the-fly
simo...@microsoft.com**20110125110112
 Ignore-this: e96e0a19ab8517d4ba648efe91f6b379
 
 This is generally a modest improvement but, more important,
 it fixes a "unify-under-forall" problem.  See Note [Avoid deferring].
 
 There's still a lurking unsatisfactory-ness in that we can't
 defer arbitrary constraints that are trapped under a forall.
] 
[Look through type synonyms when computing orphans
simo...@microsoft.com**20110126171229
 Ignore-this: 6dfc45dae3a94cdb0022b2d21d6e09f6
 
 I renamed functions tyClsNamesOfTypes to oprhNamesOfType,
 because it's only used in that capacity, and we therefore
 want to look through type synonyms.  Similarly exprOrphNames.
 
 This fixes Trac #4912.
] 
[Improve Simplifier and SpecConstr behaviour
simo...@microsoft.com**20110131113529
 Ignore-this: e5b96c97cee0950e558ddf15178bb6c9
 
 Trac #4908 identified a case where SpecConstr wasn't "seeing" a
 specialisation it should easily get.  The solution was simple: see
 Note [Add scrutinee to ValueEnv too] in SpecConstr.
 
 Then it turned out that there was an exactly analogous infelicity in
 the mighty Simplifer too; see Note [Add unfolding for scrutinee] in
 Simplify. This fix is good for Simplify even in the absence of the
 SpecConstr change.  (It arose when I moved the binder- swap stuff to
 OccAnall, not realising that it *remains* valuable to record info
 about the scrutinee of a case expression.  The Note says why.
 
 Together these two changes are unconditionally good.  Better
 simplification, better specialisation. Thank you Max.
] 
[Fix dependencies among specialisations for imported Ids
simo...@microsoft.com**20110126172112
 Ignore-this: 364e09c11affe7bfe8f1b934ea28bbb6
 
 This was a subtle one (Trac #4903).  See
   Note [Glom the bindings if imported functions are specialised]
 in Speclialise.
 
 Fundamentally, a specialised binding for an imported Id was being
 declared non-recursive, whereas in fact it can become recursive
 via a RULE.  Once it's specified non-recurive the OccAnal pass
 treats that as gospel -- and that in turn led to infinite inlining.
 
 Easily fixed by glomming all the specialised bindings in a Rec;
 now the OccAnal will sort them out correctly.
] 
[Fix Trac #4874: specialisation of INLINABLE things
simo...@microsoft.com**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.
] 
[Fix an egregious strictness analyser bug (Trac #4924)
simo...@microsoft.com**20110128080748
 Ignore-this: 3bf533c3d30b45a8e78b1fec3d9634f
 
 The "virgin" flag was being threaded rather than treated
 like an environment.  As a result, the second and subsequent
 recursive definitions in a module were not getting a
 correctly-initialised fixpoint loop, causing much worse
 strictness analysis results.  Indeed the symptoms in
 Trac #4924 were quite bizarre.
 
 Anyway, it's easily fixed.  Merge to stable branch.
] 
[tweak newArray# documentation again
Simon Marlow <marlo...@gmail.com>**20110119140633
 Ignore-this: ceee33428dbad7e0f5eabfa0a2590466
] 
[Fix documentation bug: newArray# accepts word count, not byte count.
Edward Z. Yang <ezy...@mit.edu>**20110118221834
 Ignore-this: 8daab134bf72a740b89d273fb4e983d5
] 
[Fix validate on OS X 64
Ian Lynagh <ig...@earth.li>**20110124183618] 
[Whitespace-only in rts/Linker.c
Ian Lynagh <ig...@earth.li>**20101217234124] 
[Fix Windows build: move rtsTimerSignal to the POSIX-only section
Simon Marlow <marlo...@gmail.com>**20101210090045
 Ignore-this: aa1844b70b9f1a44447787c4bbe10d44
] 
[Export the value of the signal used by scheduler (#4504)
Dmitry Astapov <dasta...@gmail.com>**20101208183755
 Ignore-this: 427bf8c2469283fc7a6f759440d07d87
] 
[Add some casts to fix warnings; patch from Greg Wright
Ian Lynagh <ig...@earth.li>**20101217223811] 
[Keep separate linker flags, for when we want to link with gcc or ld
Ian Lynagh <ig...@earth.li>**20110124233121] 
[Track change in isInlinePragma
simo...@microsoft.com**20101105131545
 Ignore-this: 256f4940744d84086c0f1c99a9ab8778
 
 In TcBinds we want to use isAnyInlinePragma, to get
 both INLINE and INLINABLE.  I don't know why this isn't
 leading to failures for others!  The (bogus) error I got, 
 triggered by this bug was:
 
   libraries\haskeline\System\Console\Haskeline\Key.hs:23:1:
     You cannot SPECIALISE `M.findWithDefault'
       because its definition has no INLINE/INLINABLE pragma
] 
[In configure, test that GHC generates code for the correct platform (#4819)
Simon Marlow <marlo...@gmail.com>**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
] 
[Produce an error message, not a crash, for HsOpApp with non-var operator
simo...@microsoft.com**20110112170719
 Ignore-this: df0f6f2e3318f9c33a714609019b0262
 
 Fixes Trac #4877.
] 
[Fix longstanding bug in C-- inlining for functions calls.
Edward Z. Yang <ezy...@mit.edu>**20110113130654
 Ignore-this: 79001003b1f3cc5005207ccfed980c21
] 
[Fix a buglet in postInlineUnconditionally
simo...@microsoft.com**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]
] 
[Some infrastruture for lambda-lifting
simo...@microsoft.com**20101116173500
 Ignore-this: bb0b7db06898b9fa731602107febbf7
 
 This stuff should have no effect but it sets things
 up so that we can try floating out lambdas of n value
 arguments.
 
 The new (secret) flag is -ffloatt-lam-args=n.
 
 This is *not* working yet, but it's got tangled up with
 other stuff I want to commit, and it does no harm.
] 
[Refactoring of the way that inlinings and rules are activated
simo...@microsoft.com**20101116173719
 Ignore-this: d195c39a646e1fac3804fb044644d226
 
 Principally, the SimplifierMode now carries several (currently
 four) flags in *all* phases, not just the "Gentle" phase.
 This makes things simpler and more uniform.
 
 As usual I did more refactoring than I had intended.
 
 This stuff should go into 7.0.2 in due course, once
 we've checked it solves the DPH performance problems.
] 
[Two signficant changes to the simplifier
simo...@microsoft.com**20101027193729
 Ignore-this: 9b35e8ad975ba1cebbba28028f1c7f43
 
 1. Do eta-expansion at let-bindings, not lambdas.
    I have wanted to do this for a long time.
    See Note [Eta-expanding at let bindings] in SimplUtils
 
 2. Simplify the rather subtle way in which InlineRules (the
    template captured by an INLINE pragma) was simplified.
    Now, these templates are always simplified in "gentle"
    mode only, and only INLINE things inline inside them.
 
    See Note Note [Gentle mode], Note [Inlining in gentle mode]
    and Note [RULEs enabled in SimplGently] in SimplUtils
] 
[Can't use DeriveFunctor in 7.0, as we need to be able to build with 6.10
Ian Lynagh <ig...@earth.li>**20110121151201
 Ignore-this: 5bdffaf4e23bf333bf5ca2d2872a026a
] 
[Resolve conflicts
Ian Lynagh <ig...@earth.li>**20110121150119
 Ignore-this: b26de1a8fcd756bd233225f79724c032
] 
[Resolve conflict
Ian Lynagh <ig...@earth.li>**20110121144437
 Ignore-this: 57893f741650c80c758f8d69ac192ed8
] 
[Major refactoring of the type inference engine
simo...@microsoft.com**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.
] 
[A little refactoring (remove redundant argument passed to isGoodRecEv)
simo...@microsoft.com**20101202123110
 Ignore-this: e517c5c12109a230f08dafb4d1e386df
] 
[Doing the smart canonicalization only if we are not simplifying a Rule LHS.
dimit...@microsoft.com**20101210132221
 Also, same thing now applies for adding superclasses.
 
] 
[Fix recursive superclasses (again).  Fixes Trac #4809.
simo...@microsoft.com**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.
] 
[Comments and layout
simo...@microsoft.com**20101015131924
 Ignore-this: 126fbdb629a08c1380c7a1f5cd967d97
] 
[Occurrence analyser takes account of the phase when handing RULES
simo...@microsoft.com**20101116173312
 Ignore-this: 50558fb8ec8fe1d0d50db46a7153b077
 
 See Note [Finding rule RHS free vars]
 
 This should make Roman happy.
] 
[Comments and formatting only
b...@ouroborus.net**20100914062903
 Ignore-this: b0fc25f0952cafd56cc25353936327d4
] 
[Fix up TcInstDcls
simo...@microsoft.com**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  simo...@microsoft.com
   * 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.
] 
[Moved canonicalisation inside solveInteract
dimit...@microsoft.com**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]
 
] 
[Fix Trac #3731: more superclass subtlety (sigh)
simo...@microsoft.com**20101214180344
 Ignore-this: f4168e59f3164303ba7be022ba19c37b
 
 I will add more comments, but I want to commit this tonight,
 so the overnight builds get it.
] 
[Re-jig simplifySuperClass (again)
simo...@microsoft.com**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.
] 
[Do dependency analysis when kind-checking type declarations
simo...@microsoft.com**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.
] 
[Update the generics docs; pointed out by Christian Maeder
Ian Lynagh <ig...@earth.li>**20110117214632] 
[Reinstate the OS X flags in the LDFLAGS etc variables
Ian Lynagh <ig...@earth.li>**20110117200540
 Ignore-this: 9261baa1843100f65b02fb91c1a0d225
 I expect this will fix:
 http://www.haskell.org/pipermail/cvs-ghc/2011-January/059098.html
] 
[It's not clear if LDFLAGS flags will be given to gcc or ld,
Ian Lynagh <ig...@earth.li>**20110116151230
 Ignore-this: a6a2d0b1f550c922c32f6f252e4e3285
 and they accept different flags, so for now do nothing
] 
[Fix libffi build rules
Ian Lynagh <ig...@earth.li>**20110115202104
 Ignore-this: 57e1763d2079301b0165be7deba29c85
 Fixes a rare race when both libHSffi.a and libHSffi_p.a were being built
 at the same time:
 
 "cp" libffi/dist-install/build/libffi.a libffi/dist-install/build/libHSffi.a
 "cp" libffi/dist-install/build/libffi.a libffi/dist-install/build/libHSffi.a
 "cp" libffi/dist-install/build/libffi.so libffi/dist-install/build/libHSffi-ghc7.1.20110115.so
 cp: cannot create regular file `libffi/dist-install/build/libHSffi.a': File exists
] 
[Turn off dtrace unless you override USE_DTRACE
Ian Lynagh <ig...@earth.li>**20110116180306
 Ignore-this: beafc2002091fa7f0e66666004c870a5
 There are problems with dtrace on 64bit 10.5. For now at least, we
 just turn dtrace off unless you override USE_DTRACE
] 
[throwTo: report the why_blocked value in the barf()
Simon Marlow <marlo...@gmail.com>**20101203094840
 Ignore-this: 3b167c581be1c51dfe3586cc6359e1d0
] 
[Fix Trac #4870: get the inlining for an imported INLINABLE Id
simo...@microsoft.com**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).
] 
[Fix installation on cygwin
Ian Lynagh <ig...@earth.li>**20110111194838
 Ignore-this: fe923d0619da3bd3a34968106c92fdab
] 
[Rejig the includes/ installation rules
Ian Lynagh <ig...@earth.li>**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).
] 
[MERGED: releaseCapabilityAndQueueWorker: task->stopped should be false (#4850)
Ian Lynagh <ig...@earth.li>**20110109005801] 
[boundTaskExiting: don't set task->stopped unless this is the last call (#4850)
Simon Marlow <marlo...@gmail.com>**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).
] 
[Add utils/ghc-cabal/Makefile
Ian Lynagh <ig...@earth.li>**20110108144049] 
[Make DESTDIR an absolute path when installing; fixes #4883
Ian Lynagh <ig...@earth.li>**20110108171635] 
[Improve error message when importing data constructors (ticket #4058).
Michal Terepeta <michal.terep...@gmail.com>**20101127211338
 Ignore-this: 3289a08f0391dd90dfef2e0403a04ccd
] 
[Remove redundant import
Ian Lynagh <ig...@earth.li>**20110108130047
 Ignore-this: 1c7fdec77b48319c845c9593b5fb94af
] 
[catch SIGTSTP and save/restore terminal settings (#4460)
Simon Marlow <marlo...@gmail.com>**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).
] 
[Improve error message of :set in ghci (ticket #4190).
Michal Terepeta <michal.terep...@gmail.com>**20101130211505
 Ignore-this: ccc8a0816a900ba8c4a966285a465b23
] 
[Improve printing for -ddump-deriv
simo...@microsoft.com**20101215121955
 Ignore-this: 3181c948c4c2471bd99b32c5ee487a1e
] 
[do not compile part of shared lib RTS with -fno-PIC on Solaris
Karel Gardas <karel.gar...@centrum.cz>**20101217085133
 Ignore-this: 8c8dbb45cac0578a58a3557f1e03c66
] 
[provide shared libraries support on i386-unknown-solaris2 platform
Karel Gardas <karel.gar...@centrum.cz>**20101217084617
 Ignore-this: b6079c6a39a71200a1ee863573e40828
] 
[fix CPP detection of Solaris in NCG
Karel Gardas <karel.gar...@centrum.cz>**20101217084510
 Ignore-this: 9d1ce59d469294eab1f0cbc697e48d69
] 
[Fix a bug in functorLikeTraverse, which was giving wrong answer for tuples
simo...@microsoft.com**20101215123725
 Ignore-this: 560220e92429b5b1a6197a62f94a4ff2
 
 This bug led to Trac #4816, which is hereby fixed
] 
[Allow enumerations to have phantom arguments.
simo...@microsoft.com**20101215121817
 Ignore-this: 32ef8cb869e6e38c2e43b3ae87b1b9a8
 
 The bytecode generator was being too eager.
 Fixes Trac #4528, or rather, a near variant.
] 
[Tighten up what it means to be an "enumeration data constructor"
simo...@microsoft.com**20101215121927
 Ignore-this: 459b3f9f7994a13094ed87b0768b33a8
 
 See Note [Enumeration types] in TyCon, and comments in Trac #4528
] 
[add 'make re2' for rebuilding stage2 (similarly re1 and re3)
Simon Marlow <marlo...@gmail.com>**20101221100254
 Ignore-this: 5c0afe3810b66a5b6e53a3a0fe933945
] 
[add comment to remind people to update driver/gcc/gcc.c
Simon Marlow <marlo...@gmail.com>**20110106152402
 Ignore-this: c07d7ac11eb9221ef821f78aab1807cb
] 
[update paths now that we upgraded gcc to 4.5.0
Simon Marlow <marlo...@gmail.com>**20110106133729
 Ignore-this: f8f9bcad984fdd472e0ae958b66bea9d
] 
[Create ~/.ghc/ if it doesn't already exist; fixes trac #4522
Ian Lynagh <ig...@earth.li>**20101218184925] 
[Pass --hoogle to haddock; fixes trac #4521
Ian Lynagh <ig...@earth.li>**20101219125243] 
[use Win32 CreateProcess() rather than mingw spawnv() (#4531)
Simon Marlow <marlo...@gmail.com>**20110106133834
 Ignore-this: 4c0947853549dad034622c044391af6c
] 
[Fix mkUserGuidePart program name on Windows
Ian Lynagh <ig...@earth.li>**20110106143707] 
[On Cygwin, use a Cygwin-style path for /bin/install's destination
Ian Lynagh <ig...@earth.li>**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 #4829 (build does not respect --with-gcc option)
gwri...@antiope.com**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.
   
] 
[comments on SRC_HC_OPTS (#4829)
Simon Marlow <marlo...@gmail.com>**20101214101340
 Ignore-this: e2bdec00f07b68e82837e77a4faf6514
] 
[fix #3910
Simon Marlow <marlo...@gmail.com>**20101216114452
 Ignore-this: 410e95e188344a523520e192a3fb58ea
] 
[refactor and tidy up the section on RTS options
Simon Marlow <marlo...@gmail.com>**20101216123151
 Ignore-this: 9cdafd687351d8a3ff879b64347f85d3
] 
[Related to #4826: Some minor tweaks to the wording of the User Guide, section 4.16
Orphi <mathematicalorc...@hotmail.com>**20101209170440
 Ignore-this: c3d942d58594be7d4c2eb4dc3a22f19
] 
[FIX #4826 partial: Add -rtsopts and -with-rtsopts to User Guide section 4.11.6
Orphi <mathematicalorc...@hotmail.com>**20101209165152
 Ignore-this: 2fc1c0abbb783695773ab0f9c013bbaa
] 
[FIX #4826 partially: Change -f to -? in User Guide section F4.16
Orphi <mathematicalorc...@hotmail.com>**20101209144148
 Ignore-this: 73410b350e80c8943ae722dec8dea44b
] 
[Fix error compiling AsmCodeGen.lhs for PPC Mac (unused makeFar addr)
n...@post11.tele.dk**20101219213555
 Ignore-this: ab25d5f2e2ebe163547d5babaf4b1dbf
] 
[Fix error compiling AsmCodeGen.lhs for PPC Mac (rtsPackageId)
n...@post11.tele.dk**20101219212530
 Ignore-this: 946f6d3e0d3c3ddf2dc07b85e1f82d85
] 
[Add gcc and ld flags to --info output
Ian Lynagh <ig...@earth.li>**20101220173520] 
[Updated ANNOUNCE
Ian Lynagh <ig...@earth.li>**20101220162525
 Ignore-this: 9cde75aea69b8c945a1cbee488bd8ee4
] 
[Fix checkBinaries on OS X
Ian Lynagh <ig...@earth.li>**20101216201121] 
[Use "-perm -u+x" rather than "-executable" to find executables
Ian Lynagh <ig...@earth.li>**20101216145235
 On Windows, -executable is matching the html docs.
] 
[Remove a debugging print
Ian Lynagh <ig...@earth.li>**20101216011459] 
[Add release notes for 7.0.2
Ian Lynagh <ig...@earth.li>**20101215165746
 Ignore-this: 686eeb9b0b301444a2ab0ed81e9d1d76
] 
[Wibble to InstEnv.instanceHead
simo...@microsoft.com**20101214082939
 Ignore-this: 851db517f8638a0aeb7ad461298f7e9f
 
 Fixes an accidental glitch in T1835
] 
[MERGED: Fix recursive superclasses (again).  Fixes Trac #4809.
Ian Lynagh <ig...@earth.li>**20101214180026
 simo...@microsoft.com**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.
] 
[Add libstdc++-4.5.0-1-mingw32-dll-6.tar.lzma to mingw tarballs
Ian Lynagh <ig...@earth.li>**20101213223153] 
[GHCi linker: Assume non-Haskell libraries are dynamic libs
Ian Lynagh <ig...@earth.li>**20101213124930
 Ignore-this: aa153a8f6e309c7b3dae7e46bb7a9583
 This works around a segfault we get when trying to load libiconv.a on
 some platforms.
] 
[Make the case-to-let transformation a little less eager
simo...@microsoft.com**20101208172251
 Ignore-this: 55eaa1b5753af31aeb32ec792cb6b662
 
 See Note [Case elimination: lifted case].
 Thanks to Roman for identifying this case.
] 
[Fix Trac #4534: renamer bug
simo...@microsoft.com**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.
] 
[Only reset the event log if logging is turned on (addendum to #4512)
Simon Marlow <marlo...@gmail.com>**20101210093951
 Ignore-this: c9f85f0de2b11a37337672fba59aecc6
] 
[allocate enough room for the longer filename (addendum to #4512)
Simon Marlow <marlo...@gmail.com>**20101210093906
 Ignore-this: 270dc0219d98f1e0f9e006102ade7087
] 
[warning fix: don't redefine BLOCKS_PER_MBLOCK
Simon Marlow <marlo...@gmail.com>**20101210094002
 Ignore-this: cadba57f1c38f5e2af1de37d0a79c7ee
] 
[Add a test that all programs in the bindist were built with the right GHC
Ian Lynagh <ig...@earth.li>**20101210161218
 They should use the GHC from the build tree, not the bootstrapping compiler.
] 
[Add --version support to ghc-cabal
Ian Lynagh <ig...@earth.li>**20101212213600
 Ignore-this: ef696dcb1b96a23765f9f18e75a56f5
] 
[Don't link the GHC RTS into our C-only programs
Ian Lynagh <ig...@earth.li>**20101210185402
 Ignore-this: 56f620f7eb16a03e7497a161bc48458e
] 
[Build a copy of ghc-cabal with the in-tree compiler, for the bindist
Ian Lynagh <ig...@earth.li>**20101210181123] 
[fix warnings
Simon Marlow <marlo...@gmail.com>**20101209115844
 Ignore-this: ffff37feb2abbfc5bd12940c7007c208
] 
[:unset settings support
Boris Lykah <lyk...@gmail.com>**20101123190132
 Ignore-this: 5e97c99238f5d2394592858c34c004d
 Added support for settings [args, prog, prompt, editor and stop].
 Now :unset supports the same set of options as :set.
] 
[Use liftIO rather than io
Ian Lynagh <ig...@earth.li>**20101103212216] 
[Fixes for #4512: EventLog.c - provides ability to terminate event logging, Schedule.c - uses them in forkProcess.
Dmitry Astapov <dasta...@gmail.com>**20101203133950
 Ignore-this: 2da7f215d6c22708a18291a416ba8881
] 
[fix ticket number (#4505)
Simon Marlow <marlo...@gmail.com>**20101209120404
 Ignore-this: 5769c5ce2a8d69d62d977a9ae138ec23
] 
[Catch too-large allocations and emit an error message (#4505)
Simon Marlow <marlo...@gmail.com>**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.
] 
[Tweak the "sorry" message a bit
Simon Marlow <marlo...@gmail.com>**20101208163212
 Ignore-this: aa1ce5bc3c27111548204b740572efbe
 
 -		"sorry! (this is work in progress)\n"
 +		"sorry! (unimplemented feature or known bug)\n"
] 
[Cleanup comments and formatting only
b...@ouroborus.net**20101029065837
 Ignore-this: 393131d43ae57e4c1e7ac0dce734c452
] 
[Fix Windows memory freeing: add a check for fb == NULL; fixes trac #4506
Ian Lynagh <ig...@earth.li>**20101208152349
 Also added a few comments, and a load of code got indented 1 level deeper.
] 
[Make CPPFLAGS variables, as well as CFLAGS and LDFLAGS
Ian Lynagh <ig...@earth.li>**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.
] 
[Tweak the cleaning of inplace/; fixes trac #4320
Ian Lynagh <ig...@earth.li>**20101205212048] 
[Add a configure message
Ian Lynagh <ig...@earth.li>**20101206215201] 
[Tweak a configure test
Ian Lynagh <ig...@earth.li>**20101123170621] 
[Link even programs containing no Haskell modules with GHC
Ian Lynagh <ig...@earth.li>**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 <ig...@earth.li>**20101206203125] 
[Close .ghci files after reading them; fixes trac #4487
Ian Lynagh <ig...@earth.li>**20101205205301] 
[Fix a nasty bug in RULE matching: Trac #4814
simo...@microsoft.com**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.
] 
[Fix a recomp bug: make classes/datatypes depend directly on DFuns (#4469)
Simon Marlow <marlo...@gmail.com>**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
] 
[removeThreadFromQueue: stub out the link field before returning (#4813)
Simon Marlow <marlo...@gmail.com>**20101202160838
 Ignore-this: 653ae17bc1120d7f4130da94665002a1
] 
[handle ThreadMigrating in throwTo() (#4811)
Simon Marlow <marlo...@gmail.com>**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.
] 
[Tell gcc to support back to OS X 10.5
Ian Lynagh <ig...@earth.li>**20101203201558
 Ignore-this: f02d70e5b9cce50137981c6cb2b62a18
] 
[Remove the no-ghci-lib warning in ghc-pkg
Ian Lynagh <ig...@earth.li>**20101127235805
 GHCi libs are no longer necessary, as we can use the .a or .so versions
 instead.
] 
[rts/Linker.c (loadArchive):
p...@cielonegro.org**20101130142700
 Ignore-this: bc84f9369ce5c2d289440701b7a3a2ab
 
 This routine should be aware of Mach-O misalignment of malloc'ed memory regions.
] 
[Add GNU-variant support to the .a parser, and other improvements/tidyups
Ian Lynagh <ig...@earth.li>**20101127223945] 
[Re-indent only
Ian Lynagh <ig...@earth.li>**20101127191646] 
[Improve linker debugging for archive files
Ian Lynagh <ig...@earth.li>**20101127190907] 
[Always enable the archive-loading code
Ian Lynagh <ig...@earth.li>**20101127173000
 If the GHCi .o lib doesn't exist, load the .a instead
] 
[FIX #1845 (unconditional relative branch out of range)
p...@cielonegro.org**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 (machoGetMisalignment):
p...@cielonegro.org**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):
p...@cielonegro.org**20101130121425
 Ignore-this: 1e2c207e4b1d17387617ec5d645204b7
 
 I found this function causes a segfault when ocAllocateSymbolExtras() has allocated a separate memory region for jump islands.
] 
[fix ref to utils/ext-core, which moved to Hackage (extcore package)
Simon Marlow <marlo...@gmail.com>**20101201092147
 Ignore-this: 272a7daaa335ef60bcc645db70b4d68b
] 
[fix floating-point/FFI section: fenv is C99, not POSIX
Simon Marlow <marlo...@gmail.com>**20101201092119
 Ignore-this: ce8b3edd428e4f77691dd739b5b4ae73
] 
[Document the behaviour of fenv.h functions with GHC (#4391)
Simon Marlow <marlo...@gmail.com>**20101126125336
 Ignore-this: bc4eab49428d567505a28add6fed90f1
] 
[Substitution should just substitute, not optimise
simo...@microsoft.com**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.
] 
[Allow the old [$foo| ... |] syntax for quasi-quotes
simo...@microsoft.com**20101112083052
 Ignore-this: 868e0e07fc6bbc9772bcba54e8ca79d
 
 This is just a backward-compatibility thing, to be removed
 eventually.
] 
[For bindists, build ghc-pwd with stage 1
Ian Lynagh <ig...@earth.li>**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 <ig...@earth.li>**20101121183342
 Ignore-this: cd55a2819c1a5fd36da1bc7a75d2ded1
] 
[Fix a makefile include ordering sanity check
Ian Lynagh <ig...@earth.li>**20101121174916
 Ignore-this: d0bdd41c4b618944d04ecb4f54fdd0f1
] 
[Tweak the bindist configure.ac.in
Ian Lynagh <ig...@earth.li>**20101120173735] 
[configure.ac tweaks
Ian Lynagh <ig...@earth.li>**20101120170245] 
[When testing the bindist, tell it where gcc is
Ian Lynagh <ig...@earth.li>**20101120155920
 The location isn't baked into the bindist, as it may differ from
 machine to machine.
] 
[Add -fwarn-lazy-unlifted-bindings to the list of flags
simo...@microsoft.com**20101116172211
 Ignore-this: 4f150f347bb74027adacb64545f6b757
] 
[Improve documentation for -fwarn-incomplete-patterns
simo...@microsoft.com**20101116171527
 Ignore-this: d8386202cc322207436db0c5b185dab
] 
[Eventlog: Put correct size for startup event
sc...@leeds.ac.uk**20101105151655
 Ignore-this: 8b6eb4fa2137c8dfe50c5917e3a609a7
] 
[Omit bogus test for -XDeriveFunctor
simo...@microsoft.com**20101118090028
 Ignore-this: a534243011809ebbb788b910961601c5
 
 It was duplicated in the case of 'deriving( Functor )'
 and wrong for 'deriving( Foldable )'
] 
[Move the superclass generation to the canonicaliser
simo...@microsoft.com**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.
] 
[Improve error message on advice from a user
simo...@microsoft.com**20101118085306
 Ignore-this: bd4f3858ff24e602e985288f27d536f3
 
 See Trac #4499
] 
[Buglet in tcIface, now that nested binders can have pragmas
simo...@microsoft.com**20101027184235
 Ignore-this: de2db50370c35b8ae92ec2574d806b33
 
 This fix ties the knot for recursive groups properly
] 
[Fix initialisation of strictness in the demand analyser
simo...@microsoft.com**20101026081757
 Ignore-this: d89b117caa95b51b6c24584ac03bedf6
 
 Previously, the demand analyser assumed that every binder 
 starts off with no strictness info.  But now that we are
 preserving strictness on nesting bindings in interface files,
 that assumption is no longer correct, because an inlined function
 might have a nested binding with strictness set.
 
 So we need to know when we are in the initial sweep, so that we can
 set the strictness to 'bottom'. 
 
 See Note [Initialising strictness]
] 
[Fix the generation of in-scope variables for IfaceLint check
simo...@microsoft.com**20101118090057
 Ignore-this: bbcdba61ddf89d07fe69ca99c2017e3f
] 
[Serialise nested unfoldings across module boundaries
simo...@microsoft.com**20101025152817
 Ignore-this: 1520586f152501d4acb084ebf9cd3136
 
 As Roman reported in #4428, nested let-bindings weren't
 being recorded with their unfoldings.  Needless to say,
 fixing this had more knock-on effects than I expected.
] 
[Nicer error message for #3782
b...@ouroborus.net**20101029063320
 Ignore-this: fc746cad57410123a29f37f61f13dd3c
 It now says:
 
 ghc-stage2: sorry! (this is work in progress)
   (GHC version 7.1.20101028 for i386-apple-darwin):
 	Vectorise.Builtins.indexBuiltin
     
     DPH builtin function 'sumTyCon' of size '11' is not yet implemented.
     This function does not appear in your source program, but it is needed
     to compile your code in the backend. This is a known, current limitation
     of DPH. If you want it to to work you should send mail to cvs-ghc@haskell.org
     and ask what you can do to help (it might involve some GHC hacking).
 
 
 I added 'pprSorry' that behaves like 'pprPanic' except it say sorry! instead 
 of panic!, and doesn't ask the user to report a bug. 
] 
[Build system tweak: Inline DQ now it's the same on all platforms
Ian Lynagh <ig...@earth.li>**20101114134636] 
[Update to docbook 4.5; fixes trac #4447
Ian Lynagh <ig...@earth.li>**20101114155023] 
[Fix -fwarn-missing-import-lists (fix Trac #4489)
simo...@microsoft.com**20101115232142
 Ignore-this: 656b3a76540a488a7111ba7c9ec8ebc4
] 
[Ensure that instance overlap errors are report properly
simo...@microsoft.com**20101115142805
 Ignore-this: 2fca29a95bdc69a4c783cbcc663a10f7
 
 This (annoyingly) requires us to re-flatten the class predicate.
 See Note [Flattening in error message generation]
] 
[Fix Trac #4501: a transposition error in DynFlags
simo...@microsoft.com**20101117100832
 Ignore-this: b81eca419581a7cec773556514915814
 
 Push to STABLE
] 
[Fix Trac #4498: bang-pattern bindings are monomorphic
simo...@microsoft.com**20101117101058
 Ignore-this: 2a739aeca590b4dd1907078ba80133ff
 
 This patch forces bang patterns to be monomorphic,
 and documents this fact.
] 
[Ensure that unification variables alloc'd during solving are untouchable
simo...@microsoft.com**20101115121540
 Ignore-this: 4cdb38180488e605489ce5d018998089
 
 This fixes Trac #4494.  See Note [Extra TcsTv untouchables] in TcSimplify.
] 
[Document SPECIALISE for imported functions
simo...@microsoft.com**20101117111559
 Ignore-this: 5c9e83d15b85fe5a8639321e00e5dcaa
 
 This is a really useful new facility, but I'd forgotten to document it.
 Pls merge to 7.0 branch
] 
[Add a build system dependency; fixes #4357
Ian Lynagh <ig...@earth.li>**20101114140311] 
[Set RELEASE to NO
Ian Lynagh <ig...@earth.li>**20101117141621] 
[TAG GHC 7.0.1 release
Ian Lynagh <ig...@earth.li>**20101117140118
 Ignore-this: ac737bfbb99523a6e0aa7f7a32727de9
] 
Patch bundle hash:
7221ac5b361c5ef113c73ac593325dc9588de914
_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to