Proposal: add some missing tuple functions

Don Stewart dons at galois.com
Tue Mar 11 14:13:15 EDT 2008


Basic texts often define

    swap, fst3, snd3 and thd3

So let's add them to the rather bare Data.Tuple.

The fst3.. series were approved to be added a couple of years ago, but I
never got around to it.

The patch is attached.

-- Don

-------------- next part --------------

New patches:

[Some long missing tuple functions
Don Stewart <dons at galois.com>**20080311180851] {
hunk ./Data/Tuple.hs 278
+-- | Swap components of a pair
+swap (x,y)              = (y,x)
+
+-- | Extract the first component of a triple.
+fst3                    :: (a,b,c) -> a
+fst3 (x,_,_)            = x
+
+-- | Extract the second component of a triple.
+snd3                    :: (a,b,c) -> a
+snd3 (_,y,_)            = y
+
+-- | Extract the third component of a triple.
+thd3                    :: (a,b,c) -> a
+thd3 (_,_,z)            = z
+
+
}

Context:

[untabify
Don Stewart <dons at galois.com>**20080310005455] 
[untabify
Don Stewart <dons at galois.com>**20080308014256] 
[untabify
Don Stewart <dons at galois.com>**20080308014129] 
[untabify
Don Stewart <dons at galois.com>**20080308014040] 
[untabify
Don Stewart <dons at galois.com>**20080308013556] 
[untabify
Don Stewart <dons at galois.com>**20080308012457] 
[untabify
Don Stewart <dons at galois.com>**20080308012059] 
[untabify
Don Stewart <dons at galois.com>**20080307192727] 
[untabify
Don Stewart <dons at galois.com>**20080305033712] 
[untabify
Don Stewart <dons at galois.com>**20080305015827] 
[untabify
Don Stewart <dons at galois.com>**20080305012530] 
[untabify
Don Stewart <dons at galois.com>**20080305010343] 
[untabify
Don Stewart <dons at galois.com>**20080305010255] 
[untabify
Don Stewart <dons at galois.com>**20080305005041] 
[untabify
Don Stewart <dons at galois.com>**20080305005025] 
[untabify
Don Stewart <dons at galois.com>**20080304235330] 
[untabify
Don Stewart <dons at galois.com>**20080304225120] 
[untabify
Don Stewart <dons at galois.com>**20080304174827] 
[untabify
Don Stewart <dons at galois.com>**20080303195109] 
[untabify
Don Stewart <dons at galois.com>**20080303195002] 
[untabify
Don Stewart <dons at galois.com>**20080303194454] 
[untabify
Don Stewart <dons at galois.com>**20080228234443] 
[untabify
Don Stewart <dons at galois.com>**20080228185409] 
[untabify
Don Stewart <dons at galois.com>**20080228185356] 
[untabify
Don Stewart <dons at galois.com>**20080228185331] 
[export MVar, TVar, and STM non-abstractly
Simon Marlow <simonmar at microsoft.com>**20080228113035
 As requested by Sterling Clover on ghc-users
] 
[Added Down class and improved groupWith fusion
Max Bolingbroke <batterseapower at hotmail.com>**20080213212246] 
[untabify
Don Stewart <dons at galois.com>**20080227062836] 
[untabify
Don Stewart <dons at galois.com>**20080226070630] 
[mention explicitly that hIsEOF may block
Simon Marlow <simonmar at microsoft.com>**20080220141209] 
[untabify
Don Stewart <dons at galois.com>**20080219233644] 
[untabify
Don Stewart <dons at galois.com>**20080219233047] 
[untabify
Don Stewart <dons at galois.com>**20080219232910] 
[untabify
Don Stewart <dons at galois.com>**20080219225437] 
[untabify
Don Stewart <dons at galois.com>**20080219061513] 
[Add exitSuccess :: IO a. For symmetry with exitFailure
Don Stewart <dons at galois.com>**20080213222644] 
[untabify
Don Stewart <dons at galois.com>**20080218075732] 
[untabify
Don Stewart <dons at galois.com>**20080218065411] 
[untabify
Don Stewart <dons at galois.com>**20080215005543] 
[FIX dynamic001, dynamic002: further fixes to tuple printing
Simon Marlow <simonmar at microsoft.com>**20080211101908] 
[untabify
Don Stewart <dons at galois.com>**20080213221950] 
[untabify only
Don Stewart <dons at galois.com>**20080213221856] 
[whitespace only
Don Stewart <dons at galois.com>**20080207191939] 
[Whitespace only
Don Stewart <dons at galois.com>**20080207183954] 
[FIX dynamic001 dynamic002: isTupleTyCon had rotted
Simon Marlow <simonmar at microsoft.com>**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 <igloo at earth.li>**20080203152755] 
[Generalise type of forever :: (Monad m) => m a -> m b
Don Stewart <dons at galois.com>**20080129191940] 
[FIX #1936: hGetBufNonBlocking was blocking on stdin/stdout/stderr
Simon Marlow <simonmar at microsoft.com>**20080124092203] 
[The default uncaught exception handler was adding an extra \n
Simon Marlow <simonmar at microsoft.com>**20080124091216] 
[add comment about lack of _chsize_s()
Simon Marlow <simonmar at microsoft.com>**20080123131248] 
[Windows: large file support for hFileSize and hSeek (#1771)
Simon Marlow <simonmar at microsoft.com>**20080123102904
 
 
] 
[Export topHandler, topHandlerFastExit from GHC.TopHandler
Ian Lynagh <igloo at earth.li>**20080120182429
 We now use one of these in ghc when running with ghc -e
] 
[haddock attributes for haddock-2.0
Ross Paterson <ross at soi.city.ac.uk>**20080120022308] 
[Data.List.sort: force elements from start to end.
Bertram Felgenhauer <int-e at gmx.de>**20071121101458
 this prevents a stack overflow on  sort (take 10^6 [1..])
] 
[Fix comment on GHC.Ptr.minusPtr
simonpj at microsoft.com**20080109114736] 
[Remove redundant imports of GHC.Err
simonpj at 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.
 
] 
[Tuple tycons have parens around their names
simonpj at 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 at 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 <david.waern at gmail.com>*-20071209173931
 
 Please merge to the stable branch
] 
[Add GHC.Prim to exposedModules in the Haddock 0.x hook
David Waern <david.waern at gmail.com>**20071209173931
 
 Please merge to the stable branch
] 
[Simplify the GHC.Prim hack in base.cabal/Setup.hs
Ian Lynagh <igloo at earth.li>**20071202215758] 
[Implement 'openTempFile' for nhc98.
Malcolm.Wallace at cs.york.ac.uk**20071207133335] 
[docs: describe the changes to forkIO, and document forkOnIO
Simon Marlow <simonmar at microsoft.com>**20071205091423] 
[doc only: use realToFrac instead of fromRational.toRational
Simon Marlow <simonmar at microsoft.com>**20071205091334] 
[Add singletonP to GHC.PArr
Roman Leshchinskiy <rl at cse.unsw.edu.au>**20071205220859] 
[FIX #1621: bug in Windows code for getCPUTime
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20071204153940] 
[protect against concurrent access to the signal handlers (#1922)
Simon Marlow <simonmar at microsoft.com>**20071204110817] 
[restore fdToHandle' to avoid breaking clients (#1109)
Simon Marlow <simonmar at microsoft.com>**20071130135122
 
] 
[note about how to convert CTime (aka EpochTime) to UTCTime
Simon Marlow <simonmar at microsoft.com>**20071130101648] 
[Fix some URLs
Ian Lynagh <igloo at earth.li>**20071126214213] 
[Fix some links in haddock docs
Ian Lynagh <igloo at earth.li>**20071126184428] 
[Don't try to make haddock links to the mtl package as we don't depend on it
Ian Lynagh <igloo at earth.li>**20071126170631] 
[Escape some special characters in haddock docs
Ian Lynagh <igloo at earth.li>**20071126163443] 
[FIX BUILD: maybeUpdateFile: ignore failures when removing the target
Simon Marlow <simonmar at microsoft.com>**20071123092219] 
[FIX #1753
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20071121102248] 
[oops, we forgot to export traceShow
Simon Marlow <simonmar at microsoft.com>**20071121094300] 
[Fix compilation with GHC 6.2.x
Simon Marlow <simonmar at microsoft.com>**20071121084341] 
[Move file locking into the RTS, fixing #629, #1109
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20071120102042
 This avoids make doing unnecessary work after 'setup makefile'.
] 
[fix comment
Simon Marlow <simonmar at microsoft.com>**20071116091227] 
[Fix ` characters in elem's haddock docs
Ian Lynagh <igloo at earth.li>**20071110173052] 
[Filter out GHC.Prim also for the Haddock step
David Waern <david.waern at gmail.com>**20071109000806
 Please merge to the GHC 6.8.2 branch
] 
[Add module of special magic GHC desugaring helper functions
Simon Marlow <simonmar at microsoft.com>**20071102160054
 Currently containing only one such helper: (>>>) for arrow desugaring
] 
[add Control.Category to the nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20071030120459] 
[fix nhc98 build: need a qualified Prelude import
Malcolm.Wallace at cs.york.ac.uk**20071030120410] 
[Fix performance regression: re-instate -funbox-strict-fields
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20071029131921] 
[new Control.Category, ghc ticket #1773
Ashley Yakeley <ashley at semantic.org>**20071029022526] 
[new Control.Compositor module
Ashley Yakeley <ashley at semantic.org>**20071013074851
 
 The Compositor class is a superclass of Arrow.
] 
[Fix doc building with Haddock 0.9
Simon Marlow <simonmar at microsoft.com>**20071024090947
 I was using a recent build here, which is more tolerant.
] 
[FIX #1258: document that openTempFile is secure(ish)
Simon Marlow <simonmar at microsoft.com>**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 <duncan at haskell.org>**20071022132708
 specify build-type and cabal-version >= 1.2
 put extra-tmp-files in the right place
 use os(windows) rather than os(mingw32)
] 
[base in 6.8 and head branch should be version 3.0
Don Stewart <dons at galois.com>**20071007150408] 
[FIX #1652: openTempFile should accept an empty string for the directory
Simon Marlow <simonmar at microsoft.com>**20071018122345] 
[clean up duplicate code
Simon Marlow <simonmar at microsoft.com>**20071017141311] 
[expose the value of +RTS -N as GHC.Conc.numCapabilities (see #1733)
Simon Marlow <simonmar at microsoft.com>**20071009132042] 
[typo
Simon Marlow <simonmar at microsoft.com>**20070917130703] 
[put extra-tmp-files field in the right place
Simon Marlow <simonmar at microsoft.com>**20070914140812] 
[Add more entries to boring file
Ian Lynagh <igloo at earth.li>**20070913210500] 
[Add a boring file
Ian Lynagh <igloo at earth.li>**20070913204641] 
[TAG 2007-09-13
Ian Lynagh <igloo at earth.li>**20070913215720] 
[FIX #1689 (openTempFile returns wrong filename)
Tim Chevalier <chevalier at alum.wellesley.edu>**20070913052025] 
[TAG ghc-6.8 branched 2007-09-03
Ian Lynagh <igloo at earth.li>**20070903155541] 
[Remove some incorrect rules; fixes #1658: CSE [of Doubles] changes semantics
Ian Lynagh <igloo at earth.li>**20070904134140] 
[make hWaitForInput/hReady not fail with "invalid argument" on Windows
Simon Marlow <simonmar at microsoft.com>**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 <igloo at earth.li>**20070830154131] 
[Fix building HashTable: Use ord rather than fromEnum
Ian Lynagh <igloo at earth.li>**20070830150214] 
[Better hash functions for Data.HashTable, from Jan-Willem Maessen
Ian Lynagh <igloo at earth.li>**20070830142844] 
[Remove redundant include/Makefile
Ian Lynagh <igloo at earth.li>**20070828205659] 
[Make arrays safer (e.g. trac #1046)
Ian Lynagh <igloo at earth.li>**20070810163405] 
[delete configure droppings in setup clean
Simon Marlow <simonmar at microsoft.com>**20070824104100] 
[FIX #1282: 64-bit unchecked shifts are not exported from base
Simon Marlow <simonmar at microsoft.com>**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 <igloo at earth.li>**20070821140706
 As pointed out in
 http://www.haskell.org/pipermail/glasgow-haskell-bugs/2007-August/009545.html
 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 <ross at soi.city.ac.uk>**20070819233500] 
[fpstring.h has moved to bytestring
Ross Paterson <ross at soi.city.ac.uk>**20070819233815] 
[remove now-unused SIG constants
Ross Paterson <ross at soi.city.ac.uk>**20070819233745] 
[include Win32 extra-libraries for non-GHC's too
Ross Paterson <ross at soi.city.ac.uk>**20070819233611] 
[Don't import Distribution.Setup in Setup.hs as we no longer need it
Ian Lynagh <igloo at earth.li>**20070816151643] 
[Correct the swapMVar haddock doc
Ian Lynagh <igloo at earth.li>**20070814145028] 
[install Typeable.h for use by other packages
Malcolm.Wallace at cs.york.ac.uk**20070813112855] 
[Don't try to build modules no longer living in base.
Malcolm.Wallace at cs.york.ac.uk**20070813112803] 
[Move Data.{Foldable,Traversable} back to base
Ian Lynagh <igloo at earth.li>**20070812165654
 The Array instances are now in Data.Array.
] 
[Remove bits left over from the old build system
Ian Lynagh <igloo at earth.li>**20070811135019] 
[Move the datamap001 (our only test) to the containers package
Ian Lynagh <igloo at earth.li>**20070803180932] 
[Data.Array* and Data.PackedString have now moved to their own packages
Ian Lynagh <igloo at earth.li>**20070801235542] 
[Remove a number of modules now in a "containers" package
Ian Lynagh <igloo at earth.li>**20070801223858] 
[Remove System.Posix.Signals (moving to unix)
Ian Lynagh <igloo at earth.li>**20070729215213] 
[bytestring is now in its own package
Ian Lynagh <igloo at earth.li>**20070729132215] 
[Export throwErrnoPath* functions
Ian Lynagh <igloo at earth.li>**20070722002923] 
[Add simple haddock docs for throwErrnoPath* functions
Ian Lynagh <igloo at earth.li>**20070722002817] 
[Move throwErrnoPath* functions from unix:System.Posix.Error
Ian Lynagh <igloo at earth.li>**20070722002746] 
[Clarify the swapMVar haddock doc
Ian Lynagh <igloo at earth.li>**20070807185557] 
[fix Haddock markup
Simon Marlow <simonmar at microsoft.com>**20070802081717] 
[Temporarily fix breakage for nhc98.
Malcolm.Wallace at 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 at 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 <igloo at earth.li>**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 <igloo at earth.li>**20070729161739] 
[Use cabal configurations rather than Setup hacks
Ian Lynagh <igloo at earth.li>**20070729132157] 
[Handle buffers should be allocated with newPinnedByteArray# always
Simon Marlow <simonmar at microsoft.com>**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 <ross at soi.city.ac.uk>**20070724114003] 
[Hugs only: avoid dependency cycle
Ross Paterson <ross at soi.city.ac.uk>**20070724113852] 
[open(Binary)TempFile is now portable
Ian Lynagh <igloo at earth.li>**20070722152752] 
[Tweak temporary file filename chooser
Ian Lynagh <igloo at earth.li>**20070722105445] 
[Move open(Binary)TempFile to System.IO
Ian Lynagh <igloo at earth.li>**20070722010205] 
[Rename openFd to fdToHandle'
Ian Lynagh <igloo at earth.li>**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 <igloo at earth.li>**20070721002119] 
[fix Data.Map.updateAt
Bertram Felgenhauer <int-e at gmx.de>**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 <simonmar at microsoft.com>**20070719161419
 This helps reduce the memory requirements for a closed but unfinalised
 Handle.
] 
[Implement GHC.Environment.getFullArgs
Ian Lynagh <igloo at earth.li>**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 <igloo at earth.li>**20070714235204] 
[no need to hide Maybe
Malcolm.Wallace at cs.york.ac.uk**20070710154058] 
[Add a more efficient Data.List.foldl' for GHC (from GHC's utils/Util.lhs)
Ian Lynagh <igloo at earth.li>**20070706205526] 
[Remove include-dirs ../../includes and ../../rts
Ian Lynagh <igloo at earth.li>**20070705205356
 We get these by virtue of depending on the rts package.
] 
[FIX #1131 (newArray_ allocates an array full of garbage)
Simon Marlow <simonmar at microsoft.com>**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 at cs.york.ac.uk**20070702150355] 
[Word is a type synonym in nhc98 - so class instance not permitted.
Malcolm.Wallace at cs.york.ac.uk**20070629122035] 
[fix bug in writes to blocking FDs in the non-threaded RTS
Simon Marlow <simonmar at microsoft.com>**20070628134320] 
[Modernize printf.
lennart.augustsson at 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 <john at repetae.net>**20070608182353] 
[Use "--  //" (2 spaces) rather than "-- //" (1) to avoid tripping haddock up
Ian Lynagh <igloo at earth.li>**20070627010930
 Are we nearly there yet?
] 
[Use a combination of Haskell/C comments to ensure robustness.
Malcolm.Wallace at 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 at 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 <simonmar at microsoft.com>**20070622073424] 
[Hugs now gets MonadFix(mfix) from its prelude
Ross Paterson <ross at soi.city.ac.uk>**20070620000343] 
[Typo (consUtils.hs -> consUtils.h)
Ian Lynagh <igloo at earth.li>**20070619124140] 
[install dependent include files and Typeable.h
Bertram Felgenhauer <int-e at gmx.de>**20070613041734] 
[update prototype following inputReady->fdReady change
Simon Marlow <simonmar at microsoft.com>**20070614095309] 
[FIX hGetBuf001: cut-and-pasto in readRawBufferNoBlock
Simon Marlow <simonmar at microsoft.com>**20070614094222] 
[fix description of CWStringLen
Ross Paterson <ross at soi.city.ac.uk>**20070605223345] 
[Remove unsafeCoerce-importing kludgery in favor of Unsafe.Coerce
Isaac Dupree <id at isaac.cedarswampstudios.org>**20070601203625] 
[--configure-option and --ghc-option are now provided by Cabal
Ross Paterson <ross at soi.city.ac.uk>**20070604115233] 
[Data.PackedString: Data.Generics is GHC-only
Ross Paterson <ross at soi.city.ac.uk>**20070529232427] 
[Add Data instance for PackedString; patch from greenrd in trac #1263
Ian Lynagh <igloo at earth.li>**20070529205420] 
[Control.Concurrent documentation fix
shae at ScannedInAvian.com**20070524163325] 
[add nhc98-options: field to .cabal file
Malcolm.Wallace at cs.york.ac.uk**20070528122626] 
[add a dummy implementation of System.Timeout.timeout for nhc98
Malcolm.Wallace at cs.york.ac.uk**20070528110309] 
[Add System.Timeout to base.cabal
Ian Lynagh <igloo at earth.li>**20070527123314
 Filtered out for non-GHC by Setup.hs.
] 
[add module Data.Fixed to nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20070525141021] 
[DIRS now lives in package Makefile, not script/pkgdirlist
Malcolm.Wallace at cs.york.ac.uk**20070525111749] 
[delete unused constants
Ross Paterson <ross at soi.city.ac.uk>**20070525001741] 
[remove System.Cmd and System.Time too
Malcolm.Wallace at cs.york.ac.uk**20070524163200] 
[remove locale as well
Malcolm.Wallace at cs.york.ac.uk**20070524161943] 
[nhc98 version of instance Show (a->b) copied from Prelude
Malcolm.Wallace at cs.york.ac.uk**20070524160615] 
[remove directory, pretty, and random bits from base for nhc98
Malcolm.Wallace at cs.york.ac.uk**20070524160608] 
[Remove Makefile and package.conf.in (used in the old build system)
Ian Lynagh <igloo at earth.li>**20070524142545] 
[Split off process package
Ian Lynagh <igloo at earth.li>**20070523210523] 
[Fix comment: maperrno is in Win32Utils.c, not runProcess.c
Ian Lynagh <igloo at earth.li>**20070523181331] 
[System.Locale is now split out
Ian Lynagh <igloo at earth.li>**20070519132638] 
[Split off directory, random and old-time packages
Ian Lynagh <igloo at earth.li>**20070519120642] 
[Remove Control.Parallel*, now in package parallel
Ian Lynagh <igloo at earth.li>**20070518165431] 
[Remove the pretty-printing modules (now in package pretty(
Ian Lynagh <igloo at earth.li>**20070518162521] 
[add install-includes: field
Simon Marlow <simonmar at microsoft.com>**20070517094948] 
[correct the documentation for newForeignPtr
Simon Marlow <simonmar at microsoft.com>**20070516082019] 
[When doing safe writes, handle EAGAIN rather than raising an exception
Simon Marlow <simonmar at microsoft.com>**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 <igloo at earth.li>**20070514110409] 
[Build GHC/Prim.hs and GHC/PrimopWrappers.hs from Cabal
Ian Lynagh <igloo at earth.li>**20070509142655] 
[fix imports for non-GHC
Ross Paterson <ross at soi.city.ac.uk>**20070513001138] 
[Give an example of how intersection takes elements from the first set
Ian Lynagh <igloo at earth.li>**20070512160253] 
[further clarify the docs for 'evaluate'
Malcolm.Wallace at cs.york.ac.uk**20070508101124] 
[improve documentation for evaluate
Simon Marlow <simonmar at microsoft.com>**20070508081712] 
[FIX: #724 (tee complains if used in a process started by ghc)
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20070426135931] 
[Make Control.Exception buildable by nhc98.
Malcolm.Wallace at 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 at 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 at microsoft**20070503093707] 
[Remove Splittable class (a vestige of linear implicit parameters)
simonpj at microsoft**20070221104329] 
[Add IsString to exports of GHC.Exts
simonpj at microsoft**20070221104249] 
[tweak documentation as per suggestion from Marc Weber on libraries at haskell.org
Simon Marlow <simonmar at microsoft.com>**20070426075921] 
[Add extra libraries when compiling with GHC on Windows
Ian Lynagh <igloo at earth.li>**20070424213127] 
[Follow Cabal changes in Setup.hs
Ian Lynagh <igloo at earth.li>**20070418114345] 
[inclusion of libc.h is conditional on __APPLE__
Malcolm.Wallace at cs.york.ac.uk**20070417085556] 
[MERGE: fix ugly uses of memcpy foreign import inside ST
Simon Marlow <simonmar at microsoft.com>**20070416101530
 fixes cg026
] 
[Fix configure with no --with-cc
Ian Lynagh <igloo at earth.li>**20070415165143] 
[MacOS 10.3 needs #include <libc.h> as well
Malcolm.Wallace at cs.york.ac.uk**20070414155507] 
[For nhc98 only, use hsc2hs to determine System.Posix.Types.
Malcolm.Wallace at 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 <simonmar at microsoft.com>**20070413151307] 
[Remove unnecesary SOURCE import of GHC.Err in GHC.Pack
Ian Lynagh <igloo at earth.li>**20070412235908] 
[add System.Posix.Types to default nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20070412195026] 
[mark System.IO.openTempFile as non-portable in haddocks
Malcolm.Wallace at cs.york.ac.uk**20070412135359] 
[Don't turn on -Werror in Data.Fixed
Ian Lynagh <igloo at earth.li>**20070411155721
 This may be responsible for the x86_64/Linux nightly build failing.
] 
[Fix -Wall warnings
Ian Lynagh <igloo at earth.li>**20070411004929] 
[Add missing case in removePrefix
Ian Lynagh <igloo at earth.li>**20070411002537] 
[Allow additional options to pass on to ./configure to be given
Ian Lynagh <igloo at earth.li>**20070406151856] 
[Hugs only: fix location of unsafeCoerce
Ross Paterson <ross at soi.city.ac.uk>**20070406113731] 
[fix isPortableBuild test
Ross Paterson <ross at soi.city.ac.uk>**20070406111304] 
[Unsafe.Coerce doesn't need Prelude
Ian Lynagh <igloo at earth.li>**20070405175930] 
[make Setup and base.cabal suitable for building the libraries with GHC
Ian Lynagh <igloo at earth.li>**20070308163824] 
[HsByteArray doesn't exist
Ian Lynagh <igloo at earth.li>**20070404163051] 
[Don't use Fd/FD in foreign decls
Ian Lynagh <igloo at earth.li>**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 <igloo at earth.li>**20070404155732] 
[Fix braino
Ian Lynagh <igloo at earth.li>**20070404144508] 
[Fix incorrect changes to C types in a foreign import for nhc98.
Malcolm.Wallace at 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 <igloo at earth.li>**20070403194943] 
[add new module Unsafe.Coerce to build system
Malcolm.Wallace at cs.york.ac.uk**20070403131333] 
[Fix type mismatches between foreign imports and HsBase.h
Ian Lynagh <igloo at earth.li>**20070403001611
 
 Merge to stable, checking for interface changes.
] 
[put 'unsafeCoerce' in a standard location
Malcolm.Wallace at cs.york.ac.uk**20061113114103] 
[fix for nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20070402141712] 
[Function crossMapP for fixing desugaring of comprehensions
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20070402082906
 
 Merge into 6.6 branch.
] 
[Add min/max handling operations for IntSet/IntMap
jeanphilippe.bernardy at gmail.com**20070315072352] 
[Monoid instance for Maybe and two wrappers: First and Last. trac proposal #1189
Jeffrey Yasskin <jyasskin at gmail.com>**20070309062550] 
[Fix the type of wgencat
Ian Lynagh <igloo at earth.li>**20070329164223] 
[fix strictness of foldr/build rule for take, see #1219
Simon Marlow <simonmar at microsoft.com>**20070327103941] 
[remove Makefile.inc (only affects nhc98)
Malcolm.Wallace at cs.york.ac.uk**20070320120057] 
[copyBytes copies bytes, not elements; fixes trac #1203
Ian Lynagh <igloo at earth.li>**20070312113555] 
[Add ioeGetLocation, ioeSetLocation to System/IO/Error.hs; trac #1191
Ian Lynagh <igloo at earth.li>**20070304130315] 
[fix race condition in prodServiceThread
Simon Marlow <simonmar at microsoft.com>**20070307134330
 See #1187
] 
[Prevent duplication of unsafePerformIO on a multiprocessor
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20070305160921] 
[document timeout limitations
Peter Simons <simons at cryp.to>**20070228223540] 
[So many people were involved in the writing of this module that
Peter Simons <simons at cryp.to>**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 <simons at cryp.to>**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 <chak at cse.unsw.edu.au>**20070305055807] 
[Add Data.String, containing IsString(fromString); trac proposal #1126
Ian Lynagh <igloo at earth.li>**20070130134841
 This is used by the overloaded strings extension (-foverloaded-strings in GHC).
] 
[GHC.PArr: add bounds checking
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20070302053224] 
[Bump nhc98 stack size for System/Time.hsc
sven.panne at aedion.de**20070301153009] 
[FDs are CInts now, fixing non-GHC builds
sven.panne at aedion.de**20070225105620] 
[Fixed PArr.dropP
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**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 <igloo at earth.li>**20070220141039
 Otherwise we only close one of the FDs when closing the handle.
 Fixes trac #1149.
] 
[Remove more redundant FD conversions
Ian Lynagh <igloo at earth.li>**20070220092520] 
[Fix FD changes on Windows
Ian Lynagh <igloo at earth.li>**20070220091516] 
[Consistently use CInt rather than Int for FDs
Ian Lynagh <igloo at earth.li>**20070219233854] 
[Fix the types of minView/maxView (ticket #1134)
jeanphilippe.bernardy at gmail.com**20070210065115] 
[fix for hashString, from Jan-Willem Maessen (see #1137)
Simon Marlow <simonmar at microsoft.com>**20070215094304
 
] 
[fix to getUSecOfDay(): arithmetic was overflowing
Simon Marlow <simonmar at microsoft.com>**20070214161719] 
[The Windows counterpart to 'wrapround of thread delays'
Ian Lynagh <igloo at earth.li>**20070209173510] 
[wrapround of thread delays
Neil Davies <SemanticPhilosopher at gmail.com>**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 <igloo at earth.li>**20070206232722] 
[Add some type sigs
Ian Lynagh <igloo at earth.li>**20070206232439] 
[Use static inline rather than extern inline/inline
Ian Lynagh <igloo at earth.li>**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 <ross at soi.city.ac.uk>**20070202190847] 
[add doc pointers to Foldable
Ross Paterson <ross at soi.city.ac.uk>**20070202110931
 
 Could be applied to STABLE.
] 
[Eliminate some warnings
Ian Lynagh <igloo at earth.li>**20060729220854
 Eliminate warnings in the libraries caused by mixing pattern matching
 with numeric literal matching.
] 
[Remove IsString(fromString) from the Prelude
Ian Lynagh <igloo at earth.li>**20070130124136] 
[Add Kleisli composition
Don Stewart <dons at cse.unsw.edu.au>**20061113015442] 
[IsString is GHC-only (so why is it in the Prelude?)
Ross Paterson <ross at soi.city.ac.uk>**20070123183007] 
[Applicative and Monad instances for Tree
Ross Paterson <ross at soi.city.ac.uk>**20070115174510] 
[Add IsString class for overloaded string literals.
lennart at augustsson.net**20061221210532] 
[Added examples, more detailed documentation to Data.List Extracting sublists functions
Andriy Palamarchuk <apa3a at yahoo.com>**20061204164710] 
[fix threadDelay
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20070116124328] 
[Fix crash with   (minBound :: Int*) `div (-1)   as result is maxBound + 1.
Ian Lynagh <igloo at earth.li>**20070115142005] 
[version of example using Tomasz Zielonka's technique
Ross Paterson <ross at soi.city.ac.uk>**20070105175907] 
[Added Unknowns for higher kinds
Pepe Iborra <mnislaih at gmail.com>**20061108155938] 
[Improved the Show instance for Unknown
Pepe Iborra <mnislaih at gmail.com>**20060813111816] 
[Show instance for GHC.Base.Unknown
mnislaih at gmail.com**20060801233530] 
[Introduce Unknowns for the closure viewer. Add breakpointCond which was missing
mnislaih at gmail.com**20060725174537] 
[Fix missing comma in Fractional documentation
Alec Berryman <alec at thened.net>**20061201173237] 
[Mention that throwTo does not guarantee promptness of delivery
simonpj at microsoft**20061211123215] 
[Add note about synhronous delivery of throwTo
simonpj at microsoft**20061211122257] 
[documentation for installHandler
Simon Marlow <simonmar at microsoft.com>**20061205154927
 merge to 6.6
] 
[dos2unix
Simon Marlow <simonmar at microsoft.com>**20061204095439] 
[don't try to compile this on Unix
Simon Marlow <simonmar at microsoft.com>**20061204095427] 
[TAG 6.6 release
Ian Lynagh <igloo at earth.li>**20061011124740] 
[TAG Version 2.1
Ian Lynagh <igloo at earth.li>**20061009114014] 
[Bump version number
Ian Lynagh <igloo at earth.li>**20061009114009] 
[Add support for the IO manager thread on Windows
Simon Marlow <simonmar at microsoft.com>**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 <simonmar at microsoft.com>**20061201144032] 
[Make sure the threaded threadDelay sleeps at least as long as it is asked to
Ian Lynagh <igloo at earth.li>**20061128204807] 
[Add comments about argument order to the definitions of gmapQ and constrFields
simonpj at microsoft**20061124164505] 
[Hugs: add Control.Parallel.Strategies
Ross Paterson <ross at soi.city.ac.uk>**20061124161039] 
[Move instance of Show Ptr to Ptr.hs (fewer orphans)
simonpj at microsoft.com**20061124100639] 
[Add type signatures
simonpj at microsoft.com**20061124100621] 
[Add an example of the use of unfoldr, following doc feedback from dozer
Don Stewart <dons at cse.unsw.edu.au>**20061124011249] 
[trim imports
Ross Paterson <ross at soi.city.ac.uk>**20061123190352] 
[Data.Graph is now portable (enable for nhc98)
Malcolm.Wallace at cs.york.ac.uk**20061123174913] 
[remove Data.FunctorM and Data.Queue
Ross Paterson <ross at soi.city.ac.uk>**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 <ross at soi.city.ac.uk>**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 <dons at cse.unsw.edu.au>**20061120120242] 
[typo in comment
Ross Paterson <ross at soi.city.ac.uk>**20061120115106] 
[fix shift docs to match ffi spec
Ross Paterson <ross at soi.city.ac.uk>**20061117003144] 
[(nhc98) use new primitive implementations of h{Put,Get}Buf.
Malcolm.Wallace at cs.york.ac.uk**20061116173104] 
[The wrong 'cycle' was exported from Data.ByteString.Lazy.Char8, spotted by sjanssen
Don Stewart <dons at cse.unsw.edu.au>**20061110021311] 
[LPS chunk sizes should be 16 bytes, not 17. 
Don Stewart <dons at cse.unsw.edu.au>**20061110021254] 
[Update comments on Prelude organisation in GHC/Base.lhs
Ian Lynagh <igloo at earth.li>**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 at cs.chalmers.se**20061113224202] 
[Control.Parallel.Strategies: added NFData instances for Data.Int.*, Data.Word.*, Maybe, Either, Map, Set, Tree, IntMap, IntSet.
bringert at cs.chalmers.se**20061113221843] 
[Control.Parallel.Strategies: deprecate sPar, sSeq, Assoc, fstPairFstList, force and sforce. 
bringert at 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 at cs.york.ac.uk**20061113113221] 
[Control.Parallel.Strategies: clarified documentation of parListChunk.
bringert at cs.chalmers.se**20061112232904] 
[Added and cleaned up Haddock comments in Control.Parallel.Strategies.
bringert at 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 <igloo at earth.li>**20061111205916] 
[add doc link to bound threads section
Ross Paterson <ross at soi.city.ac.uk>**20060929103252] 
[hide Data.Array.IO.Internals
Ross Paterson <ross at soi.city.ac.uk>**20061111113248
 
 It's hidden from haddock, and everything it exports is re-exported by
 Data.Array.IO.
] 
[add Data.Function
Malcolm.Wallace at cs.york.ac.uk**20061110142710] 
[add Data.Function
Ross Paterson <ross at soi.city.ac.uk>**20061110141354] 
[whitespace only
Ross Paterson <ross at soi.city.ac.uk>**20061110141326] 
[move fix to Data.Function
Ross Paterson <ross at soi.city.ac.uk>**20061110141120] 
[import Prelude
Ross Paterson <ross at soi.city.ac.uk>**20061110140445] 
[Added Data.Function (Trac ticket #979).
Nils Anders Danielsson <nad at cs.chalmers.se>**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 at cs.york.ac.uk**20061110113222] 
[redefine writeFile and appendFile using withFile
Ross Paterson <ross at soi.city.ac.uk>**20061107140359] 
[add withFile and withBinaryFile (#966)
Ross Paterson <ross at soi.city.ac.uk>**20061107134510] 
[remove conflicting import for nhc98
Malcolm.Wallace at cs.york.ac.uk**20061108111215] 
[Add intercalate to Data.List (ticket #971)
Josef Svenningsson <josef.svenningsson at gmail.com>**20061102122052] 
[non-GHC: fix canonicalizeFilePath
Ross Paterson <ross at soi.city.ac.uk>**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 <simonmar at microsoft.com>**20061107121141] 
[Update documentation for hWaitForInput
Simon Marlow <simonmar at microsoft.com>**20061107111430
 See #972
 Merge to 6.6 branch.
] 
[Use unchecked shifts to implement Data.Bits.rotate
Samuel Bronson <naesten at gmail.com>**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 <ross at soi.city.ac.uk>**20061106124140] 
[fix example in docs
Ross Paterson <ross at soi.city.ac.uk>**20061106115628] 
[Add intercalate and split to Data.List
Josef Svenningsson <josef.svenningsson at gmail.com>*-20061024172357] 
[Data.Generics.Basics is GHC-only
Ross Paterson <ross at soi.city.ac.uk>**20061102111736] 
[#ifdef around non-portable Data.Generics.Basics
Malcolm.Wallace at cs.york.ac.uk**20061102103445] 
[Add deriving Data to Complex
simonpj at microsoft**20061101102059] 
[minor clarification of RandomGen doc
Ross Paterson <ross at soi.city.ac.uk>**20061030230842] 
[rearrange docs a bit
Ross Paterson <ross at soi.city.ac.uk>**20061030161223] 
[Add intercalate and split to Data.List
Josef Svenningsson <josef.svenningsson at gmail.com>**20061024172357] 
[Export pseq from Control.Parallel, and use it in Control.Parallel.Strategies
Simon Marlow <simonmar at microsoft.com>**20061027150141] 
[`par` should be infixr 0
Simon Marlow <simonmar at microsoft.com>**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 <ross at soi.city.ac.uk>**20061023163925] 
[Use the new Any type for dynamics (GHC only)
simonpj at microsoft**20061019160408] 
[add Data.Sequence to nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20061012135200] 
[Remove Data.FiniteMap, add Control.Applicative, Data.Traversable, and
Malcolm.Wallace at cs.york.ac.uk**20061012095605
 Data.Foldable to the nhc98 build.
] 
[STM invariants
tharris at microsoft.com**20061007123253] 
[Inline shift in GHC's Bits instances for {Int,Word}{,8,16,32,64}
Samuel Bronson <naesten at gmail.com>**20061009020906] 
[Don't create GHC.Prim when bootstrapping; we can't, and we don't need it
Ian Lynagh <igloo at earth.li>**20061004165355] 
[Data.ByteString: fix lazyness of take, drop & splitAt
Don Stewart <dons at cse.unsw.edu.au>**20061005011703
 
 ByteString.Lazy's take, drop and splitAt were too strict when demanding
 a byte string. Spotted by Einar Karttunen. Thanks to him and to Bertram
 Felgenhauer for explaining the problem and the fix.
 
] 
[Fix syntax error that prevents building Haddock documentation on Windows
brianlsmith at gmail.com**20060917013530] 
[Hugs only: unbreak typeRepKey
Ross Paterson <ross at soi.city.ac.uk>**20060929102743] 
[make hGetBufNonBlocking do something on Windows w/ -threaded
Simon Marlow <simonmar at microsoft.com>**20060927145811
 hGetBufNonBlocking will behave the same as hGetBuf on Windows now, which
 is better than just crashing (which it did previously).
] 
[add typeRepKey :: TypeRep -> IO Int
Simon Marlow <simonmar at microsoft.com>**20060927100342
 See feature request #880
] 
[fix header comment
Ross Paterson <ross at soi.city.ac.uk>**20060926135843] 
[Add strict versions of insertWith and insertWithKey (Data.Map)
jeanphilippe.bernardy at gmail.com**20060910162443] 
[doc tweaks, including more precise equations for evaluate
Ross Paterson <ross at soi.city.ac.uk>**20060910115259] 
[Sync Data.ByteString with stable branch
Don Stewart <dons at cse.unsw.edu.au>**20060909050111
 
 This patch: 
     * hides the LPS constructor (its in .Base if you need it)
     * adds functions to convert between strict and lazy bytestrings
     * and adds readInteger
 
] 
[Typeable1 instances for STM and TVar
Ross Paterson <ross at soi.city.ac.uk>**20060904231425] 
[remove obsolete Hugs stuff
Ross Paterson <ross at soi.city.ac.uk>**20060904223944] 
[Cleaner isInfixOf suggestion from Ross Paterson
John Goerzen <jgoerzen at complete.org>**20060901143654] 
[New function isInfixOf that searches a list for a given sublist
John Goerzen <jgoerzen at complete.org>**20060831151556
 
 Example:
 
 isInfixOf "Haskell" "I really like Haskell." -> True
 isInfixOf "Ial" "I really like Haskell." -> False
 
 This function was first implemented in MissingH as MissingH.List.contains
] 
[Better doc on Data.Map.lookup: explain what the monad is for
jeanphilippe.bernardy at gmail.com**20060903133440] 
[fix hDuplicateTo on Windows
Simon Marlow <simonmar at microsoft.com>**20060901150016
 deja vu - I'm sure I remember fixing this before...
] 
[Improve documentation of atomically
simonpj at microsoft**20060714120207] 
[Add missing method genRange for StdGen (fixes #794)
simonpj at microsoft**20060707151901
 
 	MERGE TO STABLE
 
 Trac #794 reports (correctly) that the implementation of StdGen
 only returns numbers in the range (0..something) rather than 
 (minBound, maxBound), which is what StdGen's genRange claims.
 
 This commit fixes the problem, by implementing genRange for StdGen
 (previously it just used the default method).
 
 
] 
[mark nhc98 import hack
Ross Paterson <ross at soi.city.ac.uk>**20060831125219] 
[remove some outdated comments
Simon Marlow <simonmar at microsoft.com>**20060831104200] 
[import Control.Arrow.ArrowZero to help nhc98's type checker
Malcolm.Wallace at cs.york.ac.uk**20060831101105] 
[remove Text.Regex(.Posix) from nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20060831101016] 
[add Data.Foldable.{msum,asum}, plus tweaks to comments
Ross Paterson <ross at soi.city.ac.uk>**20060830163521] 
[fix doc typo
Ross Paterson <ross at soi.city.ac.uk>**20060830134123] 
[add Data.Foldable.{for_,forM_} and Data.Traversable.{for,forM}
Ross Paterson <ross at soi.city.ac.uk>**20060830133805
 
 generalizing Control.Monad.{forM_,forM}
] 
[Make length a good consumer
simonpj at microsoft*-20060508142726
 
 Make length into a good consumer.  Fixes Trac bug #707.
 
 (Before length simply didn't use foldr.)
 
] 
[Add Control.Monad.forM and forM_
Don Stewart <dons at cse.unsw.edu.au>**20060824081118
 
 flip mapM_ is more and more common, I find. Several suggestions have
 been made to add this, as foreach or something similar. This patch 
 does just that:
 
     forM  :: (Monad m) => [a] -> (a -> m b) -> m [b]
     forM_ :: (Monad m) => [a] -> (a -> m b) -> m ()
 
 So we can write:
      
     Prelude Control.Monad> forM_ [1..4] $ \x -> print x
     1
     2
     3
     4
 
] 
[Hide internal module from haddock in Data.ByteString
Don Stewart <dons at cse.unsw.edu.au>**20060828011515] 
[add advice on avoiding import ambiguities
Ross Paterson <ross at soi.city.ac.uk>**20060827170407] 
[expand advice on importing these modules
Ross Paterson <ross at soi.city.ac.uk>**20060827164044] 
[add Haddock marker
Ross Paterson <ross at soi.city.ac.uk>**20060827115140] 
[Clarify how one hides Prelude.catch
Don Stewart <dons at cse.unsw.edu.au>**20060826124346
 
 User feedback indicated that an example was required, of how to hide
 Prelude.catch, so add such an example to the docs
 
] 
[Workaround for OSes that don't have intmax_t and uintmax_t
Ian Lynagh <igloo at earth.li>**20060825134936
 OpenBSD (and possibly others) do not have intmax_t and uintmax_t types:
     http://www.mail-archive.com/haskell-prime@haskell.org/msg01548.html
 so substitute (unsigned) long long if we have them, otherwise
 (unsigned) long.
 
] 
[add docs for par
Simon Marlow <simonmar at microsoft.com>**20060825110610] 
[document minimal complete definition for Bits
Ross Paterson <ross at soi.city.ac.uk>**20060824140504] 
[C regex library bits have moved to the regex-posix package
Simon Marlow <simonmar at microsoft.com>**20060824132311] 
[Add shared Typeable support (ghc only)
Esa Ilari Vuokko <ei at vuokko.info>**20060823003126] 
[this should have been removed with the previous patch
Simon Marlow <simonmar at microsoft.com>**20060824121223] 
[remove Text.Regx & Text.Regex.Posix
Simon Marlow <simonmar at microsoft.com>**20060824094615
 These are subsumed by the new regex-base, regex-posix and regex-compat
 packages.
] 
[explicitly tag Data.ByteString rules with the FPS prefix.
Don Stewart <dons at cse.unsw.edu.au>**20060824041326] 
[Add spec rules for sections in Data.ByteString
Don Stewart <dons at cse.unsw.edu.au>**20060824012611] 
[Sync Data.ByteString with current stable branch, 0.7
Don Stewart <dons at cse.unsw.edu.au>**20060823143338] 
[add notes about why copyFile doesn't remove the target
Simon Marlow <simonmar at microsoft.com>**20060823095059] 
[copyFile: try removing the target file before opening it for writing
Simon Marlow <simonmar at microsoft.com>*-20060822121909] 
[copyFile: try removing the target file before opening it for writing
Simon Marlow <simonmar at microsoft.com>**20060822121909] 
[add alternative functors and extra instances
Ross Paterson <ross at soi.city.ac.uk>**20060821152151
 
 * Alternative class, for functors with a monoid
 * instances for Const
 * instances for arrows
] 
[generate Haddock docs on all platforms
Simon Marlow <simonmar at microsoft.com>**20060821131612] 
[remove extra comma from import
Ross Paterson <ross at soi.city.ac.uk>**20060819173954] 
[fix docs for withC(A)StringLen
Ross Paterson <ross at soi.city.ac.uk>**20060818170328] 
[use Haskell'98 compliant indentation in do blocks
Malcolm.Wallace at cs.york.ac.uk**20060818130810] 
[use correct names of IOArray operations for nhc98
Malcolm.Wallace at cs.york.ac.uk**20060818130714] 
[add mapMaybe and mapEither, plus WithKey variants
Ross Paterson <ross at soi.city.ac.uk>**20060817235041] 
[remove Text.Html from nhc98 build
Malcolm.Wallace at cs.york.ac.uk**20060817135502] 
[eliminate more HOST_OS tests
Ross Paterson <ross at soi.city.ac.uk>**20060815190609] 
[Hugs only: disable unused process primitives
Ross Paterson <ross at soi.city.ac.uk>**20060813184435
 
 These were the cause of Hugs bug #30, I think, and weren't used by Hugs anyway.
] 
[markup fix to Data.HashTable
Ross Paterson <ross at soi.city.ac.uk>**20060812103835] 
[revert removal of ghcconfig.h from package.conf.in
Ross Paterson <ross at soi.city.ac.uk>**20060812082702
 
 as it's preprocessed with -undef (pointed out by Esa Ilari Vuokko)
] 
[fix Data.HashTable for non-GHC
Ross Paterson <ross at soi.city.ac.uk>**20060811231521] 
[remove deprecated 'withObject'
Simon Marlow <simonmar at microsoft.com>**20060811152350] 
[Jan-Willem Maessen's improved implementation of Data.HashTable
Simon Marlow <simonmar at microsoft.com>**20060811151024
 Rather than incrementally enlarging the hash table, this version
 just does it in one go when the table gets too full.
] 
[Warning police: Make some prototypes from the RTS known
sven.panne at aedion.de**20060811144629] 
[Warning police: Removed useless catch-all clause
sven.panne at aedion.de**20060811142208] 
[reduce dependency on ghcconfig.h
Ross Paterson <ross at soi.city.ac.uk>**20060811124030
 
 The only remaining use is in cbits/dirUtils.h, which tests solaris2_HOST_OS
 
 (Also System.Info uses ghcplatform.h and several modules import MachDeps.h
 to get SIZEOF_* and ALIGNMENT_* from ghcautoconf.h)
] 
[(non-GHC only) track MArray interface change
Ross Paterson <ross at soi.city.ac.uk>**20060810182902] 
[move Text.Html to a separate package
Simon Marlow <simonmar at microsoft.com>**20060810113017] 
[bump version to 2.0
Simon Marlow <simonmar at microsoft.com>**20060810112833] 
[Remove deprecated Data.FiniteMap and Data.Set interfaces
Simon Marlow <simonmar at microsoft.com>**20060809153810] 
[move altzone test from ghc to base package
Ross Paterson <ross at soi.city.ac.uk>**20060809124259] 
[remove unnecessary #include "ghcconfig.h"
Ross Paterson <ross at soi.city.ac.uk>**20060809123812] 
[Change the API of MArray to allow resizable arrays
Simon Marlow <simonmar at microsoft.com>**20060809100548
 See #704
 
 The MArray class doesn't currently allow a mutable array to change its
 size, because of the pure function 
 
   bounds :: (HasBounds a, Ix i) => a i e -> (i,i)
 
 This patch removes the HasBounds class, and adds
 
   getBounds :: (MArray a e m, Ix i) => a i e -> m (i,i)
 
 to the MArray class, and
 
   bounds :: (IArray a e, Ix i) => a i e -> (i,i)
 
 to the IArray class.
 
 The reason that bounds had to be incorporated into the IArray class is
 because I couldn't make DiffArray work without doing this.  DiffArray
 acts as a layer converting an MArray into an IArray, and there was no
 way (that I could find) to define an instance of HasBounds for
 DiffArray.
] 
[deprecate this module.
Simon Marlow <simonmar at microsoft.com>**20060808100708] 
[add traceShow (see #474)
Simon Marlow <simonmar at microsoft.com>**20060807155545] 
[remove spurious 'extern "C" {'
Simon Marlow <simonmar at microsoft.com>**20060724160258] 
[Fix unsafeIndex for large ranges
Simon Marlow <simonmar at microsoft.com>**20060721100225] 
[disambiguate uses of foldr for nhc98 to compile without errors
Malcolm.Wallace at cs.york.ac.uk**20060711161614] 
[make Control.Monad.Instances compilable by nhc98
Malcolm.Wallace at cs.york.ac.uk**20060711160941] 
[breakpointCond
Lemmih <lemmih at gmail.com>**20060708055528] 
[UNDO: Merge "unrecognized long opt" fix from 6.4.2
Simon Marlow <simonmar at microsoft.com>**20060705142537
 This patch undid the previous patch, "RequireOrder: do not collect
 unrecognised options after a non-opt".  I asked Sven to revert it, but
 didn't get an answer.
 
 See bug #473.
] 
[Avoid strictness in accumulator for unpackFoldr
Don Stewart <dons at cse.unsw.edu.au>**20060703091806
 
 The seq on the accumulator for unpackFoldr will break in the presence of
 head/build rewrite rules. The empty list case will be forced, producing
 an exception. This is a known issue with seq and rewrite rules that we
 just stumbled on to.
 
] 
[Disable unpack/build fusion
Don Stewart <dons at cse.unsw.edu.au>**20060702083913
 
 unpack/build on bytestrings seems to trigger a bug when interacting with
 head/build fusion in GHC.List. The bytestring001 testcase catches it.
 
 I'll investigate further, but best to disable this for now (its not
 often used anyway).
 
 Note that with -frules-off or ghc 6.4.2 things are fine. It seems to
 have emerged with the recent rules changes.
 
] 
[Import Data.ByteString.Lazy, improve ByteString Fusion, and resync with FPS head
Don Stewart <dons at cse.unsw.edu.au>**20060701084345
 
 This patch imports the Data.ByteString.Lazy module, and its helpers,
 providing a ByteString implemented as a lazy list of strict cache-sized
 chunks. This type allows the usual lazy operations to be written on
 bytestrings, including lazy IO, with much improved space and time over
 the [Char] equivalents.
 
] 
[Wibble in docs for new ForeignPtr functionsn
Don Stewart <dons at cse.unsw.edu.au>**20060609075924] 
[comments for Applicative and Traversable
Ross Paterson <ross at soi.city.ac.uk>**20060622170436] 
[default to NoBuffering on Windows for a read/write text file
Simon Marlow <simonmar at microsoft.com>**20060622144446
 Fixes (works around) #679
] 
[remove dead code
Simon Marlow <simonmar at microsoft.com>**20060622144433] 
[clarify and expand docs
Simon Marlow <simonmar at microsoft.com>**20060622112911] 
[Add minView and maxView to Map and Set
jeanphilippe.bernardy at gmail.com**20060616180121] 
[add signature for registerDelay
Ross Paterson <ross at soi.city.ac.uk>**20060614114456] 
[a few doc comments
Ross Paterson <ross at soi.city.ac.uk>**20060613142704] 
[Optimised foreign pointer representation, for heap-allocated objects
Don Stewart <dons at cse.unsw.edu.au>**20060608015011] 
[Add the inline function, and many comments
simonpj at microsoft.com**20060605115814
 
 This commit adds the 'inline' function described in the
 related patch in the compiler.
 
 I've also added comments about the 'lazy' function.
 
] 
[small intro to exceptions
Ross Paterson <ross at soi.city.ac.uk>**20060525111604] 
[export breakpoint
Simon Marlow <simonmar at microsoft.com>**20060525090456] 
[Merge in changes from fps head. Highlights:
Don Stewart <dons at cse.unsw.edu.au>**20060525065012
 
     Wed May 24 15:49:38 EST 2006  sjanssen at cse.unl.edu
       * instance Monoid ByteString
 
     Wed May 24 15:04:04 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Rearange export lists for the .Char8 modules
 
     Wed May 24 14:59:56 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Implement mapAccumL and reimplement mapIndexed using loopU
 
     Wed May 24 14:47:32 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Change the implementation of the unfoldr(N) functions.
       Use a more compact implementation for unfoldrN and change it's behaviour
       to only return Just in the case that it actually 'overflowed' the N, so
       the boundary case of unfolding exactly N gives Nothing.
       Implement unfoldr and Lazy.unfoldr in terms of unfoldrN. Use fibonacci
       growth for the chunk size in unfoldr
 
     Wed May 24 08:32:29 EST 2006  sjanssen at cse.unl.edu
       * Add unfoldr to ByteString and .Char8
       A preliminary implementation of unfoldr.
 
     Wed May 24 01:39:41 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Reorder the export lists to better match the Data.List api
 
     Tue May 23 14:04:32 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * pack{Byte,Char} -> singleton. As per fptools convention
 
     Tue May 23 14:00:51 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * elemIndexLast -> elemIndexEnd
 
     Tue May 23 13:57:34 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * In the search for a more orthogonal api, we kill breakFirst/breakLast,
         which were of dubious value
 
     Tue May 23 12:24:09 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Abolish elems. It's name implied it was unpack, but its type didn't. it made no sense
 
     Tue May 23 10:42:09 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Minor doc tidyup. Use haddock markup better.
 
     Tue May 23 11:00:31 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Simplify the join() implementation. Spotted by Duncan.
 
] 
[add a way to ask the IO manager thread to exit
Simon Marlow <simonmar at microsoft.com>**20060524121823] 
[Sync with FPS head, including the following patches:
Don Stewart <dons at cse.unsw.edu.au>**20060520030436
         
     Thu May 18 15:45:46 EST 2006  sjanssen at cse.unl.edu
       * Export unsafeTake and unsafeDrop
 
     Fri May 19 11:53:08 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Add foldl1'
 
     Fri May 19 13:41:24 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Add fuseable scanl, scanl1 + properties
 
     Fri May 19 18:20:40 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Spotted another chance to use unsafeTake,Drop (in groupBy)
 
     Thu May 18 09:24:25 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * More effecient findIndexOrEnd based on the impl of findIndex
 
     Thu May 18 09:22:49 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Eliminate special case in findIndex since it's handled anyway.
 
     Thu May 18 09:19:08 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Add unsafeTake and unsafeDrop
       These versions assume the n is in the bounds of the bytestring, saving
       two comparison tests. Then use them in varous places where we think this
       holds. These cases need double checking (and there are a few remaining
       internal uses of take / drop that might be possible to convert).
       Not exported for the moment.
 
     Tue May 16 23:15:11 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Handle n < 0 in drop and splitAt. Spotted by QC.
 
     Tue May 16 22:46:22 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Handle n <= 0 cases for unfoldr and replicate. Spotted by QC
 
     Tue May 16 21:34:11 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * mapF -> map', filterF -> filter'
 
] 
[haddock fix
Ross Paterson <ross at soi.city.ac.uk>**20060518154723] 
[simplify indexing in Data.Sequence
Ross Paterson <ross at soi.city.ac.uk>**20060518154316] 
[Move Eq, Ord, Show instances for ThreadId to GHC.Conc
Simon Marlow <simonmar at microsoft.com>**20060518113339
 Eliminates orphans.
] 
[Better error handling in the IO manager thread
Simon Marlow <simonmar at microsoft.com>**20060518113303
 In particular, handle EBADF just like rts/posix/Select.c, by waking up
 all the waiting threads.  Other errors are thrown, instead of just
 being ignored.
] 
[#define _REENTRANT 1  (needed to get the right errno on some OSs)
Simon Marlow <simonmar at microsoft.com>**20060518104151
 Part 2 of the fix for threaded RTS problems on Solaris and possibly
 *BSD (Part 1 was the same change in ghc/includes/Rts.h).
] 
[copyCString* should be in IO. Spotted by Tomasz Zielonka
Don Stewart <dons at cse.unsw.edu.au>**20060518012154] 
[add import Prelude to get dependencies right for Data/Fixed.hs
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060517222044
 Hopefully this fixes parallel builds.
] 
[Fix negative index handling in splitAt, replicate and unfoldrN. Move mapF, filterF -> map', filter' while we're here
Don Stewart <dons at cse.unsw.edu.au>**20060517020150] 
[Use our own realloc. Thus reduction functions (like filter) allocate on the Haskell heap. Makes around 10% difference.
Don Stewart <dons at cse.unsw.edu.au>**20060513051736] 
[Last two CInt fixes for 64 bit, and bracket writeFile while we're here
Don Stewart <dons at cse.unsw.edu.au>**20060512050750] 
[Some small optimisations, generalise the type of unfold
Don Stewart <dons at cse.unsw.edu.au>**20060510043309
 
     Tue May  9 22:36:29 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Surely the error function should not be inlined.
 
     Tue May  9 22:35:53 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Reorder memory writes for better cache locality.
 
     Tue May  9 23:28:09 EST 2006  Duncan Coutts <duncan.coutts at worc.ox.ac.uk>
       * Generalise the type of unfoldrN
       
       The type of unfoldrN was overly constrained:
       unfoldrN :: Int -> (Word8 -> Maybe (Word8, Word8)) -> Word8 -> ByteString
       
       if we compare that to unfoldr:
       unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
       
       So we can generalise unfoldrN to this type:
       unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> ByteString
       
       and something similar for the .Char8 version. If people really do want to
       use it a lot with Word8/Char then perhaps we should add a specialise pragma.
 
     Wed May 10 13:26:40 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
       * Add foldl', and thus a fusion rule for length . {map,filter,fold}, 
       that avoids creating an array at all if the end of the pipeline is a 'length' reduction
 
 **END OF DESCRIPTION***
 
 Place the long patch description above the ***END OF DESCRIPTION*** marker.
 The first line of this file will be the patch name.
 
 
 This patch contains the following changes:
 
 M ./Data/ByteString.hs -8 +38
 M ./Data/ByteString/Char8.hs -6 +12
] 
[portable implementation of WordPtr/IntPtr for non-GHC
Ross Paterson <ross at soi.city.ac.uk>**20060510001826
 
 plus much tweaking of imports to avoid cycles
] 
[add WordPtr and IntPtr types to Foreign.Ptr, with associated conversions
Simon Marlow <simonmar at microsoft.com>**20060509092606
 
 As suggested by John Meacham.  
 
 I had to move the Show instance for Ptr into GHC.ForeignPtr to avoid
 recursive dependencies.
] 
[add CIntPtr, CUIntPtr, CIntMax, CUIntMax types
Simon Marlow <simonmar at microsoft.com>**20060509092427] 
[add GHC.Dynamic
Simon Marlow <simonmar at microsoft.com>**20060509082739] 
[Two things. #if defined(__GLASGOW_HASKELL__) on INLINE [n] pragmas (for jhc). And careful use of INLINE on words/unwords halves runtime for those functions
Don Stewart <dons at cse.unsw.edu.au>**20060509023425] 
[Make length a good consumer
simonpj at microsoft**20060508142726
 
 Make length into a good consumer.  Fixes Trac bug #707.
 
 (Before length simply didn't use foldr.)
 
] 
[Trim imports
simonpj at microsoft**20060508142557] 
[Make unsafePerformIO lazy
simonpj at microsoft**20060508142507
 
 The stricteness analyser used to have a HACK which ensured that NOINLNE things
 were not strictness-analysed.  The reason was unsafePerformIO. Left to itself,
 the strictness analyser would discover this strictness for unsafePerformIO:
 	unsafePerformIO:  C(U(AV))
 But then consider this sub-expression
 	unsafePerformIO (\s -> let r = f x in 
 			       case writeIORef v r s of (# s1, _ #) ->
 			       (# s1, r #)
 The strictness analyser will now find that r is sure to be eval'd,
 and may then hoist it out.  This makes tests/lib/should_run/memo002
 deadlock.
 
 Solving this by making all NOINLINE things have no strictness info is overkill.
 In particular, it's overkill for runST, which is perfectly respectable.
 Consider
 	f x = runST (return x)
 This should be strict in x.
 
 So the new plan is to define unsafePerformIO using the 'lazy' combinator:
 
 	unsafePerformIO (IO m) = lazy (case m realWorld# of (# _, r #) -> r)
 
 Remember, 'lazy' is a wired-in identity-function Id, of type a->a, which is 
 magically NON-STRICT, and is inlined after strictness analysis.  So
 unsafePerformIO will look non-strict, and that's what we want.
 
] 
[Sync with FPS head.
Don Stewart <dons at cse.unsw.edu.au>**20060508122322
 
 Mon May  8 10:40:14 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Fix all uses for Int that should be CInt or CSize in ffi imports.
   Spotted by Igloo, dcoutts
 
 Mon May  8 16:09:41 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Import nicer loop/loop fusion rule from ghc-ndp
 
 Mon May  8 17:36:07 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Fix stack leak in split on > 60M strings
 
 Mon May  8 17:50:13 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Try same fix for stack overflow in elemIndices
 
] 
[Fix all uses for Int that should be CInt or CSize in ffi imports. Spotted by Duncan and Ian
Don Stewart <dons at cse.unsw.edu.au>**20060508010311] 
[Fixed import list syntax
Sven Panne <sven.panne at aedion.de>**20060507155008] 
[Faster filterF, filterNotByte
dons at cse.unsw.edu.au**20060507042301] 
[Much faster find, findIndex. Hint from sjanssen
dons at cse.unsw.edu.au**20060507033048] 
[Merge "unrecognized long opt" fix from 6.4.2
Sven Panne <sven.panne at aedion.de>**20060506110519] 
[
dons at cse.unsw.edu.au**20060506061029
 Sat May  6 13:01:34 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Do loopU realloc on the Haskell heap. And add a really tough stress test
 
 Sat May  6 12:28:58 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Use simple, 3x faster concat. Plus QC properties. Suggested by sjanssen and dcoutts
 
 Sat May  6 15:59:31 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * dcoutt's packByte bug squashed
   
   With inlinePerformIO, ghc head was compiling:
   
    packByte 255 `compare` packByte 127
   
   into roughly
   
    case mallocByteString 2 of
        ForeignPtr f internals ->
             case writeWord8OffAddr# f 0 255 of _ ->
             case writeWord8OffAddr# f 0 127 of _ ->
             case eqAddr# f f of
                    False -> case compare (GHC.Prim.plusAddr# f 0)
                                          (GHC.Prim.plusAddr# f 0)
   
   which is rather stunning. unsafePerformIO seems to prevent whatever
   magic inlining was leading to this. Only affected the head.
   
] 
[Add array fusion versions of map, filter and foldl
dons at cse.unsw.edu.au**20060505060858
 
 This patch adds fusable map, filter and foldl, using the array fusion
 code for unlifted, flat arrays, from the Data Parallel Haskell branch,
 after kind help from Roman Leshchinskiy, 
 
 Pipelines of maps, filters and folds should now need to walk the
 bytestring once only, and intermediate bytestrings won't be constructed.
 
] 
[fix for non-GHC
Ross Paterson <ross at soi.city.ac.uk>**20060504093044] 
[use bracket in appendFile (like writeFile)
Ross Paterson <ross at soi.city.ac.uk>**20060504091528] 
[writeFile: close the file on error
Simon Marlow <simonmar at microsoft.com>**20060504084505
 Suggested by Ross Paterson, via Neil Mitchell
 
] 
[Sync with FPS head
dons at cse.unsw.edu.au**20060503105259
 
 This patch brings Data.ByteString into sync with the FPS head.
 The most significant of which is the new Haskell counting sort.
 
 Changes:
 
 Sun Apr 30 18:16:29 EST 2006  sjanssen at cse.unl.edu
   * Fix foldr1 in Data.ByteString and Data.ByteString.Char8
 
 Mon May  1 11:51:16 EST 2006  Don Stewart <dons at cse.unsw.edu.au>
   * Add group and groupBy. Suggested by conversation between sjanssen and petekaz on #haskell
 
 Mon May  1 16:42:04 EST 2006  sjanssen at cse.unl.edu
   * Fix groupBy to match Data.List.groupBy.
 
 Wed May  3 15:01:07 EST 2006  sjanssen at cse.unl.edu
   * Migrate to counting sort.
   
   Data.ByteString.sort used C's qsort(), which is O(n log n).  The new algorithm 
   is O(n), and is faster for strings larger than approximately thirty bytes.  We
   also reduce our dependency on cbits!
 
] 
[improve performance of Integer->String conversion
Simon Marlow <simonmar at microsoft.com>**20060503113306
 See
  http://www.haskell.org//pipermail/libraries/2006-April/005227.html
 
 Submitted by: bertram.felgenhauer at googlemail.com
 
 
] 
[inline withMVar, modifyMVar, modifyMVar_
Simon Marlow <simonmar at microsoft.com>**20060503111152] 
[Fix string truncating in hGetLine -- it was a pasto from Simon's code
Simon Marlow <simonmar at microsoft.com>**20060503103504
 (from Don Stewart)
] 
[Merge in Data.ByteString head. Fixes ByteString+cbits in hugs
Don Stewart <dons at cse.unsw.edu.au>**20060429040733] 
[Import Data.ByteString from fps 0.5.
Don Stewart <dons at cse.unsw.edu.au>**20060428130718
 Fast, packed byte vectors, providing a better PackedString.
 
] 
[fix previous patch
Ross Paterson <ross at soi.city.ac.uk>**20060501154847] 
[fixes for non-GHC
Ross Paterson <ross at soi.city.ac.uk>**20060501144322] 
[fix imports for mingw32 && !GHC
Ross Paterson <ross at soi.city.ac.uk>**20060427163248] 
[RequireOrder: do not collect unrecognised options after a non-opt
Simon Marlow <simonmar at microsoft.com>**20060426121110
 The documentation for RequireOrder says "no option processing after
 first non-option", so it doesn't seem right that we should process the
 rest of the arguments to collect the unrecognised ones.  Presumably
 the client wants to know about the unrecognised options up to the
 first non-option, and will be using a different option parser for the
 rest of the command line.
 
 eg. before:
 
 Prelude System.Console.GetOpt> getOpt' RequireOrder [] ["bar","--foo"]
 ([],["bar","--foo"],["--foo"],[])
 
 after:
 
 Prelude System.Console.GetOpt> getOpt' RequireOrder [] ["bar","--foo"]
 ([],["bar","--foo"],[],[])
] 
[fix for Haddock 0.7
Ashley Yakeley <ashley at semantic.org>**20060426072521] 
[add Data.Fixed module
Ashley Yakeley <ashley at semantic.org>**20060425071853] 
[add instances
Ross Paterson <ross at soi.city.ac.uk>**20060424102146] 
[add superclasses to Applicative and Traversable
Ross Paterson <ross at soi.city.ac.uk>**20060411144734
 
 Functor is now a superclass of Applicative, and Functor and Foldable
 are now superclasses of Traversable.  The new hierarchy makes clear the
 inclusions between the classes, but means more work in defining instances.
 Default definitions are provided to help.
] 
[add Functor and Monad instances for Prelude types
Ross Paterson <ross at soi.city.ac.uk>**20060410111443] 
[GHC.Base.breakpoint
Lemmih <lemmih at gmail.com>**20060407125827] 
[Track the GHC source tree reorganisation
Simon Marlow <simonmar at microsoft.com>**20060407041631] 
[in the show instance for Exception, print the type of dynamic exceptions
Simon Marlow <simonmar at microsoft.com>**20060406112444
 Unfortunately this requires some recursve module hackery to get at 
 the show instance for Typeable.
] 
[implement ForeignEnvPtr, newForeignPtrEnv, addForeignPtrEnv for GHC
Simon Marlow <simonmar at microsoft.com>**20060405155448] 
[add  forkOnIO :: Int -> IO () -> IO ThreadId
Simon Marlow <simonmar at microsoft.com>**20060327135018] 
[Rework previous: not a gcc bug after all
Simon Marlow <simonmar at microsoft.com>**20060323161229
 It turns out that we were relying on behaviour that is undefined in C,
 and undefined behaviour in C means "the compiler can do whatever the
 hell it likes with your entire program".  So avoid that.
] 
[work around a gcc 4.1.0 codegen bug in -O2 by forcing -O1 for GHC.Show
Simon Marlow <simonmar at microsoft.com>**20060323134514
 See http://gcc.gnu.org/bugzilla/show_bug.cgi?id=26824
] 
[commit mysteriously missing parts of "runIOFastExit" patch
Simon Marlow <simonmar at microsoft.com>**20060321101535] 
[add runIOFastExit :: IO a -> IO a
Simon Marlow <simonmar at microsoft.com>**20060320124333
 Similar to runIO, but calls stg_exit() directly to exit, rather than
 shutdownHaskellAndExit().  Needed for running GHCi in the test suite.
] 
[Fix a broken invariant
Simon Marlow <simonmar at microsoft.com>**20060316134151
 Patch from #694,  for the problem "empty is an identity for <> and $$" is
 currently broken by eg. isEmpty (empty<>empty)"
] 
[Add unsafeSTToIO :: ST s a -> IO a
Simon Marlow <simonmar at microsoft.com>**20060315160232
 Implementation for Hugs is missing, but should be easy.  We need this
 for the forthcoming nested data parallelism implementation.
] 
[Added 'alter'
jeanphilippe.bernardy at gmail.com**20060315143539
 Added 'alter :: (Maybe a -> Maybe a) -> k -> Map k a -> Map k a' to IntMap and Map
 This addresses ticket #665
] 
[deprecate FunctorM in favour of Foldable and Traversable
Ross Paterson <ross at soi.city.ac.uk>**20060315092942
 as discussed on the libraries list.
] 
[Simplify Eq, Ord, and Show instances for UArray
Simon Marlow <simonmar at microsoft.com>**20060313142701
 The Eq, Ord, and Show instances of UArray were written out longhand
 with one instance per element type.  It is possible to condense these
 into a single instance for each class, at the expense of using more
 extensions (non-std context on instance declaration).
 
 Suggestion by: Frederik Eaton <frederik at ofb.net>
 
] 
[Oops typo in intSet notMember 
jeanphilippe.bernardy at gmail.com**20060311224713] 
[IntMap lookup now returns monad instead of Maybe.
jeanphilippe.bernardy at gmail.com**20060311224502] 
[Added notMember to Data.IntSet and Data.IntMap
jeanphilippe.bernardy at gmail.com**20060311085221] 
[add Data.Set.notMember and Data.Map.notMember
John Meacham <john at repetae.net>**20060309191806] 
[addToClockTime: handle picoseconds properly
Simon Marlow <simonmar at microsoft.com>**20060310114532
 fixes #588
] 
[make head/build rule apply to all types, not just Bool.
John Meacham <john at repetae.net>**20060303045753] 
[Avoid overflow when normalising clock times
Ian Lynagh <igloo at earth.li>**20060210144638] 
[Years have 365 days, not 30*365
Ian Lynagh <igloo at earth.li>**20060210142853] 
[declare blkcmp() static
Simon Marlow <simonmar at microsoft.com>**20060223134317] 
[typo in comment in Foldable class
Ross Paterson <ross at soi.city.ac.uk>**20060209004901] 
[simplify fmap
Ross Paterson <ross at soi.city.ac.uk>**20060206095048] 
[update ref in comment
Ross Paterson <ross at soi.city.ac.uk>**20060206095139] 
[Give -foverlapping-instances to Data.Typeable
simonpj at microsoft**20060206133439
 
 For some time, GHC has made -fallow-overlapping-instances "sticky": 
 any instance in a module compiled with -fallow-overlapping-instances
 can overlap when imported, regardless of whether the importing module
 allows overlap.  (If there is an overlap, both instances must come from
 modules thus compiled.)
 
 Instances in Data.Typeable might well want to be overlapped, so this
 commit adds the flag to Data.Typeable (with an explanatory comment)
 
 
] 
[Add -fno-bang-patterns to modules using both bang and glasgow-exts
simonpj at microsoft.com**20060203175759] 
[When splitting a bucket, keep the contents in the same order
Simon Marlow <simonmar at microsoft.com>**20060201130427
 To retain the property that multiple inserts shadow each other
 (see ticket #661, test hash001)
] 
[add foldr/build optimisation for take and replicate
Simon Marlow <simonmar at microsoft.com>**20060126164603
 This allows take to be deforested, and improves performance of
 replicate and replicateM/replicateM_.  We have a separate problem that
 means expressions involving [n..m] aren't being completely optimised
 because eftIntFB isn't being inlined but otherwise the results look
 good.  
 
 Sadly this has invalidated a number of the nofib benchmarks which were
 erroneously using take to duplicate work in a misguided attempt to
 lengthen their runtimes (ToDo).
] 
[Generate PrimopWrappers.hs with Haddock docs
Simon Marlow <simonmar at microsoft.com>**20060124131121
 Patch originally from Dinko Tenev <dinko.tenev at gmail.com>, modified
 to add log message by me.
] 
[[project @ 2006-01-19 14:47:15 by ross]
ross**20060119144715
 backport warning avoidance from Haddock
] 
[[project @ 2006-01-18 11:45:47 by malcolm]
malcolm**20060118114547
 Fix import of Ix for nhc98.
] 
[[project @ 2006-01-17 09:38:38 by ross]
ross**20060117093838
 add Ix instance for GeneralCategory.
] 
[TAG Initial conversion from CVS complete
John Goerzen <jgoerzen at complete.org>**20060112154126] 
Patch bundle hash:
83819f69b3b12919bfcf79a6fbeda00c676a5435


More information about the Libraries mailing list