Fri Mar 24 13:26:13 GMT 2006  Duncan Coutts <[EMAIL PROTECTED]>
  * mkDerivedConstants.c depends on ghcplatform.h
  I think this missing dep is what broke my parallel build
  I used make -j2 with ghc-6.4.2.20060323 and got:
  
  ------------------------------------------------------------------------
  ==fptools== make boot -wr --jobserver-fds=3,11 -j;
  in /var/tmp/portage/ghc-6.4.2_pre20060323/work/ghc-6.4.2.20060323/ghc/includes
  ------------------------------------------------------------------------
  Creating ghcplatform.h...
  Done.
  gcc -O -O2 -march=k8 -pipe -Wa,--noexecstack    -c mkDerivedConstants.c -o 
mkDerivedConstants.o
  In file included from ghcconfig.h:5,
                   from Stg.h:42,
                   from Rts.h:19,
                   from mkDerivedConstants.c:20:
  ghcplatform.h:1:1: unterminated #ifndef
  Done.
                                                    
  With this patch applied I can no longer repoduce this build bug.
  So I think this patch should be applied to the cvs ghc-6-4-branch too.
New patches:

[mkDerivedConstants.c depends on ghcplatform.h
Duncan Coutts <[EMAIL PROTECTED]>**20060324132613
 I think this missing dep is what broke my parallel build
 I used make -j2 with ghc-6.4.2.20060323 and got:
 
 ------------------------------------------------------------------------
 ==fptools== make boot -wr --jobserver-fds=3,11 -j;
 in /var/tmp/portage/ghc-6.4.2_pre20060323/work/ghc-6.4.2.20060323/ghc/includes
 ------------------------------------------------------------------------
 Creating ghcplatform.h...
 Done.
 gcc -O -O2 -march=k8 -pipe -Wa,--noexecstack    -c mkDerivedConstants.c -o mkDerivedConstants.o
 In file included from ghcconfig.h:5,
                  from Stg.h:42,
                  from Rts.h:19,
                  from mkDerivedConstants.c:20:
 ghcplatform.h:1:1: unterminated #ifndef
 Done.
 						    
 With this patch applied I can no longer repoduce this build bug.
 So I think this patch should be applied to the cvs ghc-6-4-branch too.
] {
hunk ./ghc/includes/Makefile 116
-mkDerivedConstants.c : $(H_CONFIG)
+mkDerivedConstants.c : $(H_CONFIG) $(H_PLATFORM)
}

Context:

