For symmetry with exitFailure :: IO a. Should be pretty uncontroversial.
Patch attached. Consideration period: 2 weeks, or until there's no
traffic on the subject for a week.
------------------------------------------------------------------------
New patches:
[Add exitSuccess :: IO a. For symmetry with exitFailure
Don Stewart **20080213222644] {
hunk ./System/Exit.hs 16
-    ( 
+    (
hunk ./System/Exit.hs 20
+    , exitSuccess   -- :: IO a
hunk ./System/Exit.hs 77
+-- | The computation 'exitSuccess' is equivalent to
+-- 'exitWith' 'ExitSuccess', It terminates the program
+-- sucessfully.
+exitSuccess :: IO a
+exitSuccess = exitWith ExitSuccess
+
}
Context:
[untabify
Don Stewart **20080213221950] 
[untabify only
Don Stewart **20080213221856] 
[whitespace only
Don Stewart **20080207191939] 
[FIX dynamic001 dynamic002: isTupleTyCon had rotted
Simon Marlow **20080205103904
 In the patch "Tuple tycons have parens around their names", the names
 of the tuple tycons were changed to include parens, but isTupleTyCon
 was not updated to match, which made tuple types show as "(,) a b"
 rather than "(a,b)"
] 
[deforestation rules for enumFromThenTo; based on a patch from Robin Houston
Ian Lynagh **20080203152755] 
[Whitespace only
Don Stewart **20080207183954] 
[FIX #1936: hGetBufNonBlocking was blocking on stdin/stdout/stderr
Simon Marlow **20080124092203] 
[The default uncaught exception handler was adding an extra \n
Simon Marlow **20080124091216] 
[add comment about lack of _chsize_s()
Simon Marlow **20080123131248] 
[Windows: large file support for hFileSize and hSeek (#1771)
Simon Marlow **20080123102904
 
 
] 
[Export topHandler, topHandlerFastExit from GHC.TopHandler
Ian Lynagh **20080120182429
 We now use one of these in ghc when running with ghc -e
] 
[haddock attributes for haddock-2.0
Ross Paterson **20080120022308] 
[Data.List.sort: force elements from start to end.
Bertram Felgenhauer **20071121101458
 this prevents a stack overflow on  sort (take 10^6 [1..])
] 
[Fix comment on GHC.Ptr.minusPtr
simonpj@microsoft.com**20080109114736] 
[Remove redundant imports of GHC.Err
simonpj@microsoft.com**20080104091314
 
 GHC.Base SOURCE-imports GHC.Err, and re-exports 'error'.  So 
 other modules need only import GHC.Base.
 
 This doesn't change the fact that these other modules are all compiled
 before GHC.Err, so they are all part of the module loop that starts with
 GHC.Base and finishes with GHC.Err.  But it does reduce the occurrence
 of those SOURCE imports.
 
] 
[Generalise type of forever :: (Monad m) => m a -> m b
Don Stewart **20080129191940] 
[Tuple tycons have parens around their names
simonpj@microsoft**20071220171812
 
 The name of the pair TyCon, in the Typeable instance,
 should be "(,)" not ",".
 
 Don't merge to 6.8; it's a minor API change. 
 
] 
[Add groupWith, sortWith, the, to support generalised list comprehensions
simonpj@microsoft.com**20071220111929
 
   This the base-library patch to support the main compiler patch
      Implement generalised list comprehensions
   
   It just adds three functions to GHC.Exts.
 
] 
[Add GHC.Prim to exposedModules in the Haddock 0.x hook
David Waern *-20071209173931
 
 Please merge to the stable branch
] 
[Add GHC.Prim to exposedModules in the Haddock 0.x hook
David Waern **20071209173931
 
 Please merge to the stable branch
] 
[Simplify the GHC.Prim hack in base.cabal/Setup.hs
Ian Lynagh **20071202215758] 
[Implement 'openTempFile' for nhc98.
Malcolm.Wallace@cs.york.ac.uk**20071207133335] 
[docs: describe the changes to forkIO, and document forkOnIO
Simon Marlow **20071205091423] 
[doc only: use realToFrac instead of fromRational.toRational
Simon Marlow **20071205091334] 
[Add singletonP to GHC.PArr
Roman Leshchinskiy **20071205220859] 
[FIX #1621: bug in Windows code for getCPUTime
Simon Marlow **20071205120118
 We were reading the components of FILETIME as CLong, when they should
 be unsigned.  Word32 seems to be the correct type here.
] 
[protect console handler against concurrent access (#1922)
Simon Marlow **20071204153940] 
[protect against concurrent access to the signal handlers (#1922)
Simon Marlow **20071204110817] 
[restore fdToHandle' to avoid breaking clients (#1109)
Simon Marlow **20071130135122
 
] 
[note about how to convert CTime (aka EpochTime) to UTCTime
Simon Marlow **20071130101648] 
[Fix some URLs
Ian Lynagh **20071126214213] 
[Fix some links in haddock docs
Ian Lynagh **20071126184428] 
[Don't try to make haddock links to the mtl package as we don't depend on it
Ian Lynagh **20071126170631] 
[Escape some special characters in haddock docs
Ian Lynagh **20071126163443] 
[FIX BUILD: maybeUpdateFile: ignore failures when removing the target
Simon Marlow **20071123092219] 
[FIX #1753
Simon Marlow **20071122094207
 hClose should close the Handle and unlock the file even if calling
 close() fails for some reason.
] 
[remove lockFile.h from install-includes
Simon Marlow **20071121102248] 
[oops, we forgot to export traceShow
Simon Marlow **20071121094300] 
[Fix compilation with GHC 6.2.x
Simon Marlow **20071121084341] 
[Move file locking into the RTS, fixing #629, #1109
Simon Marlow **20071120121053
 File locking (of the Haskell 98 variety) was previously done using a
 static table with linear search, which had two problems: the array had
 a fixed size and was sometimes too small (#1109), and performance of
 lockFile/unlockFile was suboptimal due to the linear search.
 Also the algorithm failed to count readers as required by Haskell 98
 (#629).
 
 Now it's done using a hash table (provided by the RTS).  Furthermore I
 avoided the extra fstat() for every open file by passing the dev_t and
 ino_t into lockFile.  This and the improvements to the locking
 algorithm result in a healthy 20% or so performance increase for
 opening/closing files (see openFile008 test).
] 
[Only overwrite GHC/Prim.hs and GHC/Primopwrappers.hs if they change
Simon Marlow **20071120102042
 This avoids make doing unnecessary work after 'setup makefile'.
] 
[fix comment
Simon Marlow **20071116091227] 
[Fix ` characters in elem's haddock docs
Ian Lynagh **20071110173052] 
[Filter out GHC.Prim also for the Haddock step
David Waern **20071109000806
 Please merge to the GHC 6.8.2 branch
] 
[Add module of special magic GHC desugaring helper functions
Simon Marlow **20071102160054
 Currently containing only one such helper: (>>>) for arrow desugaring
] 
[add Control.Category to the nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20071030120459] 
[fix nhc98 build: need a qualified Prelude import
Malcolm.Wallace@cs.york.ac.uk**20071030120410] 
[Fix performance regression: re-instate -funbox-strict-fields
Simon Marlow **20071029150730
 Yikes!  While investigating the increase in code size with GHC 6.8
 relative to 6.6, I noticed that in the transition to Cabal for the
 libraries we lost -funbox-strict-fields, which is more or less
 depended on by the IO library for performance.  I'm astonished that we
 didn't notice this earlier!
 
 To reduce the chances of this happening again, I put
 -funbox-strict-fields in the OPTIONS_GHC pragma of the modules that
 need it.  {-# UNPACK #-} pragmas would be better, though.
] 
[FIX BUILD: Haddock 1.x fails to parse (Prelude..)
Simon Marlow **20071029131921] 
[new Control.Category, ghc ticket #1773
Ashley Yakeley **20071029022526] 
[new Control.Compositor module
Ashley Yakeley **20071013074851
 
 The Compositor class is a superclass of Arrow.
] 
[Fix doc building with Haddock 0.9
Simon Marlow **20071024090947
 I was using a recent build here, which is more tolerant.
] 
[FIX #1258: document that openTempFile is secure(ish)
Simon Marlow **20071023130928
 Also change the mode from 0666 to 0600, which seems like a more
 sensible value and matches what C's mkstemp() does.
] 
[Clean up .cabal file a bit
Duncan Coutts **20071022132708
 specify build-type and cabal-version >= 1.2
 put extra-tmp-files in the right place
 use os(windows) rather than os(mingw32)
] 
[FIX #1652: openTempFile should accept an empty string for the directory
Simon Marlow **20071018122345] 
[clean up duplicate code
Simon Marlow **20071017141311] 
[expose the value of +RTS -N as GHC.Conc.numCapabilities (see #1733)
Simon Marlow **20071009132042] 
[base in 6.8 and head branch should be version 3.0
Don Stewart **20071007150408] 
[typo
Simon Marlow **20070917130703] 
[put extra-tmp-files field in the right place
Simon Marlow **20070914140812] 
[Add more entries to boring file
Ian Lynagh **20070913210500] 
[Add a boring file
Ian Lynagh **20070913204641] 
[TAG 2007-09-13
Ian Lynagh **20070913215720] 
[FIX #1689 (openTempFile returns wrong filename)
Tim Chevalier **20070913052025] 
[TAG ghc-6.8 branched 2007-09-03
Ian Lynagh **20070903155541] 
[Remove some incorrect rules; fixes #1658: CSE [of Doubles] changes semantics
Ian Lynagh **20070904134140] 
[make hWaitForInput/hReady not fail with "invalid argument" on Windows
Simon Marlow **20070830131115
 See #1198.  This doesn't fully fix it, because hReady still always
 returns False on file handles.  I'm not really sure how to fix that.
] 
[Fix haddock docs in Hashtable
Ian Lynagh **20070830154131] 
[Fix building HashTable: Use ord rather than fromEnum
Ian Lynagh **20070830150214] 
[Better hash functions for Data.HashTable, from Jan-Willem Maessen
Ian Lynagh **20070830142844] 
[Remove redundant include/Makefile
Ian Lynagh **20070828205659] 
[Make arrays safer (e.g. trac #1046)
Ian Lynagh **20070810163405] 
[delete configure droppings in setup clean
Simon Marlow **20070824104100] 
[FIX #1282: 64-bit unchecked shifts are not exported from base
Simon Marlow **20070823135033
 I've exported these functions from GHC.Exts.  They are still
 implemented using the FFI underneath, though.
 
 To avoid conditional exports, on a 64-bit build:
 
   uncheckedShiftL64# = uncheckShiftL#
 
 (etc.) which has a different type than the 32-bit version of
 uncheckedShiftL64#, but at least GHC.Exts exports the same names.
 
] 
[Fix hashInt
Ian Lynagh **20070821140706
 As pointed out in
 http://www.haskell.org/pipermail/glasgow-haskell-bugs/2007-August/009545.htm...
 the old behaviour was
 Prelude Data.HashTable> map hashInt [0..10]
 [0,-1,-1,-2,-2,-2,-3,-3,-4,-4,-4]
 
 Fixed according to the "Fibonacci Hashing" algorithm described in
 http://www.brpreiss.com/books/opus4/html/page213.html
 http://www.brpreiss.com/books/opus4/html/page214.html
] 
[test impl(ghc) instead of IsGHC
Ross Paterson **20070819233500] 
[fpstring.h has moved to bytestring
Ross Paterson **20070819233815] 
[remove now-unused SIG constants
Ross Paterson **20070819233745] 
[include Win32 extra-libraries for non-GHC's too
Ross Paterson **20070819233611] 
[Don't import Distribution.Setup in Setup.hs as we no longer need it
Ian Lynagh **20070816151643] 
[Correct the swapMVar haddock doc
Ian Lynagh **20070814145028] 
[install Typeable.h for use by other packages
Malcolm.Wallace@cs.york.ac.uk**20070813112855] 
[Don't try to build modules no longer living in base.
Malcolm.Wallace@cs.york.ac.uk**20070813112803] 
[Move Data.{Foldable,Traversable} back to base
Ian Lynagh **20070812165654
 The Array instances are now in Data.Array.
] 
[Remove bits left over from the old build system
Ian Lynagh **20070811135019] 
[Move the datamap001 (our only test) to the containers package
Ian Lynagh **20070803180932] 
[Data.Array* and Data.PackedString have now moved to their own packages
Ian Lynagh **20070801235542] 
[Remove a number of modules now in a "containers" package
Ian Lynagh **20070801223858] 
[Remove System.Posix.Signals (moving to unix)
Ian Lynagh **20070729215213] 
[bytestring is now in its own package
Ian Lynagh **20070729132215] 
[Export throwErrnoPath* functions
Ian Lynagh **20070722002923] 
[Add simple haddock docs for throwErrnoPath* functions
Ian Lynagh **20070722002817] 
[Move throwErrnoPath* functions from unix:System.Posix.Error
Ian Lynagh **20070722002746] 
[Clarify the swapMVar haddock doc
Ian Lynagh **20070807185557] 
[fix Haddock markup
Simon Marlow **20070802081717] 
[Temporarily fix breakage for nhc98.
Malcolm.Wallace@cs.york.ac.uk**20070801163750
 A recent patch to System.IO introduced a cyclic dependency on Foreign.C.Error,
 and also inadvertently dragged along System.Posix.Internals which has
 non-H'98 layout, causing many build problems.  The solution for now
 is to #ifndef __NHC__ all of the recent the openTempFile additions,
 and mark them non-portable once again.  (I also took the opportunity
 to note a number of other non-portable functions in their Haddock
 comments.)
] 
[Generalise the type of synthesize, as suggested by Trac #1571
simonpj@microsoft**20070801125208
 
 I have not looked at the details, but the type checker is happy with the
 more general type, and more general types are usually a Good Thing.
 
] 
[Fix fdToHandle on Windows
Ian Lynagh **20070730133139
 The old setmode code was throwing an exception, and I'm not sure it is
 meant to do what we need anyway. For now we assume that all FDs are
 both readable and writable.
] 
[Correct Windows OS name in cabal configuration
Ian Lynagh **20070729161739] 
[Use cabal configurations rather than Setup hacks
Ian Lynagh **20070729132157] 
[Handle buffers should be allocated with newPinnedByteArray# always
Simon Marlow **20070725095550
 Not just on Windows.  This change is required because we now use safe
 foreign calls for I/O on blocking file descriptors with the threaded
 RTS.  Exposed by concio001.thr on MacOS X: MacOS apparently uses
 smaller buffers by default, so they weren't being allocated as large
 objects.
 
] 
[fix Hugs implementation of openTempFile
Ross Paterson **20070724114003] 
[Hugs only: avoid dependency cycle
Ross Paterson **20070724113852] 
[open(Binary)TempFile is now portable
Ian Lynagh **20070722152752] 
[Tweak temporary file filename chooser
Ian Lynagh **20070722105445] 
[Move open(Binary)TempFile to System.IO
Ian Lynagh **20070722010205] 
[Rename openFd to fdToHandle'
Ian Lynagh **20070721235538
 The name collision with System.Posix.IO.openFd made my brain hurt.
] 
[Add a test for Data.Map, for a bug on the libraries@ list
Ian Lynagh **20070721002119] 
[fix Data.Map.updateAt
Bertram Felgenhauer **20070718150340
 See http://haskell.org/pipermail/libraries/2007-July/007785.html for a piece
 of code triggering the bug. updateAt threw away parts of the tree making up
 the map.
] 
[in hClose, free the handle buffer by replacing it with an empty one
Simon Marlow **20070719161419
 This helps reduce the memory requirements for a closed but unfinalised
 Handle.
] 
[Implement GHC.Environment.getFullArgs
Ian Lynagh **20070717141918
 This returns all the arguments, including those normally eaten by the
 RTS (+RTS ... -RTS).
 This is mainly for ghc-inplace, where we need to pass /all/ the
 arguments on to the real ghc. e.g. ioref001(ghci) was failing because
 the +RTS -K32m -RTS wasn't getting passed on.
] 
[Define stripPrefix; fixes trac #1464
Ian Lynagh **20070714235204] 
[no need to hide Maybe
Malcolm.Wallace@cs.york.ac.uk**20070710154058] 
[Add a more efficient Data.List.foldl' for GHC (from GHC's utils/Util.lhs)
Ian Lynagh **20070706205526] 
[Remove include-dirs ../../includes and ../../rts
Ian Lynagh **20070705205356
 We get these by virtue of depending on the rts package.
] 
[FIX #1131 (newArray_ allocates an array full of garbage)
Simon Marlow **20070704102020
 Now newArray_ returns a deterministic result in the ST monad, and
 behaves as before in other contexts.  The current newArray_ is renamed
 to unsafeNewArray_; the MArray class therefore has one more method
 than before.
] 
[change nhc98 option from -prelude to --prelude
Malcolm.Wallace@cs.york.ac.uk**20070702150355] 
[Word is a type synonym in nhc98 - so class instance not permitted.
Malcolm.Wallace@cs.york.ac.uk**20070629122035] 
[fix bug in writes to blocking FDs in the non-threaded RTS
Simon Marlow **20070628134320] 
[Modernize printf.
lennart.augustsson@credit-suisse.com**20070628083852
 
 Add instances for Int8, Int16, Int32, Int64, Word, Word8, Word16, Word32, and
 Word64.
 Handle + flag.
 Handle X, E, and G formatting characters.
 Rewrite internals to make it simpler.
] 
[Speed up number printing and remove the need for Array by using the standard 'intToDigit' routine
John Meacham **20070608182353] 
[Use "--  //" (2 spaces) rather than "-- //" (1) to avoid tripping haddock up
Ian Lynagh **20070627010930
 Are we nearly there yet?
] 
[Use a combination of Haskell/C comments to ensure robustness.
Malcolm.Wallace@cs.york.ac.uk**20070626095222
 e.g. -- // ensures that _no_ preprocessor will try to tokenise the
 rest of the line.
] 
[Change C-style comments to Haskell-style.
Malcolm.Wallace@cs.york.ac.uk**20070625094515
 These two headers are only ever used for pre-processing Haskell code,
 and are never seen by any C tools except cpp.  Using the Haskell comment
 convention means that cpphs no longer needs to be given the --strip
 option to remove C comments from open code.  This is a Good Thing,
 because all of /* */ and // are valid Haskell operator names, and there
 is no compelling reason to forbid using them in files which also happen
 to have C-preprocessor directives.
] 
[makefileHook needs to generate PrimopWrappers.hs too
Simon Marlow **20070622073424] 
[Hugs now gets MonadFix(mfix) from its prelude
Ross Paterson **20070620000343] 
[Typo (consUtils.hs -> consUtils.h)
Ian Lynagh **20070619124140] 
[install dependent include files and Typeable.h
Bertram Felgenhauer **20070613041734] 
[update prototype following inputReady->fdReady change
Simon Marlow **20070614095309] 
[FIX hGetBuf001: cut-and-pasto in readRawBufferNoBlock
Simon Marlow **20070614094222] 
[fix description of CWStringLen
Ross Paterson **20070605223345] 
[Remove unsafeCoerce-importing kludgery in favor of Unsafe.Coerce
Isaac Dupree **20070601203625] 
[--configure-option and --ghc-option are now provided by Cabal
Ross Paterson **20070604115233] 
[Data.PackedString: Data.Generics is GHC-only
Ross Paterson **20070529232427] 
[Add Data instance for PackedString; patch from greenrd in trac #1263
Ian Lynagh **20070529205420] 
[Control.Concurrent documentation fix
shae@ScannedInAvian.com**20070524163325] 
[add nhc98-options: field to .cabal file
Malcolm.Wallace@cs.york.ac.uk**20070528122626] 
[add a dummy implementation of System.Timeout.timeout for nhc98
Malcolm.Wallace@cs.york.ac.uk**20070528110309] 
[Add System.Timeout to base.cabal
Ian Lynagh **20070527123314
 Filtered out for non-GHC by Setup.hs.
] 
[add module Data.Fixed to nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20070525141021] 
[DIRS now lives in package Makefile, not script/pkgdirlist
Malcolm.Wallace@cs.york.ac.uk**20070525111749] 
[delete unused constants
Ross Paterson **20070525001741] 
[remove System.Cmd and System.Time too
Malcolm.Wallace@cs.york.ac.uk**20070524163200] 
[remove locale as well
Malcolm.Wallace@cs.york.ac.uk**20070524161943] 
[nhc98 version of instance Show (a->b) copied from Prelude
Malcolm.Wallace@cs.york.ac.uk**20070524160615] 
[remove directory, pretty, and random bits from base for nhc98
Malcolm.Wallace@cs.york.ac.uk**20070524160608] 
[Remove Makefile and package.conf.in (used in the old build system)
Ian Lynagh **20070524142545] 
[Split off process package
Ian Lynagh **20070523210523] 
[Fix comment: maperrno is in Win32Utils.c, not runProcess.c
Ian Lynagh **20070523181331] 
[System.Locale is now split out
Ian Lynagh **20070519132638] 
[Split off directory, random and old-time packages
Ian Lynagh **20070519120642] 
[Remove Control.Parallel*, now in package parallel
Ian Lynagh **20070518165431] 
[Remove the pretty-printing modules (now in package pretty(
Ian Lynagh **20070518162521] 
[add install-includes: field
Simon Marlow **20070517094948] 
[correct the documentation for newForeignPtr
Simon Marlow **20070516082019] 
[When doing safe writes, handle EAGAIN rather than raising an exception
Simon Marlow **20070515114615
 It might be that stdin was set to O_NONBLOCK by someone else, and we
 should handle this case.  (this happens with GHCi, I'm not quite sure why)
] 
[Use FilePath to make paths when building GHC/Prim.hs and GHC/PrimopWrappers.hs
Ian Lynagh **20070514110409] 
[Build GHC/Prim.hs and GHC/PrimopWrappers.hs from Cabal
Ian Lynagh **20070509142655] 
[fix imports for non-GHC
Ross Paterson **20070513001138] 
[Give an example of how intersection takes elements from the first set
Ian Lynagh **20070512160253] 
[further clarify the docs for 'evaluate'
Malcolm.Wallace@cs.york.ac.uk**20070508101124] 
[improve documentation for evaluate
Simon Marlow **20070508081712] 
[FIX: #724 (tee complains if used in a process started by ghc)
Simon Marlow **20070507123537
 
 Now, we only set O_NONBLOCK on file descriptors that we create
 ourselves.  File descriptors that we inherit (stdin, stdout, stderr)
 are kept in blocking mode.  The way we deal with this differs between
 the threaded and non-threaded runtimes:
 
  - with -threaded, we just make a safe foreign call to read(), which
    may block, but this is ok.
 
  - without -threaded, we test the descriptor with select() before
    attempting any I/O.  This isn't completely safe - someone else
    might read the data between the select() and the read() - but it's
    a reasonable compromise and doesn't seem to measurably affect
    performance.
] 
[the "unknown" types are no longer required
Simon Marlow **20070426135931] 
[Make Control.Exception buildable by nhc98.
Malcolm.Wallace@cs.york.ac.uk**20070504105548
 The nhc98 does not have true exceptions, but these additions should be
 enough infrastructure to pretend that it does.  Only IO exceptions will
 actually work.
] 
[Trim imports, remove a cycle
simonpj@microsoft**20070503123010
 
 A first attempt at removing gratuitous cycles in the base package.
 I've removed the useless module GHC.Dynamic, which gets rid of a cycle;
 and trimmed off various unnecesary imports.
 
 This also fixes the IsString import problem.
 
] 
[Be less quiet about building the base package
simonpj@microsoft**20070503093707] 
[Remove Splittable class (a vestige of linear implicit parameters)
simonpj@microsoft**20070221104329] 
[Add IsString to exports of GHC.Exts
simonpj@microsoft**20070221104249] 
[tweak documentation as per suggestion from Marc Weber on libraries@haskell.org
Simon Marlow **20070426075921] 
[Add extra libraries when compiling with GHC on Windows
Ian Lynagh **20070424213127] 
[Follow Cabal changes in Setup.hs
Ian Lynagh **20070418114345] 
[inclusion of libc.h is conditional on __APPLE__
Malcolm.Wallace@cs.york.ac.uk**20070417085556] 
[MERGE: fix ugly uses of memcpy foreign import inside ST
Simon Marlow **20070416101530
 fixes cg026
] 
[Fix configure with no --with-cc
Ian Lynagh **20070415165143] 
[MacOS 10.3 needs #include  as well
Malcolm.Wallace@cs.york.ac.uk**20070414155507] 
[For nhc98 only, use hsc2hs to determine System.Posix.Types.
Malcolm.Wallace@cs.york.ac.uk**20070413155831
 Avoids the existing autoconf stuff, by introducing an auxiliary module
 called NHC.PosixTypes that uses hsc2hs, which is then simply re-exported
 from System.Posix.Types.
] 
[we need a makefileHook too
Simon Marlow **20070413151307] 
[Remove unnecesary SOURCE import of GHC.Err in GHC.Pack
Ian Lynagh **20070412235908] 
[add System.Posix.Types to default nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20070412195026] 
[mark System.IO.openTempFile as non-portable in haddocks
Malcolm.Wallace@cs.york.ac.uk**20070412135359] 
[Don't turn on -Werror in Data.Fixed
Ian Lynagh **20070411155721
 This may be responsible for the x86_64/Linux nightly build failing.
] 
[Fix -Wall warnings
Ian Lynagh **20070411004929] 
[Add missing case in removePrefix
Ian Lynagh **20070411002537] 
[Allow additional options to pass on to ./configure to be given
Ian Lynagh **20070406151856] 
[Hugs only: fix location of unsafeCoerce
Ross Paterson **20070406113731] 
[fix isPortableBuild test
Ross Paterson **20070406111304] 
[Unsafe.Coerce doesn't need Prelude
Ian Lynagh **20070405175930] 
[make Setup and base.cabal suitable for building the libraries with GHC
Ian Lynagh **20070308163824] 
[HsByteArray doesn't exist
Ian Lynagh **20070404163051] 
[Don't use Fd/FD in foreign decls
Ian Lynagh **20070404155822
 Using CInt makes it much easier to verify that it is right, and we won't
 get caught out by possible newtype switches between CInt/Int.
] 
[HsByteArray doesn't exist
Ian Lynagh **20070404155732] 
[Fix braino
Ian Lynagh **20070404144508] 
[Fix incorrect changes to C types in a foreign import for nhc98.
Malcolm.Wallace@cs.york.ac.uk**20070404120954
 If we use type CTime, it needs to be imported.  Also, CTime is not an
 instance of Integral, so use some other mechanism to convert it.
] 
[Fix C/Haskell type mismatches
Ian Lynagh **20070403194943] 
[add new module Unsafe.Coerce to build system
Malcolm.Wallace@cs.york.ac.uk**20070403131333] 
[Fix type mismatches between foreign imports and HsBase.h
Ian Lynagh **20070403001611
 
 Merge to stable, checking for interface changes.
] 
[put 'unsafeCoerce' in a standard location
Malcolm.Wallace@cs.york.ac.uk**20061113114103] 
[fix for nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20070402141712] 
[Function crossMapP for fixing desugaring of comprehensions
Manuel M T Chakravarty **20070402082906
 
 Merge into 6.6 branch.
] 
[Add min/max handling operations for IntSet/IntMap
jeanphilippe.bernardy@gmail.com**20070315072352] 
[Monoid instance for Maybe and two wrappers: First and Last. trac proposal #1189
Jeffrey Yasskin **20070309062550] 
[Fix the type of wgencat
Ian Lynagh **20070329164223] 
[fix strictness of foldr/build rule for take, see #1219
Simon Marlow **20070327103941] 
[remove Makefile.inc (only affects nhc98)
Malcolm.Wallace@cs.york.ac.uk**20070320120057] 
[copyBytes copies bytes, not elements; fixes trac #1203
Ian Lynagh **20070312113555] 
[Add ioeGetLocation, ioeSetLocation to System/IO/Error.hs; trac #1191
Ian Lynagh **20070304130315] 
[fix race condition in prodServiceThread
Simon Marlow **20070307134330
 See #1187
] 
[Prevent duplication of unsafePerformIO on a multiprocessor
Simon Marlow **20070306145424
 Fixes #986.  The idea is to add a new operation
 
   noDuplicate :: IO ()
 
 it is guaranteed that if two threads have executed noDuplicate, then
 they are not duplicating any computation.
 
 We now provide two new unsafe operations:
 
 unsafeDupablePerformIO    :: IO a -> a
 unsafeDupableInterleaveIO :: IO a -> IO a
 
 which are equivalent to the old unsafePerformIO and unsafeInterleaveIO
 respectively.  The new versions of these functions are defined as:
 
 unsafePerformIO    m = unsafeDupablePerformIO (noDuplicate >> m)
 unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m)
] 
[expand docs for forkOS
Simon Marlow **20070305160921] 
[document timeout limitations
Peter Simons **20070228223540] 
[So many people were involved in the writing of this module that
Peter Simons **20070228223415
 it feels unfair to single anyone out as the lone copyright
 holder.
] 
[This patch adds a timeout function to the base libraries. Trac #980 is
Peter Simons **20070126222615
 concerned with this issue. The design guideline for this implementation
 is that 'timeout N E' should behave exactly the same as E as long as E
 doesn't time out. In our implementation, this means that E has the same
 myThreadId it would have without the timeout wrapper. Any exception E
 might throw cancels the timeout and propagates further up. It also
 possible for E to receive exceptions thrown to it by another thread.
] 
[PArr: fixed permutations
Manuel M T Chakravarty **20070305055807] 
[Add Data.String, containing IsString(fromString); trac proposal #1126
Ian Lynagh **20070130134841
 This is used by the overloaded strings extension (-foverloaded-strings in GHC).
] 
[GHC.PArr: add bounds checking
Manuel M T Chakravarty **20070302053224] 
[Bump nhc98 stack size for System/Time.hsc
sven.panne@aedion.de**20070301153009] 
[FDs are CInts now, fixing non-GHC builds
sven.panne@aedion.de**20070225105620] 
[Fixed PArr.dropP
Manuel M T Chakravarty **20070222032405
 - Thanks to Audrey Tang for the bug report
] 
[Keep the same FD in both halves of a duplex handle when dup'ing
Ian Lynagh **20070220141039
 Otherwise we only close one of the FDs when closing the handle.
 Fixes trac #1149.
] 
[Remove more redundant FD conversions
Ian Lynagh **20070220092520] 
[Fix FD changes on Windows
Ian Lynagh **20070220091516] 
[Consistently use CInt rather than Int for FDs
Ian Lynagh **20070219233854] 
[Fix the types of minView/maxView (ticket #1134)
jeanphilippe.bernardy@gmail.com**20070210065115] 
[fix for hashString, from Jan-Willem Maessen (see #1137)
Simon Marlow **20070215094304
 
] 
[fix to getUSecOfDay(): arithmetic was overflowing
Simon Marlow **20070214161719] 
[The Windows counterpart to 'wrapround of thread delays'
Ian Lynagh **20070209173510] 
[wrapround of thread delays
Neil Davies **20070129160519
 
   * made the wrapround of the underlying O/S occur before the wrapround
     of the delayed threads by making threads delay in microseconds since
     O/S epoch (1970 - Unix, 1601 - Windows) stored in Word64.
   * removed redundant calls reading O/S realtime clock
   * removed rounding to 1/50th of sec for timers
   * Only for Unix version of scheduler.
] 
[Whitespace changes only
Ian Lynagh **20070206232722] 
[Add some type sigs
Ian Lynagh **20070206232439] 
[Use static inline rather than extern inline/inline
Ian Lynagh **20070205203628
 I understand this is more portable, and it also fixes warnings when
 C things we are wrapping are themselves static inlines (which FD_ISSET
 is on ppc OS X).
] 
[add derived instances for Dual monoid
Ross Paterson **20070202190847] 
[add doc pointers to Foldable
Ross Paterson **20070202110931
 
 Could be applied to STABLE.
] 
[Eliminate some warnings
Ian Lynagh **20060729220854
 Eliminate warnings in the libraries caused by mixing pattern matching
 with numeric literal matching.
] 
[Remove IsString(fromString) from the Prelude
Ian Lynagh **20070130124136] 
[Add Kleisli composition
Don Stewart **20061113015442] 
[IsString is GHC-only (so why is it in the Prelude?)
Ross Paterson **20070123183007] 
[Applicative and Monad instances for Tree
Ross Paterson **20070115174510] 
[Add IsString class for overloaded string literals.
lennart@augustsson.net**20061221210532] 
[Added examples, more detailed documentation to Data.List Extracting sublists functions
Andriy Palamarchuk **20061204164710] 
[fix threadDelay
Simon Marlow **20070117091702
 In "Add support for the IO manager thread" I accidentally spammed part
 of "Make sure the threaded threadDelay sleeps at least as long as it
 is asked", which is why the ThreadDelay001 test has been failing.
] 
[update section on "blocking"
Simon Marlow **20070116124328] 
[Fix crash with   (minBound :: Int*) `div (-1)   as result is maxBound + 1.
Ian Lynagh **20070115142005] 
[version of example using Tomasz Zielonka's technique
Ross Paterson **20070105175907] 
[Added Unknowns for higher kinds
Pepe Iborra **20061108155938] 
[Improved the Show instance for Unknown
Pepe Iborra **20060813111816] 
[Show instance for GHC.Base.Unknown
mnislaih@gmail.com**20060801233530] 
[Introduce Unknowns for the closure viewer. Add breakpointCond which was missing
mnislaih@gmail.com**20060725174537] 
[Fix missing comma in Fractional documentation
Alec Berryman **20061201173237] 
[Mention that throwTo does not guarantee promptness of delivery
simonpj@microsoft**20061211123215] 
[Add note about synhronous delivery of throwTo
simonpj@microsoft**20061211122257] 
[documentation for installHandler
Simon Marlow **20061205154927
 merge to 6.6
] 
[dos2unix
Simon Marlow **20061204095439] 
[don't try to compile this on Unix
Simon Marlow **20061204095427] 
[TAG 6.6 release
Ian Lynagh **20061011124740] 
[TAG Version 2.1
Ian Lynagh **20061009114014] 
[Bump version number
Ian Lynagh **20061009114009] 
[Add support for the IO manager thread on Windows
Simon Marlow **20061201152042
 Fixes #637.  The test program in that report now works for me with
 -threaded, but it doesn't work without -threaded (I don't know if
 that's new behaviour or not, though).
] 
[deriving (Eq, Ord, Enum, Show, Read, Typeab) for ConsoleEvent
Simon Marlow **20061201144032] 
[Make sure the threaded threadDelay sleeps at least as long as it is asked to
Ian Lynagh **20061128204807] 
[Add comments about argument order to the definitions of gmapQ and constrFields
simonpj@microsoft**20061124164505] 
[Hugs: add Control.Parallel.Strategies
Ross Paterson **20061124161039] 
[Move instance of Show Ptr to Ptr.hs (fewer orphans)
simonpj@microsoft.com**20061124100639] 
[Add type signatures
simonpj@microsoft.com**20061124100621] 
[Add an example of the use of unfoldr, following doc feedback from dozer
Don Stewart **20061124011249] 
[trim imports
Ross Paterson **20061123190352] 
[Data.Graph is now portable (enable for nhc98)
Malcolm.Wallace@cs.york.ac.uk**20061123174913] 
[remove Data.FunctorM and Data.Queue
Ross Paterson **20061112001046
 
 These were deprecated in 6.6, and can thus be removed in 6.8.
] 
[make Data.Graph portable (no change to the interface)
Ross Paterson **20061122010040
 
 The algorithm now uses STArrays on GHC and IntSets elsewhere.
 (Hugs has STArrays, but avoiding them saves a -98, and boxed arrays
 aren't fast under Hugs anyway.)
] 
[One less unsafeCoerce# in the tree
Don Stewart **20061120120242] 
[typo in comment
Ross Paterson **20061120115106] 
[fix shift docs to match ffi spec
Ross Paterson **20061117003144] 
[(nhc98) use new primitive implementations of h{Put,Get}Buf.
Malcolm.Wallace@cs.york.ac.uk**20061116173104] 
[The wrong 'cycle' was exported from Data.ByteString.Lazy.Char8, spotted by sjanssen
Don Stewart **20061110021311] 
[LPS chunk sizes should be 16 bytes, not 17. 
Don Stewart **20061110021254] 
[Update comments on Prelude organisation in GHC/Base.lhs
Ian Lynagh **20061115001926] 
[Control.Parallel.Strategies clean-up: Added export list to avoid exporting seq, fixed import list strangeness that haddock choked on, and moved the deprecated functions to a separate section.
bringert@cs.chalmers.se**20061113224202] 
[Control.Parallel.Strategies: added NFData instances for Data.Int.*, Data.Word.*, Maybe, Either, Map, Set, Tree, IntMap, IntSet.
bringert@cs.chalmers.se**20061113221843] 
[Control.Parallel.Strategies: deprecate sPar, sSeq, Assoc, fstPairFstList, force and sforce. 
bringert@cs.chalmers.se**20061113215219
 Code comments indicated that sPar and sSeq have been superceded by sparking and demanding, and that Assoc, fstPairFstList, force and sforce are examples and hacks needed by the Lolita system.
] 
[add Control.Monad.Instances to nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20061113113221] 
[Control.Parallel.Strategies: clarified documentation of parListChunk.
bringert@cs.chalmers.se**20061112232904] 
[Added and cleaned up Haddock comments in Control.Parallel.Strategies.
bringert@cs.chalmers.se**20061112220445
 Many of the definitions in Control.Parallel.Strategies had missing or unclear Haddock comments. I converted most of the existing plain code comments to haddock comments, added some missing documentation and cleaned up the existing Haddock mark-up.
] 
[Fix broken pragmas; spotted by Bulat Ziganshin
Ian Lynagh **20061111205916] 
[add doc link to bound threads section
Ross Paterson **20060929103252] 
[hide Data.Array.IO.Internals
Ross Paterson **20061111113248
 
 It's hidden from haddock, and everything it exports is re-exported by
 Data.Array.IO.
] 
[add Data.Function
Malcolm.Wallace@cs.york.ac.uk**20061110142710] 
[add Data.Function
Ross Paterson **20061110141354] 
[whitespace only
Ross Paterson **20061110141326] 
[move fix to Data.Function
Ross Paterson **20061110141120] 
[import Prelude
Ross Paterson **20061110140445] 
[Added Data.Function (Trac ticket #979).
Nils Anders Danielsson **20061110122503
 + A module with simple combinators working solely on and with
   functions.
 + The only new function is "on".
 + Some functions from the Prelude are re-exported.
] 
[__hscore_long_path_size is not portable beyond GHC
Malcolm.Wallace@cs.york.ac.uk**20061110113222] 
[redefine writeFile and appendFile using withFile
Ross Paterson **20061107140359] 
[add withFile and withBinaryFile (#966)
Ross Paterson **20061107134510] 
[remove conflicting import for nhc98
Malcolm.Wallace@cs.york.ac.uk**20061108111215] 
[Add intercalate to Data.List (ticket #971)
Josef Svenningsson **20061102122052] 
[non-GHC: fix canonicalizeFilePath
Ross Paterson **20061107133902
 
 I've also removed the #ifdef __GLASGOW_HASKELL__ from the proper
 Windows versions of a few functions.  These will need testing with
 Hugs on Windows.
] 
[enable canonicalizePath for non-GHC platforms
Simon Marlow **20061107121141] 
[Update documentation for hWaitForInput
Simon Marlow **20061107111430
 See #972
 Merge to 6.6 branch.
] 
[Use unchecked shifts to implement Data.Bits.rotate
Samuel Bronson **20061012125553
 This should get rid of those cases, maybe lower the size enough that the inliner will like it?
] 
[fix Haddock module headers
Ross Paterson **20061106124140] 
[fix example in docs
Ross Paterson **20061106115628] 
[Add intercalate and split to Data.List
Josef Svenningsson *-20061024172357] 
[Data.Generics.Basics is GHC-only
Ross Paterson **20061102111736] 
[#ifdef around non-portable Data.Generics.Basics
Malcolm.Wallace@cs.york.ac.uk**20061102103445] 
[Add deriving Data to Complex
simonpj@microsoft**20061101102059] 
[minor clarification of RandomGen doc
Ross Paterson **20061030230842] 
[rearrange docs a bit
Ross Paterson **20061030161223] 
[Add intercalate and split to Data.List
Josef Svenningsson **20061024172357] 
[Export pseq from Control.Parallel, and use it in Control.Parallel.Strategies
Simon Marlow **20061027150141] 
[`par` should be infixr 0
Simon Marlow **20061027130800
 Alas, I didn't spot this due to lack of testing, and the symptom is
 that an expression like x `par` y `seq z will have exactly the wrong
 parallelism properties.  The workaround is to add parantheses.
 
 I think we could push this to the 6.6 branch.
] 
[fix example in comment
Ross Paterson **20061023163925] 
[Use the new Any type for dynamics (GHC only)
simonpj@microsoft**20061019160408] 
[add Data.Sequence to nhc98 build
Malcolm.Wallace@cs.york.ac.uk**20061012135200] 
[Remove Data.FiniteMap, add Control.Applicative, Data.Traversable, and
Malcolm.Wallace@cs.york.ac.uk**20061012095605
 Data.Foldable to the nhc98 build.
] 
[STM invariants
tharris@microsoft.com**20061007123253] 
[Inline shift in GHC's Bits instances for {Int,Word}{,8,16,32,64}
Samuel Bronson **20061009020906] 
[Don't create GHC.Prim when bootstrapping; we can't, and we don't need it
Ian Lynagh