[Documentation for -fno-code and -fwrite-iface.
Lemmih <[EMAIL PROTECTED]>**20060318173034] 
[Don't generate stub files when -fno-code is given.
Lemmih <[EMAIL PROTECTED]>**20060318171848] 
[-fno-code shouldn't be a mode.
Lemmih <[EMAIL PROTECTED]>**20060318171728
 
 I've removed -fno-code from Main to make it work
 equally well with --make and -c.
 I've also allowed it not to write hi files unless
 -fwrite-iface is given.
 
] 
[Cleanup after the OPTIONS parsing was moved.
Lemmih <[EMAIL PROTECTED]>**20060312132328] 
[fix build for certain picky versions of gcc
Simon Marlow <[EMAIL PROTECTED]>**20060317154734] 
[forkProcess(): watch out for ThreadRelocated
Simon Marlow <[EMAIL PROTECTED]>**20060317150752] 
[Make -fliberate-case work for GADTs
[EMAIL PROTECTED] 
[turn on unregisterised by default for alpha, hppa
Simon Marlow <[EMAIL PROTECTED]>**20060316165909] 
[remove accidental extra in previous patch
Simon Marlow <[EMAIL PROTECTED]>**20060316160322] 
[fix a warning
Simon Marlow <[EMAIL PROTECTED]>**20060316144914] 
[fix up Win32 build
Simon Marlow <[EMAIL PROTECTED]>**20060316144856] 
[sanity checking: make sure we don't mix registerised and unreg'd code
Simon Marlow <[EMAIL PROTECTED]>**20060316142727] 
[fix non-threaded way
Simon Marlow <[EMAIL PROTECTED]>**20060316135809] 
[Free all memory when shutting down.  XXX not implemented for Posix.
[EMAIL PROTECTED] 
[Improvements to forkProcess()
Simon Marlow <[EMAIL PROTECTED]>**20060316125538
 fixes failures in yesterday's testsuite run
] 
[discardTask(): reset task->tso to avoid confusion later
Simon Marlow <[EMAIL PROTECTED]>**20060316125256] 
[Improvements to shutting down of the runtime
Simon Marlow <[EMAIL PROTECTED]>**20060315145041
 Yet another attempt at shutdown & interruption.  This one appears to
 work better; ^C is more responsive in multi threaded / SMP, and I
 fixed one case where the runtime wasn't responding to ^C at all.
] 
[improve panic messages a bit, with the GHC version and platform
Simon Marlow <[EMAIL PROTECTED]>**20060314170813] 
[Bug fixes in my refactored RnNames code.
Lemmih <[EMAIL PROTECTED]>**20060314160026] 
[ENTER(): avoid re-reading the info pointer of the closure when entering it
Simon Marlow <[EMAIL PROTECTED]>**20060314114153
 This fixes another instance of a subtle SMP bug (see patch "really
 nasty bug in SMP").
] 
[small improvements to the debug printer
Simon Marlow <[EMAIL PROTECTED]>**20060314112604] 
[Make it a fatal error to try to enter a PAP
Simon Marlow <[EMAIL PROTECTED]>**20060314112550
 This is just an assertion, in effect: we should never enter a PAP, but
 for convenience we previously attached the PAP apply code to the PAP
 info table.  The problem with this was that it makes it harder to track
 down bugs that result in entering a PAP...
] 
[Fix a really nasty bug in SMP
Simon Marlow <[EMAIL PROTECTED]>**20060314112119
 In SMP mode a THUNK can change to an IND at any time.  The generic
 apply code (stg_ap_p etc.) examines a closure to determine how to
 apply it to its arguments, if it is a THUNK it must enter it first in
 order to evaluate it.  The problem was that in order to enter the
 THUNK, we were re-reading the info pointer, and possibly ending up
 with an IND instead of the original THUNK.  It isn't safe to enter the
 IND, because it points to a function (functions are never "entered",
 only applied).  Solution: we must not re-read the info pointer.
] 
[fix bug in previous patch to this file
Simon Marlow <[EMAIL PROTECTED]>**20060313155347] 
[add another SMP assertion
Simon Marlow <[EMAIL PROTECTED]>**20060313154102] 
[fix a rather subtle SMP bug in anyWorkForMe()
Simon Marlow <[EMAIL PROTECTED]>**20060313154044] 
[Enable shortcutting of stack squeezing
Simon Marlow <[EMAIL PROTECTED]>**20060310204449
 Not sure why it was disabled, probably by accident.
] 
[extra sanity checking: call checkTSO() in resumeThread()
Simon Marlow <[EMAIL PROTECTED]>**20060310204343] 
[Give WHITEHOLE the BLACKHOLE closure type, instead of INVALID_OBJECT
Simon Marlow <[EMAIL PROTECTED]>**20060310204256
 Just to keep sanity checking happy, and so we don't need a completely
 new closure type.
] 
[Look for a package.conf.d directory containing per-package .conf files
Simon Marlow <[EMAIL PROTECTED]>**20060313133211
 Contributed by Duncan Coutts, with changes to merge into the HEAD.
 This isn't the full deal, ghc-pkg still modifies files only, but it's
 enough to help the Gentoo folk along.
] 
[Move the very broad "i[[3456]]86-*-gnu*" HostPlatform pattern to the end.
Ian Lynagh <[EMAIL PROTECTED]>**20060307161140] 
[fix the build with GHC 6.4 (not 6.4.1)
Simon Marlow <[EMAIL PROTECTED]>**20060310110409] 
[Wibble in HscMain.
Lemmih <[EMAIL PROTECTED]>**20060310021442] 
[Initial foundation for quickcheck tests.
Lemmih <[EMAIL PROTECTED]>**20060310020514
 
 I have no idea how to use the testsuite so I'll start
 making QuickCheck tests instead.
 I've included tests for 'HeaderInfo.getOptions'.
 
] 
[Parse OPTIONS properly and cache the result.
Lemmih <[EMAIL PROTECTED]>**20060310011035
 
 Use the lexer to parse OPTIONS, LANGUAGE and INCLUDE pragmas.
 This gives us greater flexibility and far better error
 messages. However, I had to make a few quirks:
   * The token parser is written manually since Happy doesn't
     like lexer errors (we need to extract options before the
     buffer is passed through 'cpp'). Still better than
     manually parsing a String, though.
   * The StringBuffer API has been extended so files can be
     read in blocks.
 I also made a new field in ModSummary called ms_hspp_opts
 which stores the updated DynFlags. Oh, and I took the liberty
 of moving 'getImports' into HeaderInfo together with
 'getOptions'.
 
] 
[Fix -ddump-if-trace
Lemmih <[EMAIL PROTECTED]>**20060308175210] 
[Bug fix in the new HscMain code.
Lemmih <[EMAIL PROTECTED]>**20060308175036
 
 I'm not sure what really happens here but this is how it's
 done in the old HscMain code and it appears to work.
 
] 
[fix one #ifdef SMP that didn't get turned into #ifdef THREADED_RTS
Simon Marlow <[EMAIL PROTECTED]>**20060307095949] 
[x86_64: add -fno-builtin to gcc command line for .hc files.
Simon Marlow <[EMAIL PROTECTED]>**20060307093800
 This seems to be required now that we're stealing more registers.
] 
[More work thrown at HscMain.
Lemmih <[EMAIL PROTECTED]>**20060307073736
 
 MkIface.writeIfaceFile doesn't check GhcMode anymore. All it does
 is what the name say: write an interface to disk.
 I've refactored HscMain so the logic is easier to manage. That means
 we can avoid running the simplifier when typechecking (: And best of
 all, HscMain doesn't use GhcMode at all, anymore!
 
 The new HscMain intro looks like this:
 
 It's the task of the compilation proper to compile Haskell, hs-boot and
 core files to either byte-code, hard-code (C, asm, Java, ect) or to
 nothing at all (the module is still parsed and type-checked. This
 feature is mostly used by IDE's and the likes).
 Compilation can happen in either 'one-shot', 'batch', 'nothing',
 or 'interactive' mode. 'One-shot' mode targets hard-code, 'batch' mode
 targets hard-code, 'nothing' mode targets nothing and 'interactive' mode
 targets byte-code.
 The modes are kept separate because of their different types and meanings.
 In 'one-shot' mode, we're only compiling a single file and can therefore
 discard the new ModIface and ModDetails. This is also the reason it only
 targets hard-code; compiling to byte-code or nothing doesn't make sense
 when we discard the result.
 'Batch' mode is like 'one-shot' except that we keep the resulting ModIface
 and ModDetails. 'Batch' mode doesn't target byte-code since that require
 us to return the newly compiled byte-code.
 'Nothing' mode has exactly the same type as 'batch' mode but they're still
 kept separate. This is because compiling to nothing is fairly special: We
 don't output any interface files, we don't run the simplifier and we don't
 generate any code.
 'Interactive' mode is similar to 'batch' mode except that we return the
 compiled byte-code together with the ModIface and ModDetails.
 
] 
[Make it clear when the symbols are using by the interpreter.
Lemmih <[EMAIL PROTECTED]>**20060306033426] 
[Use Darwin-compatible x86 assembly syntax in SMP.h (lock/cmpxchg with a slash)
[EMAIL PROTECTED] 
[Darwin/x86: Implement object splitting
[EMAIL PROTECTED] 
[Mach-O Linker: handle multiple import sections
[EMAIL PROTECTED]
 
 In the rare event that a .o file contains more than one flavour of a
 [non]lazy pointers sections, resolve all of them, not just one.
] 
[Import symbols needed by the interpreter.
Lemmih <[EMAIL PROTECTED]>**20060306013926] 
[The parser needs a set of parentheses when we don't use unsafeCoerce.
Lemmih <[EMAIL PROTECTED]>**20060305173539] 
['have_object' isn't needed in a typed environment.
Lemmih <[EMAIL PROTECTED]>**20060304191410] 
[FIXME's.
Lemmih <[EMAIL PROTECTED]>**20060304185435] 
[Why name a function 'getGhciMode' when it returns GhcMode?
Lemmih <[EMAIL PROTECTED]>**20060304165303
 
 I've changed the name to 'getGhcMode'. If someone changes
 it back, please write an explanation above it.
 
] 
[Enumerate imports and remove dead code.
Lemmih <[EMAIL PROTECTED]>**20060304134150] 
[Use hscCodeGenNothing instead of hscCodeGenSimple.
Lemmih <[EMAIL PROTECTED]>**20060304133008] 
[Comments and esthetical changes.
Lemmih <[EMAIL PROTECTED]>**20060304132712] 
[Remove the old HscMain code.
Lemmih <[EMAIL PROTECTED]>**20060304130327] 
[Use the new HscMain API in DriverPipeline.
Lemmih <[EMAIL PROTECTED]>**20060304124111] 
[Export the new HscMain API.
Lemmih <[EMAIL PROTECTED]>**20060304124051] 
[Allow hscCompileMake to target HscNothing.
Lemmih <[EMAIL PROTECTED]>**20060304123957] 
[Description of the new HscMain.
Lemmih <[EMAIL PROTECTED]>**20060304123555] 
[Initial hack on the new low-level compiler API.
Lemmih <[EMAIL PROTECTED]>**20060304002440
 
 None of the new code is in use yet.
 
 The current Haskell compiler (HscMain.hscMain) isn't as typed
 and as hack-free as we'd like. Here's a list of the things it
 does wrong:
   * In one shot mode, it returns the new interface as _|_,
     when recompilation isn't required. It's then up to the
     users of hscMain to keep their hands off the result.
   * (Maybe ModIface) is passed around when it's known that it's
     a Just. Hey, we got a type-system, let's use it.
   * In one shot mode, the backend is returning _|_ for the
     new interface. This is done to prevent space leaks since
     we know that the result of a one shot compilation is never
     used. Again, it's up to the users of hscMain to keep their
     hands off the result.
   * It is allowed to compile a hs-boot file to bytecode even
     though that doesn't make sense (it always returns
     Nothing::Maybe CompiledByteCode).
   * Logic and grunt work is completely mixed. The frontend
     and backend keeps checking what kind of input they're handling.
     This makes it very hard to get an idea of what the functions
     actually do.
   * Extra work is performed when using a null code generator.
 
 
 The new code refactors out the frontends (Haskell, Core), the
 backends (Haskell, boot) and the code generators (one-shot, make,
 nothing, interactive) and allows them to be combined in typesafe ways.
 A one-shot compilation doesn't return new interfaces at all so we
 don't need the _|_ space-leak hack. In 'make' mode (when not
 targeting bytecode) the result doesn't contain
 Nothing::Maybe CompiledByteCode. In interactive mode, the result
 is always a CompiledByteCode. The code gens are completely separate
 so compiling to Nothing doesn't perform any extra work.
 
 DriverPipeline needs a bit of work before it can use the new
 API.
 
 
] 
[callerSaveVolatileRegs: fix the Nothing case
Simon Marlow <[EMAIL PROTECTED]>**20060303133135
 When the volatile regs attached to a CmmCall is Nothing, it means
 "save everything", not "save nothing".
] 
[Darwin/x86: Support __IMPORT segments in the Linker
[EMAIL PROTECTED] 
[Darwin/x86 Mangler: Make sure each imported symbol stub gets a separate chunk.
[EMAIL PROTECTED] 
[Darwin/x86: Print 64-bit literals in a way Apple understands.
[EMAIL PROTECTED] 
[Darwin/x86: Handle IMPORT sections in mangler
[EMAIL PROTECTED] 
[Fix free-variable finder
[EMAIL PROTECTED]
 
 After a long hunt I discovered that the reason that GHC.Enum.eftIntFB
 was being marked as a loop-breaker was the bizare behaviour of exprFreeVars,
 which returned not only the free variables of an expression but also the
 free variables of RULES attached to variables occuring in the expression!
 
 This was clearly deliberate (the comment was CoreFVs rev 1.1 in 1999) but
 I've removed it; I've left the comment with further notes in case there
 turns out to be a Deep Reason.
 
 
] 
[Make -split-objs work with --make
Simon Marlow <[EMAIL PROTECTED]>**20060302170505
 This turned out to be a lot easier than I thought.  Just moving a few
 bits of -split-objs support from the build system into the compiler
 was enough.  The only thing that Cabal needs to do in order to support
 -split-objs now is to pass the names of the split objects rather than
 the monolithic ones to 'ar'.
] 
[fix for compiling the base package with --make
Simon Marlow <[EMAIL PROTECTED]>**20060302163059] 
[replace several 'fromJust's with 'expectJust's
Simon Marlow <[EMAIL PROTECTED]>**20060302141628] 
[minor cleanup; remove one use of fromJust
Simon Marlow <[EMAIL PROTECTED]>**20060302140818] 
[Sigh: one more fix to undoing the erroneous patch
[EMAIL PROTECTED] 
[Remember the free vars in HsRule.
Lemmih <[EMAIL PROTECTED]>**20060301194145] 
[Complete undo of Simplify-the-IdInfo-before-any-RHSs
[EMAIL PROTECTED] 
[Disable the NCG if GhcUnregisterised=YES
Simon Marlow <[EMAIL PROTECTED]>**20060301165341
 The NCG cannot be used in an unregisterised compiler, so there's no
 point in including it.
] 
[Undo patch Simplify-the-IdInfo-before-any-RHSs
[EMAIL PROTECTED]
 
 Sadly the above patch wasn't right, because it fouls
 up pre/postInlineUnconditionally.  This patch puts
 things back as they were functionally, but with slightly
 tidied-up code.
 
] 
[fix parse error
Simon Marlow <[EMAIL PROTECTED]>**20060301160701] 
[fix compilation with older GHCs
Simon Marlow <[EMAIL PROTECTED]>**20060301140931] 
[update docs w.r.t. dllMain() definition (EXTFUN is no more)
Simon Marlow <[EMAIL PROTECTED]>**20060301130736] 
[add comments
Simon Marlow <[EMAIL PROTECTED]>**20060301132018] 
[add ':set prompt' command
Simon Marlow <[EMAIL PROTECTED]>**20060301131948
 
 contributed by Neil Mitchell <[EMAIL PROTECTED]>, with docs by me.
] 
[Add support for Data.Char.generalCategory to libcompat
Simon Marlow <[EMAIL PROTECTED]>**20060301113536
 
 this is so that the stage1 compiler has proper support for Unicode.
 Should fix these errors:
 
   lexical error in string/character literal at character '\8759'
 
 when building the stage2 compiler.
] 
[takeMVar/putMVar were missing some write barriers when modifying a TSO
Simon Marlow <[EMAIL PROTECTED]>**20060228163724
 
 This relates to the recent introduction of clean/dirty TSOs, and the
 consqeuent write barriers required.  We were missing some write
 barriers in the takeMVar/putMVar family of primops, when performing
 the take/put directly on another TSO.
 
 Fixes #705, and probably some test failures.
] 
[A better x86_64 register mapping, with more argument registers.
Simon Marlow <[EMAIL PROTECTED]>**20060228153640
 
 Now that we can handle using C argument registers as global registers,
 extend the x86_64 register mapping.  We now have 5 integer argument
 registers, 4 float, and 2 double (all caller-saves).  This results in a
 reasonable speedup on x86_64.
] 
[filter the messages generated by gcc
Simon Marlow <[EMAIL PROTECTED]>**20060228153134
 
 Eliminate things like "warning: call-clobbered register used as global
 register variable", which is an non-suppressible warning from gcc.
] 
[Allow C argument regs to be used as global regs (R1, R2, etc.)
Simon Marlow <[EMAIL PROTECTED]>**20060228152942
 
 The problem here was that we generated C calls with expressions
 involving R1 etc. as parameters.  When some of the R registers are
 also C argument registers, both GCC and the native code generator
 generate incorrect code.  The hacky workaround is to assign
 problematic arguments to temporaries first; fortunately this works
 with both GCC and the NCG, but we have to be careful not to undo this
 with later optimisations (see changes to CmmOpt).
] 
[pass arguments to unknown function calls in registers
Simon Marlow <[EMAIL PROTECTED]>**20060228152524
 
 We now have more stg_ap entry points: stg_ap_*_fast, which take
 arguments in registers according to the platform calling convention.
 This is faster if the function being called is evaluated and has the
 right arity, which is the common case (see the eval/apply paper for
 measurements).  
 
 We still need the stg_ap_*_info entry points for stack-based
 application, such as an overflows when a function is applied to too
 many argumnets.  The stg_ap_*_fast functions actually just check for
 an evaluated function, and if they don't find one, push the args on
 the stack and invoke stg_ap_*_info.  (this might be slightly slower in
 some cases, but not the common case).
] 
[fix live register annotations on foreign calls
Simon Marlow <[EMAIL PROTECTED]>**20060228151815
 
 fix one incorrect case, and made several more accurate
] 
[	Simplify the IdInfo before any RHSs
[EMAIL PROTECTED]
 	~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Simplfy (i.e. substitute) the IdInfo of a recursive group of Ids
 before looking at the RHSs of *any* of them.  That way, the rules
 are available throughout the letrec, which means we don't have to
 be careful about function to put first.
 
 Before, we just simplified the IdInfo of f before looking at f's RHS,
 but that's not so good when f and g both have RULES, and both rules
 mention the other.
 
 This change makes things simpler, but shouldn't change performance.
 
] 
[Add floating-point symbols to the list
[EMAIL PROTECTED] 
[slightly better dependencies for GenApply.hs
Simon Marlow <[EMAIL PROTECTED]>**20060227153828] 
[x86_64: include .type and .size directives in the output, for valgrind
Simon Marlow <[EMAIL PROTECTED]>**20060227152822] 
[The initStablePtrTable should be called before ACQUIRE_LOCK(&stable_mutex)
[EMAIL PROTECTED] 
[support LOCK_DEBUG for Windows
[EMAIL PROTECTED] 
[mmap() errors on Darwin: use errorBelch/exit instead of barf()
Simon Marlow <[EMAIL PROTECTED]>**20060227111103
 
 The most likely cause is out-of-memory, not an RTS error.
] 
[remove empty .SECONDARY target
Simon Marlow <[EMAIL PROTECTED]>**20060227105939
 
 This works around a problem with recent versions of GNU make that take
 a long time when all targets are declared intermediate with
 .SECONDARY.  See 
 
   https://savannah.gnu.org/bugs/?func=detailitem&item_id=15584
 
 for discussion of the GNU make issue.
] 
[these tables have four columns, not three
[EMAIL PROTECTED] 
[Remove comment about imports and exports not being in the renamer result.
Lemmih <[EMAIL PROTECTED]>**20060226120407] 
[NCG: fix mkRegRegMoveInstr for x86-64
[EMAIL PROTECTED] 
[NCG: Fix Typo in Register Allocator Loop Patch
[EMAIL PROTECTED]
 
 Fix previous patch "NCG: Handle loops in register allocator"
 Of course, I broke it when correcting a style problem just before committing.
] 
[NCG: Handle loops in register allocator
[EMAIL PROTECTED]
 
 Fill in the missing parts in the register allocator so that it can
 handle loops.
 
 *) The register allocator now runs in the UniqSuppy monad, as it needs
    to be able to generate unique labels for fixup code blocks.
 
 *) A few functions have been added to RegAllocInfo:
 	mkRegRegMoveInstr -- generates a good old move instruction
 	mkBranchInstr     -- used to be MachCodeGen.genBranch
 	patchJump         -- Change the destination of a jump
 
 *) The register allocator now makes sure that only one spill slot is used
    for each temporary, even if it is spilled and reloaded several times.
    This obviates the need for memory-to-memory moves in fixup code.
 
 LIMITATIONS:
 
 *) The case where the fixup code needs to cyclically permute a group of
    registers is currently unhandled. This will need more work once we come
    accross code where this actually happens.
 
 *) Register allocation for code with loop is probably very inefficient
    (both at compile-time and at run-time).
 
 *) We still cannot compile the RTS via NCG, for various other reasons.
 
] 
[Oops, I got a little trigger happy while trimming package.conf.in.
Lemmih <[EMAIL PROTECTED]>**20060224223704] 
[Prettify parts of RnNames. No change of functionality.
Lemmih <[EMAIL PROTECTED]>**20060224215020] 
[Remove duplicate code from RnNames.
Lemmih <[EMAIL PROTECTED]>**20060224212748] 
[Remove non-existing modules from package.conf.in
Lemmih <[EMAIL PROTECTED]>**20060224203727] 
[Remove some unused bindings frm RnNames.
Lemmih <[EMAIL PROTECTED]>**20060224165409] 
[Rather large refactoring of RnNames.
Lemmih <[EMAIL PROTECTED]>**20060224154704
 
 This restructoring makes the renamed export and import lists
 available in IDE mode.
 
] 
[add file to go with "extract some of the generic..." patch
Simon Marlow <[EMAIL PROTECTED]>**20060224144126] 
[oops, undo accidental addition of package-time settings
Simon Marlow <[EMAIL PROTECTED]>**20060224143051] 
[turn off a trace
Simon Marlow <[EMAIL PROTECTED]>**20060224124608] 
[add instance Outputable CLabel
Simon Marlow <[EMAIL PROTECTED]>**20060224124349] 
[-O2 implies -optc-O2 now
Simon Marlow <[EMAIL PROTECTED]>**20060224124033] 
[extract some of the generic C-- optimisations from the NCG
Simon Marlow <[EMAIL PROTECTED]>**20060224111753] 
[lag/drag/void: add an extra assertion, and some commentary
Simon Marlow <[EMAIL PROTECTED]>**20060223155120] 
[lag/drag/void profiling fix
Simon Marlow <[EMAIL PROTECTED]>**20060223155046
 
 We were searching the wrong part of the heap for dead objects, this
 was broken by recent changes to the step structure: from-space is now
 in step->old_blocks, not step->blocks.  Fortunately some assertions in
 ProfHeap picked up the problem.
] 
[add (trivial) support for STM objects in lag/drag/void profiling
Simon Marlow <[EMAIL PROTECTED]>**20060223154859] 
[bugfix for LDV profiling on 64-bit platforms
Simon Marlow <[EMAIL PROTECTED]>**20060223150904
 
 There was an integer overflow in the definition of LDV_RECORD_CREATE
 when StgWord is 64 bits.
] 
[warning fix
Simon Marlow <[EMAIL PROTECTED]>**20060223144537] 
[further fix for floating point primitives
Simon Marlow <[EMAIL PROTECTED]>**20060223143013] 
[Comment wibbles
[EMAIL PROTECTED] 
[Wibbles to instance validity checking
[EMAIL PROTECTED] 
[Fix comment
[EMAIL PROTECTED] 
[Improve error reporting for type-improvement errors
[EMAIL PROTECTED] 
[Reject polytypes in instance declarations (for now anyway)
[EMAIL PROTECTED] 
[Remove duplicate comment
[EMAIL PROTECTED] 
[Add renamed fixities to HsGroup.
Lemmih <[EMAIL PROTECTED]>**20060222173648] 
[oops, initialize atomic_modify_mutvar_mutex
Simon Marlow <[EMAIL PROTECTED]>**20060222163827] 
[check black holes before doing GC in scheduleDoHeapProfile()
Simon Marlow <[EMAIL PROTECTED]>**20060222160733
 
 fixes #687, see comment for details.
] 
[fix for ASSIGN_BaseReg() in the unregisterised way
Simon Marlow <[EMAIL PROTECTED]>**20060222141836] 
[floating-point fix for x86_64
Simon Marlow <[EMAIL PROTECTED]>**20060222140719
   
 For 32-bit float primtives like sinFloat#, we currently call the
 double versions of the C library functions (sin(), cos() etc.).  It
 seems more correct to call the float versions (sinf(), cosf() etc.).
 This makes a difference on x86_64, I'm not entirely sure why, but this
 way at least generates more consistent results and avoids extra
 promotion/demotion instructions when calling these primitives.
 
] 
[fix a deadlock in atomicModifyMutVar#
Simon Marlow <[EMAIL PROTECTED]>**20060221163711
 
 atomicModifyMutVar# was re-using the storage manager mutex (sm_mutex)
 to get its atomicity guarantee in SMP mode. But recently the addition
 of a call to dirty_MUT_VAR() to implement the read barrier lead to a
 rare deadlock case, because dirty_MUT_VAR() very occasionally needs to
 allocate a new block to chain on the mutable list, which requires
 sm_mutex.
] 
[warning fix
Simon Marlow <[EMAIL PROTECTED]>**20060221163308] 
[Mention the 'Encoding' module in package.conf.in
Lemmih <[EMAIL PROTECTED]>**20060221105147] 
[Loosen the rules for instance declarations (Part 3)
Ross Paterson <[EMAIL PROTECTED]>**20060213161044
 
 Relax the restrictions on derived instances in the same way, so we
 can write
 
 	data MinHeap h a = H a (h a) deriving (Show)
] 
[If we don't have libreadline then we need some dummy definition for complete* functions.
[EMAIL PROTECTED] 
[SMP bugfix: reload capability from task->cap after scheduleDoGC
[EMAIL PROTECTED] 
[SMP support (xchg(), cas() and mb()) for PowerPC
[EMAIL PROTECTED] 
[Bugfix in completion code for :set and :unset.
Lemmih <[EMAIL PROTECTED]>**20060210181319] 
[Completion for :set, :unset and :undef.
Lemmih <[EMAIL PROTECTED]>**20060210171728] 
[oops, forgot some more SMP->THREADED_RTS conversions
Simon Marlow <[EMAIL PROTECTED]>**20060210153236] 
[fix test for REG_BaseReg (it's spelled REG_Base)
Simon Marlow <[EMAIL PROTECTED]>**20060210123552] 
[fix for dirty_MUT_VAR: don't try to recordMutableCap in gen 0
Simon Marlow <[EMAIL PROTECTED]>**20060210120021] 
[STM fix from Tim Harris
Simon Marlow <[EMAIL PROTECTED]>**20060210112111
 
 Fixes assertion failures with STM and -debug.  Tim says:
 Sorry, it's a problem in how nested transactions are handled in
 non-SMP builds.  It'll bite when trying to commit a nested transaction
 which has read from a TVar but not updated it.
 
 The call to validate_and_acquire_ownership in
 stmCommitNestedTransaction should be the same as that in
 stmCommitNestedTransaction, i.e.:
 
   result = validate_and_acquire_ownership(trec, (!use_read_phase), TRUE);
 
] 
[improvement to the deadlock detection
Simon Marlow <[EMAIL PROTECTED]>*-20060209123056
 
 When the RTS is idle, as detected by the timer signal, instead of
 prodding capabilities from the signal handler (which is not guaranteed
 to work - pthread_cond_signal() can't be called from signal handlers),
 create a new thread to do it.
] 
[Simplify the -B handling. The interface to the ghc library has changed slightly.
Lemmih <[EMAIL PROTECTED]>**20060210094601] 
[Fix desugaring of unboxed tuples
[EMAIL PROTECTED]
 
 This patch is a slightly-unsatisfactory fix to desugaring unboxed
 tuples; it fixes ds057 which has been failing for some time.
 
 Unsatisfactory because rather ad hoc -- but that applies to lots
 of the unboxed tuple stuff. 
 
] 
[x86_64: fix case of out-of-range operands to leaq
Simon Marlow <[EMAIL PROTECTED]>**20060209162247] 
[Merge the smp and threaded RTS ways
Simon Marlow <[EMAIL PROTECTED]>**20060209154449
 
 Now, the threaded RTS also includes SMP support.  The -smp flag is a
 synonym for -threaded.  The performance implications of this are small
 to negligible, and it results in a code cleanup and reduces the number
 of combinations we have to test.
] 
[change dirty_MUT_VAR() to use recordMutableCap()
Simon Marlow <[EMAIL PROTECTED]>**20060209150420
 rather than recordMutableGen(), the former works better in SMP
] 
[improvement to the deadlock detection
Simon Marlow <[EMAIL PROTECTED]>**20060209123056
 
 When the RTS is idle, as detected by the timer signal, instead of
 prodding capabilities from the signal handler (which is not guaranteed
 to work - pthread_cond_signal() can't be called from signal handlers),
 create a new thread to do it.
] 
[Fix typo
[EMAIL PROTECTED] 
[Fix instance rules for functional dependencies
[EMAIL PROTECTED]
 
 GHC 6.4 implements a rather relaxed version of the Coverage Condition
 which is actually too relaxed: the compiler can get into an infinite loop
 as a result.
 
 This commit fixes the problem (see Note [Coverage condition] in FunDeps.lhs)
 and documents the change.
 
 I also took the opportunity to add documentation about functional dependencies,
 taken from the Hugs manual with kind permission of Mark Jones
 
] 
[fix for the unregisterised way
Simon Marlow <[EMAIL PROTECTED]>**20060209105058
 
 We always assign to BaseReg on return from resumeThread(), but in
 cases where BaseReg is not an lvalue (eg. unreg) we need to disable
 this assigment.  See comments for more details.
] 
[prof/smp combination probably doesn't work, disable it
Simon Marlow <[EMAIL PROTECTED]>**20060209104815] 
[tiny panic msg fix
Simon Marlow <[EMAIL PROTECTED]>**20060209102540] 
[Loosen the rules for instance declarations (Part 2)
[EMAIL PROTECTED]
 
 Tidying up to Ross's  patch, plus adding documenation for it.
 
 
] 
[relaxed instance termination test
Ross Paterson <[EMAIL PROTECTED]>**20060206111651
 
 With -fglasgow-exts but not -fallow-undecidable-instances, GHC 6.4
 requires that instances be of the following form:
 
  (1) each assertion in the context must constrain distinct variables
      mentioned in the head, and
 
  (2) at least one argument of the head must be a non-variable type.
 
 This patch replaces these rules with the requirement that each assertion
 in the context satisfy
 
  (1) no variable has more occurrences in the assertion than in the head, and
 
  (2) the assertion has fewer constructors and variables (taken together
      and counting repetitions) than the head.
 
 This allows all instances permitted by the old rule, plus such instances as
 
        instance C a
        instance Show (s a) => Show (Sized s a)
        instance (Eq a, Show b) => C2 a b
        instance C2 Int a => C3 Bool [a]
        instance C2 Int a => C3 [a] b
        instance C4 a a => C4 [a] [a]
 
 but still ensures that under any substitution assertions in the context
 will be smaller than the head, so context reduction must terminate.
 
 This is probably the best we can do if we consider each instance in
 isolation.
] 
[Fix CPP failure by adding space before hASH_TBL_SIZE
[EMAIL PROTECTED] 
[Change CVS for _darcs in dirs to prune during make dist
Duncan Coutts <[EMAIL PROTECTED]>**20060209093204] 
[an LDV profiling fix (might just fix ASSERTIONs, I'm not sure)
Simon Marlow <[EMAIL PROTECTED]>**20060208170744] 
[Do type refinement in TcIface
[EMAIL PROTECTED]
 
 This commit fixes a bug in 6.4.1 and the HEAD.  Consider this code,
 recorded **in an interface file**
 
     \(x::a) -> case y of 
 	         MkT -> case x of { True -> ... }
 (where MkT forces a=Bool)
 
 In the "case x" we need to know x's type, because we use that
 to find which module to look for "True" in. x's type comes from
 the envt, so we must refine the envt.  
 
 The alternative would be to record more info with an IfaceCase,
 but that would change the interface file format.
 
 (This stuff will go away when we have proper coercions.)
 	
] 
[Add mapOccEnv
[EMAIL PROTECTED] 
[A little more debug printing
[EMAIL PROTECTED] 
[Show types of case result when debug is on
[EMAIL PROTECTED] 
[fix installation of binary dist when the PS docs aren't present
Simon Marlow <[EMAIL PROTECTED]>**20060208153259
 
 Fixes #660
] 
[fix a bug in closure_sizeW_()
Simon Marlow <[EMAIL PROTECTED]>**20060208145451] 
[make the smp way RTS-only, normal libraries now work with -smp
Simon Marlow <[EMAIL PROTECTED]>**20060208143348
 
 We had to bite the bullet here and add an extra word to every thunk,
 to enable running ordinary libraries on SMP.  Otherwise, we would have
 needed to ship an extra set of libraries with GHC 6.6 in addition to
 the two sets we already ship (normal + profiled), and all Cabal
 packages would have to be compiled for SMP too.  We decided it best
 just to take the hit now, making SMP easily accessible to everyone in
 GHC 6.6.
 
 Incedentally, although this increases allocation by around 12% on
 average, the performance hit is around 5%, and much less if your inner
 loop doesn't use any laziness.
] 
[add -dfaststring-stats to dump some stats about the FastString hash table
Simon Marlow <[EMAIL PROTECTED]>**20060208131018] 
[fix a warning
Simon Marlow <[EMAIL PROTECTED]>**20060207132323] 
[catch up with changes to Distribution.ParseUtils.ParseResult
Simon Marlow <[EMAIL PROTECTED]>**20060207111111] 
[Wibble to type signature
[EMAIL PROTECTED] 
[Empty forall should disable implicit quantification
[EMAIL PROTECTED] 
[Remove unused constructor in SourceTypeCtxt
[EMAIL PROTECTED] 
[Basic completion in GHCi
Simon Marlow <[EMAIL PROTECTED]>**20060206122654
 
 This patch adds completion support to GHCi when readline is being
 used.  Completion of identifiers (in scope only, but including
 qualified identifiers) in expressions is provided.  Also, completion
 of commands (:cmd), and special completion for certain commands
 (eg. module names for the :module command) are also provided.
] 
[Improve error report for pattern guards
[EMAIL PROTECTED] 
[Add bang patterns
[EMAIL PROTECTED]
 
 This commit adds bang-patterns, 
 	enabled by -fglasgow-exts or -fbang-patterns
 	diabled by -fno-bang-patterns
 
 The idea is described here
 	http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatterns
 
] 
[Add Bag.anyBag (analogous to List.any)
[EMAIL PROTECTED] 
[Deal correctly with lazy patterns and GADTs
[EMAIL PROTECTED] 
[Record the type in TuplePat (necessary for GADTs)
[EMAIL PROTECTED]
 
 We must record the type of a TuplePat after typechecking, just like a ConPatOut,
 so that desugaring works correctly for GADTs. See comments with the declaration
 of HsPat.TuplePat, and test gadt15
 
] 
[Improve error reporting in Core Lint
[EMAIL PROTECTED] 
[don't clean ghc-inplace when cleaning stages other than 1
Simon Marlow <[EMAIL PROTECTED]>**20060202124359] 
[Improve error reporting in typechecker
[EMAIL PROTECTED] 
[Trim imports
[EMAIL PROTECTED] 
[Yet another fix to an old hi-boot-6 file
[EMAIL PROTECTED] 
[Kinding wibble in TH brackets
[EMAIL PROTECTED] 
[Use extraGHCiLibraries (if supplied) in GHCi linker rather than extraLibraries
Duncan Coutts <[EMAIL PROTECTED]>**20051207105654
 Also extend the parser.
] 
[combine libraries/.darcs-boring and .darcs-boring
Simon Marlow <[EMAIL PROTECTED]>**20060131161530] 
[Fix long-standing bug in CPR analysis
[EMAIL PROTECTED]
 
 	MERGE TO STABLE
 
 For a long time (2002!) the CPR analysis done by
 dmdAnalTopRhs has been bogus.  In particular, it's possible
 for a newtype constructor to look CPR-ish when it simply isn't.
 
 This fixes it.  Test is stranal/newtype
 
 
 
] 
[More hi-boot-6 updates
[EMAIL PROTECTED] 
[Fix TcUnify.subFunTys in AppTy case
[EMAIL PROTECTED]
 
 subFunTys wasn't dealing correctly with the case where the type
 to be split was of form (a ty1), where a is a type variable.
 
 This shows up when compiling 
 	Control.Arrow.Transformer.Stream
 in package arrows.
 
 This commit fixes it.
 
 
] 
[Error message wibble
[EMAIL PROTECTED] 
[Add mkHsCoerce to avoid junk in typechecked code
[EMAIL PROTECTED]
 
 Avoiding identity coercions is a Good Thing generally, but
 it turns out that the desugarer has trouble recognising 
 'otherwise' and 'True' guards if they are wrapped in an
 identity coercion; and that leads to bogus overlap warnings.
 
] 
[Improve error messsage when argument count varies
[EMAIL PROTECTED] 
[fix bug #664 in printSample()
Simon Marlow <[EMAIL PROTECTED]>**20060130115301
 printSample() was attempting to round the fractional part of the time,
 but not propagated to the non-fractional part.  It's probably better not
 to attempt to round the time at all.
] 
[Fix hi-boot file for earlier versions of GHC
[EMAIL PROTECTED] 
[Fix typo in boxy matching
[EMAIL PROTECTED] 
[fix one case where -q wasn't honoured
Simon Marlow <[EMAIL PROTECTED]>**20060127104715] 
[Check for GMP.framework on all Darwin platforms, not just PPC
[EMAIL PROTECTED] 
[Simon's big boxy-type commit
[EMAIL PROTECTED]
 
 This very large commit adds impredicativity to GHC, plus
 numerous other small things.
   
 *** WARNING: I have compiled all the libraries, and
 ***	     a stage-2 compiler, and everything seems
 ***	     fine.  But don't grab this patch if you 
 ***	     can't tolerate a hiccup if something is
 ***	     broken.
   
 The big picture is this:
 
 a) GHC handles impredicative polymorphism, as described in the
    "Boxy types: type inference for higher-rank types and
    impredicativity" paper
 
 b) GHC handles GADTs in the new simplified (and very sligtly less
    epxrssive) way described in the
    "Simple unification-based type inference for GADTs" paper
 
   
 But there are lots of smaller changes, and since it was pre-Darcs
 they are not individually recorded.
   
 Some things to watch out for:
   
 c)   The story on lexically-scoped type variables has changed, as per
      my email.  I append the story below for completeness, but I 
      am still not happy with it, and it may change again.  In particular,
      the new story does not allow a pattern-bound scoped type variable
      to be wobbly, so (\(x::[a]) -> ...) is usually rejected.  This is
      more restrictive than before, and we might loosen up again.
   
 d)   A consequence of adding impredicativity is that GHC is a bit less
      gung ho about converting automatically between
   	(ty1 -> forall a. ty2)    and    (forall a. ty1 -> ty2)
      In particular, you may need to eta-expand some functions to make
      typechecking work again.
    
      Furthermore, functions are now invariant in their argument types,
      rather than being contravariant.  Again, the main consequence is
      that you may occasionally need to eta-expand function arguments when
      using higher-rank polymorphism.
   
 
 Please test, and let me know of any hiccups
 
 
 Scoped type variables in GHC
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 	January 2006
 
 0) Terminology.
    
    A *pattern binding* is of the form
 	pat = rhs
 
    A *function binding* is of the form
 	f pat1 .. patn = rhs
 
    A binding of the formm
 	var = rhs
    is treated as a (degenerate) *function binding*.
 
 
    A *declaration type signature* is a separate type signature for a
    let-bound or where-bound variable:
 	f :: Int -> Int
 
    A *pattern type signature* is a signature in a pattern: 
 	\(x::a) -> x
 	f (x::a) = x
 
    A *result type signature* is a signature on the result of a
    function definition:
 	f :: forall a. [a] -> a
 	head (x:xs) :: a = x
 
    The form
 	x :: a = rhs
    is treated as a (degnerate) function binding with a result
    type signature, not as a pattern binding.
 
 1) The main invariants:
 
      A) A lexically-scoped type variable always names a (rigid)
  	type variable (not an arbitrary type).  THIS IS A CHANGE.
         Previously, a scoped type variable named an arbitrary *type*.
 
      B) A type signature always describes a rigid type (since
 	its free (scoped) type variables name rigid type variables).
 	This is also a change, a consequence of (A).
 
      C) Distinct lexically-scoped type variables name distinct
 	rigid type variables.  This choice is open; 
 
 2) Scoping
 
 2(a) If a declaration type signature has an explicit forall, those type
    variables are brought into scope in the right hand side of the 
    corresponding binding (plus, for function bindings, the patterns on
    the LHS).  
 	f :: forall a. a -> [a]
 	f (x::a) = [x :: a, x]
    Both occurences of 'a' in the second line are bound by 
    the 'forall a' in the first line
 
    A declaration type signature *without* an explicit top-level forall
    is implicitly quantified over all the type variables that are
    mentioned in the type but not already in scope.  GHC's current
    rule is that this implicit quantification does *not* bring into scope
    any new scoped type variables.
 	f :: a -> a
 	f x = ...('a' is not in scope here)...
    This gives compatibility with Haskell 98
 
 2(b) A pattern type signature implicitly brings into scope any type
    variables mentioned in the type that are not already into scope.
    These are called *pattern-bound type variables*.
 	g :: a -> a -> [a]
 	g (x::a) (y::a) = [y :: a, x]
    The pattern type signature (x::a) brings 'a' into scope.
    The 'a' in the pattern (y::a) is bound, as is the occurrence on 
    the RHS.  
 
    A pattern type siganture is the only way you can bring existentials 
    into scope.
 	data T where
 	  MkT :: forall a. a -> (a->Int) -> T
 
 	f x = case x of
 		MkT (x::a) f -> f (x::a)
 
 2a) QUESTION
 	class C a where
 	  op :: forall b. b->a->a
 
 	instance C (T p q) where
 	  op = <rhs>
     Clearly p,q are in scope in <rhs>, but is 'b'?  Not at the moment.
     Nor can you add a type signature for op in the instance decl.
     You'd have to say this:
 	instance C (T p q) where
 	  op = let op' :: forall b. ...
 	           op' = <rhs>
 	       in op'
 
 3) A pattern-bound type variable is allowed only if the pattern's
    expected type is rigid.  Otherwise we don't know exactly *which*
    skolem the scoped type variable should be bound to, and that means
    we can't do GADT refinement.  This is invariant (A), and it is a 
    big change from the current situation.
 
 	f (x::a) = x	-- NO; pattern type is wobbly
 	
 	g1 :: b -> b
 	g1 (x::b) = x	-- YES, because the pattern type is rigid
 
 	g2 :: b -> b
 	g2 (x::c) = x	-- YES, same reason
 
 	h :: forall b. b -> b
 	h (x::b) = x	-- YES, but the inner b is bound
 
 	k :: forall b. b -> b
 	k (x::c) = x	-- NO, it can't be both b and c
 
 3a) You cannot give different names for the same type variable in the same scope
     (Invariant (C)):
 
 	f1 :: p -> p -> p		-- NO; because 'a' and 'b' would be
 	f1 (x::a) (y::b) = (x::a)	--     bound to the same type variable
 
 	f2 :: p -> p -> p		-- OK; 'a' is bound to the type variable
 	f2 (x::a) (y::a) = (x::a)	--     over which f2 is quantified
 					-- NB: 'p' is not lexically scoped
 
 	f3 :: forall p. p -> p -> p	-- NO: 'p' is now scoped, and is bound to
 	f3 (x::a) (y::a) = (x::a)	--     to the same type varialble as 'a'
 
 	f4 :: forall p. p -> p -> p	-- OK: 'p' is now scoped, and its occurences
 	f4 (x::p) (y::p) = (x::p)	--     in the patterns are bound by the forall
 
 
 3b) You can give a different name to the same type variable in different
     disjoint scopes, just as you can (if you want) give diferent names to 
     the same value parameter
 
 	g :: a -> Bool -> Maybe a
 	g (x::p) True  = Just x  :: Maybe p
 	g (y::q) False = Nothing :: Maybe q
 
 3c) Scoped type variables respect alpha renaming. For example, 
     function f2 from (3a) above could also be written:
 	f2' :: p -> p -> p
 	f2' (x::b) (y::b) = x::b
    where the scoped type variable is called 'b' instead of 'a'.
 
 
 4) Result type signatures obey the same rules as pattern types signatures.
    In particular, they can bind a type variable only if the result type is rigid
 
 	f x :: a = x	-- NO
 
 	g :: b -> b
 	g x :: b = x	-- YES; binds b in rhs
 
 5) A *pattern type signature* in a *pattern binding* cannot bind a 
    scoped type variable
 
 	(x::a, y) = ...		-- Legal only if 'a' is already in scope
 
    Reason: in type checking, the "expected type" of the LHS pattern is
    always wobbly, so we can't bind a rigid type variable.  (The exception
    would be for an existential type variable, but existentials are not
    allowed in pattern bindings either.)
  
    Even this is illegal
 	f :: forall a. a -> a
 	f x = let ((y::b)::a, z) = ... 
 	      in 
    Here it looks as if 'b' might get a rigid binding; but you can't bind
    it to the same skolem as a.
 
 6) Explicitly-forall'd type variables in the *declaration type signature(s)*
    for a *pattern binding* do not scope AT ALL.
 
 	x :: forall a. a->a	  -- NO; the forall a does 
 	Just (x::a->a) = Just id  --     not scope at all
 
 	y :: forall a. a->a
 	Just y = Just (id :: a->a)  -- NO; same reason
 
    THIS IS A CHANGE, but one I bet that very few people will notice.
    Here's why:
 
 	strange :: forall b. (b->b,b->b)
 	strange = (id,id)
 
 	x1 :: forall a. a->a
 	y1 :: forall b. b->b
 	(x1,y1) = strange
 
     This is legal Haskell 98 (modulo the forall). If both 'a' and 'b'
     both scoped over the RHS, they'd get unified and so cannot stand
     for distinct type variables. One could *imagine* allowing this:
    
 	x2 :: forall a. a->a
 	y2 :: forall a. a->a
 	(x2,y2) = strange
 
     using the very same type variable 'a' in both signatures, so that
     a single 'a' scopes over the RHS.  That seems defensible, but odd,
     because though there are two type signatures, they introduce just
     *one* scoped type variable, a.
 
 7) Possible extension.  We might consider allowing
 	\(x :: [ _ ]) -> <expr>
     where "_" is a wild card, to mean "x has type list of something", without
     naming the something.
 
] 
[add double colon and double arrow symbols (-fglasgow-exts)
Simon Marlow <[EMAIL PROTECTED]>**20060125135501] 
[Fix conDeclFVs for GADTs, to fix bogus unused-import warning
[EMAIL PROTECTED] 
[make the par# primop actually do something
Simon Marlow <[EMAIL PROTECTED]>**20060124162521] 
[Update Cachegrind support for changes to the Valgrind CLI
Simon Marlow <[EMAIL PROTECTED]>**20060124154732] 
[send usage info to stdout, not stderr
Simon Marlow <[EMAIL PROTECTED]>**20060124145551] 
[primop-docs
Dinko Tenev <[EMAIL PROTECTED]>**20060122222446] 
[remove old CVS stuff, replace with darcs
Simon Marlow <[EMAIL PROTECTED]>**20060120151322] 
[implement clean/dirty TSOs
Simon Marlow <[EMAIL PROTECTED]>**20060123164930
 Along the lines of the clean/dirty arrays and IORefs implemented
 recently, now threads are marked clean or dirty depending on whether
 they need to be scanned during a minor GC or not.  This should speed
 up GC when there are lots of threads, especially if most of them are
 idle.
] 
[Better error message for Template Haskell pattern brackets
[EMAIL PROTECTED] 
[remove old comment
Simon Marlow <[EMAIL PROTECTED]>**20060123140530] 
[Fix for feature request #655 (Loading the GHC library from GHCi.)
Lemmih <[EMAIL PROTECTED]>**20060123110625
 Moved the utility functions out of hschooks, avoided
 linking the GHC library with hschooks.o and
 added a couple of symbols to the linkers export list.
] 
[MFLAGS += -f Makefile
Simon Marlow <[EMAIL PROTECTED]>**20060123094837
 merged from CVS, because Tailor isn't merging the libraries subdir
] 
[undo accidental commit of snapshot version
Simon Marlow <[EMAIL PROTECTED]>**20060122175817] 
[Make hsc2hs emit the full path name in {-# LINE #-} pagmas.
Duncan Coutts <[EMAIL PROTECTED]>**20060122011831
 For one thing this is the right thing to do anyway, it's what other tools do.
 Secondly it allows haddock to produce accurate source code links.
] 
[TAG final switch to darcs, this repo is now live
Simon Marlow <[EMAIL PROTECTED]>**20060120134630] 
Patch bundle hash:
05fccd7450a4835cf0b55cc262a2fdcc9e9979f7
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to