darcs patch: Control.Monad: +void :: f a -> f ()

Jeremy Shaw jeremy at n-heptane.com
Fri Jan 8 21:54:59 EST 2010


Not sure if this came up already, but there is a less general version  
of void in Foreign.Marshal.Error:

http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Foreign-Marshal-Error.html#v%3Avoid

void :: IO a -> IO ()
      Discard the return value of an IO action

Are there plans to unify the two? Perhaps Foreign.Marshal.Error can  
just re-export void from Control.Monad?

- jeremy

On Jan 8, 2010, at 3:53 PM, gwern0 at gmail.com wrote:

> Fri Jan  8 16:44:55 EST 2010  gwern0 at gmail.com
>  * Control.Monad: +void :: f a -> f ()
>  See http://hackage.haskell.org/trac/ghc/ticket/3292
>  Turns m a -> m (). Lets one call functions for their side-effects  
> without
>  having to get rid of their return values with '>> return ()'. Very  
> useful
>  in many contexts (parsing, IO etc.); particularly good for 'forkIO'  
> and 'forM_',
>  as they demand return types of 'IO ()' though most interesting IO  
> functions
>  return non-().
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA512
>
>
> New patches:
>
> [Control.Monad: +void :: f a -> f ()
> gwern0 at gmail.com**20100108214455
> Ignore-this: 4dc07452315f2d1b4941903ff42fc45f
> See http://hackage.haskell.org/trac/ghc/ticket/3292
> Turns m a -> m (). Lets one call functions for their side-effects  
> without
> having to get rid of their return values with '>> return ()'. Very  
> useful
> in many contexts (parsing, IO etc.); particularly good for 'forkIO'  
> and 'forM_',
> as they demand return types of 'IO ()' though most interesting IO  
> functions
> return non-().
> ] hunk ./Control/Monad.hs 193
> forever     :: (Monad m) => m a -> m b
> forever a   = a >> forever a
>
> +-- | @'void' value@ discards or ignores the result of evaluation,  
> such as the return value of an 'IO' action.
> +void :: Functor f => f a -> f ()
> +void = fmap (const ())
> +
> --  
> -----------------------------------------------------------------------------
> -- Other monad functions
>
>
> Context:
>
> [Replace the implementation of mergesort with a 2x faster one.
> Malcolm.Wallace at cs.york.ac.uk**20091224152014
> See ticket http://hackage.haskell.org/trac/ghc/ticket/2143.
> ]
> [Restore previous Data.Typeable.typeOf*Default implementations for  
> non-ghc.
> Malcolm.Wallace at cs.york.ac.uk**20091223142625
> Not all compilers have ScopedTypeVariables.
> ]
> [Add comments about double bounds-checking, and fast paths for  
> rectangular arrays
> simonpj at microsoft.com**20091218165655
> Ignore-this: ea0849419dc00927aba4bd410b1cc58d
>
> See Note [Double bounds-checking of index values] for the details.
>
> The fast paths omit the doubled checks for cases we know about
> ]
> [Fix Trac #3245: memoising typeOf
> simonpj at microsoft.com**20091218155117
> Ignore-this: 5a178a7f2222293c5ee0c3c43bd1b625
>
> The performance bug in #3245 was caused by computing the typeRep
> once for each call of typeOf, rather than once for each dictionary
> contruction.  (Computing TypeReps is reasonably expensive, because
> of the hash-consing machinery.)
>
> This is readily fixed by putting the TypeRep construction outside
> the lambda.  (Arguably GHC might have worked that out itself,
> but it involves floating something between a type lambda and a
> value lambda, which GHC doesn't currently do. If it happens a lot
> we could fix that.)
> ]
> [Mark 'index' as INLINE in GHC.Arr
> simonpj at microsoft.com**20091216170441
> Ignore-this: a4df9d8acf496c8e0e9ce5a520509a2a
>
> This makes indexing much faster. See Trac #1216
> ]
> [Comment the remaining orphan instance modules
> Ian Lynagh <igloo at earth.li>**20091206125021]
> [De-orphan Eq/Ord Float/Double
> Ian Lynagh <igloo at earth.li>**20091205181238]
> [Add comments to "OPTIONS_GHC -fno-warn-orphans" pragmas
> Ian Lynagh <igloo at earth.li>**20091205165854]
> [Data.Either.partitionEithers was insufficiently lazy.
> Malcolm.Wallace at cs.york.ac.uk**20091202032807
> Ignore-this: 77e1b3288f66608c71458d8a91bcbe12
> Spotted by Daniel Fischer.
> ]
> [fix the docs regarding finalizer guarantees
> Simon Marlow <marlowsd at gmail.com>**20091130144409
> Ignore-this: d1ab9532c74a002b8075ff60febcbe2d
> ]
> [x86_64 requires more stack
> Malcolm.Wallace at cs.york.ac.uk**20091201033745]
> [check for size < 0 in mallocForeignPtrBytes and friends (#3514)
> Simon Marlow <marlowsd at gmail.com>**20091125143822
> Ignore-this: 91077d01da2bbe1dfed5155e8b40da9
> ]
> [hGetContents: close the handle properly on error
> Simon Marlow <marlowsd at gmail.com>**20091125123435
> Ignore-this: bc37ff678acc6e547dc390285e056eb9
>
> When hGetContents caught an error it was closing the handle and then
> throwing the exception, without updating the handle with the new
> closed state.  This lead to a double-closed, which was the cause of
>
> *** glibc detected *** ./Setup: double free or corruption
>
> when iconv_close was called twice on the decoder.
>
> See http://hackage.haskell.org/trac/hackage/ticket/609
> ]
> [Fix arities of mapFB and zipFB
> Roman Leshchinskiy <rl at cse.unsw.edu.au>**20091126232219
> Ignore-this: c4e14cd0a92622549c86e67237a40865
> ]
> [Remove an unnecessary -fno-warn-orphans flag
> Ian Lynagh <igloo at earth.li>**20091126123404]
> [Tweak layout to work with alternative layout rule
> Ian Lynagh <igloo at earth.li>**20091125232349]
> [Tweak layout to be accepted by the alternative layout rul
> Ian Lynagh <igloo at earth.li>**20091125194147]
> [Make sure zipWithFB has arity 2
> Roman Leshchinskiy <rl at cse.unsw.edu.au>**20091125010003
> Ignore-this: 4cf60c55666f03d22a9f5a6e07f52d36
>
> It gets 2 arguments in the "zipWith" rule but its arity was higher  
> and the new
> inliner didn't inline it sometimes, for instance here:
>
> mpp ::  [Double] -> [Double] -> [Double] -> [Double] -> [Double]
> mpp as bs cs ds = zipWith (*) (zipWith (+) as bs) (zipWith (+) cs ds)
>
> This was a regression vs. 6.10.
> ]
> [Remove an old comment
> Ian Lynagh <igloo at earth.li>**20091124134647]
> [De-orphan the Eq/Ord Integer instances
> Ian Lynagh <igloo at earth.li>**20091124133639]
> [Whitespace only
> Ian Lynagh <igloo at earth.li>**20091124133421]
> [Derive some more instances, rather than writing them by hand
> Ian Lynagh <igloo at earth.li>**20091124011747]
> [We can now derive Ord ()
> Ian Lynagh <igloo at earth.li>**20091124011416]
> [De-orphan tuple Eq/Ord instances
> Ian Lynagh <igloo at earth.li>**20091123233343]
> [Control.Exception.Base no longer has any orphans
> Ian Lynagh <igloo at earth.li>**20091123224905]
> [De-orphan the MonadFix ST instance for GHC
> Ian Lynagh <igloo at earth.li>**20091123223544]
> [Rearrange the contents of Control.Monad.ST; no functionality changes
> Ian Lynagh <igloo at earth.li>**20091123222702]
> [De-orphan the Eq/Ord [a] instances
> Ian Lynagh <igloo at earth.li>**20091123215635]
> [De-orphan the Eq/Ord Char instances
> Ian Lynagh <igloo at earth.li>**20091123202253]
> [De-orphan the Eq/Ord Bool instances
> Ian Lynagh <igloo at earth.li>**20091123201817]
> [Move Eq/Ord Ordering instances to de-orphan them
> Ian Lynagh <igloo at earth.li>**20091123194310]
> [Remove ffi warnings for nhc98.
> Malcolm.Wallace at cs.york.ac.uk**20091123063743]
> [Second attempt to fix #1185 (forkProcess and -threaded)
> Simon Marlow <marlowsd at gmail.com>**20091111151915
> Ignore-this: fa5f5d5e4e080d4b612a37244f937f9c
>
> Patch 2/2: first patch is to ghc
>
> This time without dynamic linker hacks, instead I've expanded the
> existing rts/Globals.c to cache more CAFs, specifically those in
> GHC.Conc.  We were already using this trick for signal handlers, I
> should have realised before.
>
> It's still quite unsavoury, but we can do away with rts/Globals.c in
> the future when we switch to a dynamically-linked GHCi.
> ]
> [Rollback #1185 fix
> Simon Marlow <marlowsd at gmail.com>**20091106140629
> Ignore-this: cd5667e8474e37e01ba26a1984274811
>
> rolling back:
>
> Tue Nov  3 16:05:40 GMT 2009  Simon Marlow <marlowsd at gmail.com>
>   * Fix #1185: restart the IO manager after fork()
>
>   This is the libraries/base part of the patch; there is a  
> corresponding
>   patch to GHC itself.
>
>   The main change is that we now keep track of the IO manager's  
> ThreadId
>   in a top-level MVar, and ensureIOManagerIsRunning checks whether a
>   previous IO manager thread is alive before starting one.  In the  
> child
>   of fork(), we can hence call ensureIOManagerIsRunning to restart the
>   IO manager.
>
>     M ./GHC/Conc.lhs -46 +44
>
> Wed Nov  4 17:49:45 GMT 2009  Ian Lynagh <igloo at earth.li>
>   * Fix the build on Windows
>
>     M ./GHC/Conc.lhs -6 +4
> ]
> [Fix the build on Windows
> Ian Lynagh <igloo at earth.li>**20091104174945]
> [Fix #1185: restart the IO manager after fork()
> Simon Marlow <marlowsd at gmail.com>**20091103160540
> Ignore-this: 6dc05464f1500104554637f4759738cc
>
> This is the libraries/base part of the patch; there is a corresponding
> patch to GHC itself.
>
> The main change is that we now keep track of the IO manager's ThreadId
> in a top-level MVar, and ensureIOManagerIsRunning checks whether a
> previous IO manager thread is alive before starting one.  In the child
> of fork(), we can hence call ensureIOManagerIsRunning to restart the
> IO manager.
> ]
> [improve the documentation for throwErrnoIfRetry
> Simon Marlow <marlowsd at gmail.com>**20091016112404
> Ignore-this: b77275cacf730e15757946027168f63e
> ]
> [Don't inline unpackFoldrCString ever
> simonpj at microsoft.com**20091029135350
> Ignore-this: 85d672649b1b776efc7e97500b05d4f9
> ]
> [Inline more default methods
> simonpj at microsoft.com**20091029135330
> Ignore-this: 289c44b0afd6d5631c2a4e0664275ca9
>
> Namely Monad: (>>)
>        Eq:    (==), (/=)
>        Num:   (-), negate
>        Real:  quot, rem, div, mod, recip, (/), truncate
>        Float: (**), logBase, sqrt, tan, tanh
> ]
> [Move error messages out of INLINEd default methods
> simonpj at microsoft.com**20091029135118
> Ignore-this: 9e35dc947f94827a3529eb53a41575fd
>
> No need to duplicate the error generation!
> ]
> [Exploit now-working default-method INLINE pragmas for Data.Bits
> simonpj at microsoft.com**20091029135041
> Ignore-this: 8adf225f31ca7a3181ee087e9e4fe535
>
> * Add INLINE pragmas to default methods for class Bits
>
> * Remove redundant instance methods elsewhere, now that
>   the default method will do the job
> ]
> [Tidy up and comment imports
> simonpj at microsoft.com**20091029134414
> Ignore-this: bf2be31035de975d8995e988933cc940
> ]
> [Inline foldr and (.) when applied to two arguments not three
> simonpj at microsoft.com**20091029134335
> Ignore-this: fccb6f3e90e15f44cb465814be85ede2
>
> The new INLINE story is (by design) arity-sensitive, so we must
> put fewer argument on the LHS for foldr and (.)
> ]
> [dirUtils.c no longer available
> Malcolm.Wallace at cs.york.ac.uk**20091013093833]
> [Make hGetContents throw an exception if an error is encountered
> Simon Marlow <marlowsd at gmail.com>**20091012152955
> Ignore-this: 9f7a7176193eab25c9daaacd9261f2de
>
> Strictly speaking this breaks Haskell 98 compatibility, which requires
> hGetContents to just end the lazy stream silently if an error is
> encountered.  However, for a few reasons we think it will make
> everyone's life a bit easier if we make this change
>
>  1. Errors will be a lot more common in GHC 6.12.1, in the form
>     of Unicode decoding errors.
>
>  2. When Haskell 98 was designed, we didn't know how to throw
>     exceptions from inside lazy I/O, but now we do.
>
>  3. If anyone is actually relying on the previous behaviour, their
>     code is arguably broken.
> ]
> [Re-instate System.Console.Getopt for nhc98 builds.
> Malcolm.Wallace at cs.york.ac.uk**20091013092843
> Although it was split out of base a while back, that change was
> reverted for ghc soon afterwards, but nhc98 never noticed.
> ]
> [Roll back "Another instance of nhc98's strange import semantics."
> Ian Lynagh <igloo at earth.li>**20091009185618
> Fri Oct  9 14:50:51 BST 2009  Malcolm.Wallace at cs.york.ac.uk
> GHC (correctly) warns about the unused import, which breaks the  
> validate
> build.
> ]
> [Roll back "Cope with nhc98's (occasionally-strange) import semantics"
> Ian Lynagh <igloo at earth.li>**20091009184704
> Fri Oct  9 14:43:51 BST 2009  Malcolm.Wallace at cs.york.ac.uk
> GHC (correctly) warns about the unused import, which breaks the  
> validate
> build.
> ]
> [It seems that nhc98 needs defaulting in Data.Fixed.
> Malcolm.Wallace at cs.york.ac.uk**20091009135242]
> [Another instance of nhc98's strange import semantics.
> Malcolm.Wallace at cs.york.ac.uk**20091009135051]
> [Make Data.Functor compatible with non-GHC compilers.
> Malcolm.Wallace at cs.york.ac.uk**20091009134821]
> [Cope with nhc98's (occasionally-strange) import semantics.
> Malcolm.Wallace at cs.york.ac.uk**20091009134351]
> [Fix gratuitous breakage of nhc98 in System.IO.
> Malcolm.Wallace at cs.york.ac.uk**20091009134001]
> [Fix gratuitous breakage of nhc98 in Control.Exception.Base.
> Malcolm.Wallace at cs.york.ac.uk**20091009133615]
> [Fix gratuitous breakage of non-GHC in Data.Fixed.
> Malcolm.Wallace at cs.york.ac.uk**20091009133330]
> [Fix gratuitous breakage for non-GHC in Data.Bits.
> Malcolm.Wallace at cs.york.ac.uk**20091009133257]
> [Use UTF-32LE instead of UTF32LE
> Simon Marlow <marlowsd at gmail.com>**20091006100207
> Ignore-this: 7f881e36543d250ef848c9f60d67655a
> The latter is not recognised by some iconv implementations.
> ]
> [Strip any Byte Order Mark (BOM) from the front of decoded streams.
> Ben.Lippmeier at anu.edu.au*-20090930084229
> Ignore-this: d0d0c3ae87b31d71ef1627c8e1786445
> When decoding to UTF-32, Solaris iconv inserts a BOM at the front
> of the stream, but Linux iconv doesn't.
> ]
> [use UTF32BE/UTF32LE instead of UCS-4/UCS-4LE
> Simon Marlow <marlowsd at gmail.com>**20091005101554
> Ignore-this: 2aef5e9bec421e714953b7aa1bdfc1b3
> ]
> [Strip any Byte Order Mark (BOM) from the front of decoded streams.
> Ben.Lippmeier at anu.edu.au**20090930084229
> Ignore-this: d0d0c3ae87b31d71ef1627c8e1786445
> When decoding to UTF-32, Solaris iconv inserts a BOM at the front
> of the stream, but Linux iconv doesn't.
> ]
> [Add traceEvent :: String -> IO ()
> Simon Marlow <marlowsd at gmail.com>**20090925141257
> Ignore-this: 8b1888bbf9682ffba13f815b6000e4b1
> For emitting an event via the RTS tracing framework
> ]
> [Fix the error message when flushing the read buffer of a non- 
> seekable Handle
> Simon Marlow <marlowsd at gmail.com>**20090923090536
> Ignore-this: 4342026df93759d99480f4e13f80a492
> ]
> [Fix #3534: No need to flush the byte buffer when setting binary mode
> Simon Marlow <marlowsd at gmail.com>**20090923090445
> Ignore-this: 625817ed7ae2c12291eb993a99dc640a
> ]
> [Use let !y = x in .. x .. instead of seq in $! and evaluate (#2273)
> Simon Marlow <marlowsd at gmail.com>**20090916140454]
> [make some Applicative functions into methods, and split off  
> Data.Functor (proposal #3335)
> Ross Paterson <ross at soi.city.ac.uk>**20090915173109
> Ignore-this: a0cff4de6dfdbcbd56a66101bc4855a9
>
> The following functions
>
>     (<$) :: Functor f => a -> f b -> f a
>     (*>) :: Applicative f => f a -> f b -> f b
>     (<*) :: Applicative f => f a -> f b -> f a
>     some :: Alternative f => f a -> f [a]
>     many :: Alternative f => f a -> f [a]
>
> are moved into the corresponding classes, with the existing  
> implementations
> as default definitions.  This gives people creating instances the  
> option of
> defining specialized implementations of these functions, though they  
> should
> be equivalent to the default definitions.
>
> Although (<$) is now a method of the Functor class, it is hidden in  
> the
> re-export by the Prelude, Control.Monad and Monad.  The new module
> Data.Functor exposes the full class, plus the function (<$>).  These  
> are
> also re-exported by Control.Applicative.
> ]
> [On Windows, use the console code page for text file encoding/ 
> decoding.
> Judah Jacobson <judah.jacobson at gmail.com>**20090913022126
> Ignore-this: 86c2f2db8ef92b751599795d3195187b
>
> We keep all of the code page tables in the module
> GHC.IO.Encoding.CodePage.Table.  That file was generated automatically
> by running codepages/MakeTable.hs; more details are in the comments  
> at the
> start of that script.
>
> Storing the lookup tables adds about 40KB to each statically linked  
> executable;
> this only increases the size of a "hello world" program by about 7%.
>
> Currently we do not support double-byte encodings (Chinese/Japanese/ 
> Korean), since
> including those codepages would increase the table size to 400KB.   
> It will be
> straightforward to implement them once the work on library DLLs is  
> finished.
> ]
> [Fix "init" docs: the input list need not be finite. Fixes trac #3465
> Ian Lynagh <igloo at earth.li>**20090911210437]
> [Bump base version to 4.2.0.0
> Ian Lynagh <igloo at earth.li>**20090911153913]
> [Address #3310
> Simon Marlow <marlowsd at gmail.com>**20090830152850
> Ignore-this: 40c7f7c171ee299a83092fd360a952b7
>
>  - Rename BlockedOnDeadMVar   -> BlockedIndefinitelyOnMVar
>  - Rename BlockedIndefinitely -> BlockedIndefinitelyOnSTM
>  - instance Show BlockedIndefinitelyOnMVar is now
>      "blocked indefinitely in an MVar operation"
>  - instance Show BlockedIndefinitelyOnSTM is now
>      "blocked indefinitely in an STM transaction"
>
> clients using Control.OldException will be unaffected (the new
> exceptions are mapped to the old names).  However, for base4-compat
> we'll need to make a version of catch/try that does a similar
> mapping.
> ]
> [Fix unicode conversion for MSB architectures
> Ben.Lippmeier at anu.edu.au**20090830130028
> This fixes the SPARC/Solaris build.
> ]
> [Fix #3441: detect errors in partial sequences
> Simon Marlow <marlowsd at gmail.com>**20090830075909
> Ignore-this: d12a75d95e0cae5eb1555266810ec281
> ]
> [Fix hWaitForInput
> Simon Marlow <marlowsd at gmail.com>**20090827152116
> Ignore-this: 2550e911f1a4d4357a5aa8d1764238ce
> It was erroneously waiting when there were bytes to decode waiting in
> the byte buffer.
> ]
> [fix debugging code
> Simon Marlow <marlowsd at gmail.com>**20090827150628
> Ignore-this: e1c82fdc19a22e247cd69ff6fa11921d
> ]
> [Allow for configurable iconv include and library locations.
> Matthias Kilian <kili at outback.escape.de>**20090826154406
> Ignore-this: be95fab611a5534cf184b508964ed498
> This should help to fix the build on OpenBSD.
> ]
> [typo in comment
> Simon Marlow <marlowsd at gmail.com>**20090826085252
> Ignore-this: 1903ee0f354157a6ed3871c100f6b1b9
> ]
> [un-hide some modules from the Haddock docs
> Simon Marlow <marlowsd at gmail.com>**20090825152457
> Ignore-this: dce6606f93cf977fb24ebe99082dfa62
> ]
> [Apply fix for #1548, from squadette at gmail.com
> Simon Marlow <marlowsd at gmail.com>**20090819120700
> Ignore-this: 31c237c46a6445f588ed4b8c51bb6231
> ]
> [improvements to Data.Fixed: instances for Typeable and Data, more  
> predefined types
> Ashley Yakeley <ashley at semantic.org>**20090812055058
> Ignore-this: feeece36d5632f02a05d137d2a39ab78
> ]
> [Fix "Cabal check" warnings
> Ian Lynagh <igloo at earth.li>**20090811215856]
> [Add a GHC.Constants module; fixes trac #3094
> Ian Lynagh <igloo at earth.li>**20090809183252]
> [Apply proposal #3393
> Ian Lynagh <igloo at earth.li>**20090809134717
> Add openTempFileWithDefaultPermissions and
> openBinaryTempFileWithDefaultPermissions.
> ]
> [Add some more C wrappers; patch from Krister Walfridsson
> Ian Lynagh <igloo at earth.li>**20090807200631
> Fixes 21 testsuite errors on NetBSD 5.99.
> ]
> [Fixing configure for autoconf 2.64
> Alexander Dunlap <alexander.dunlap at gmail.com>**20090805060748
> Ignore-this: 992ab91ae3d68c12dbb265776e33e243
> ]
> [add INLINE toList
> Ross Paterson <ross at soi.city.ac.uk>**20090806142853
> Ignore-this: aba16aabb17d5dca44f15d188945680e
>
> In anticipation of the fixing of #2353.
> ]
> [fix a copyright
> Simon Marlow <marlowsd at gmail.com>**20090805134045
> Ignore-this: b0ffbdd38fbba121e8bcba37c4082a60
> ]
> [Tweak the BufferedIO class to enable a memory-mapped file  
> implementation
> Simon Marlow <marlowsd at gmail.com>**20090805134036
> Ignore-this: ec67d7a0a6d977438deaa342503f77e0
> We have to eliminate the assumption that an empty write buffer can be
> constructed by setting the buffer pointers to zero: this isn't
> necessarily the case when the buffer corresponds to a memory-mapped
> file, or other in-memory device implementation.
> ]
> [Deprecate Control.OldException
> Ian Lynagh <igloo at earth.li>**20090804143910]
> [Windows build fix, following RTS tidyup
> Simon Marlow <marlowsd at gmail.com>**20090803131121
> Ignore-this: ce862fb91c2b234211a8757f98690778
> ]
> [Updates to follow the RTS tidyup
> Simon Marlow <marlowsd at gmail.com>**20090801220743
> Ignore-this: 6e92412df93a66c12d75344053d5634
> C functions like isDoubleNaN moved here (primFloat.c)
> ]
> [Add integer-simple as a build option
> Ian Lynagh <igloo at earth.li>**20090722013151]
> [Use shift[LR]Integer in the Bits Integer instance
> Ian Lynagh <igloo at earth.li>**20090721222440]
> [depend directly on integer-gmp, rather than indirecting through  
> integer
> Ian Lynagh <igloo at earth.li>**20090721185228]
> [Move the instances of Functor and Monad IO to GHC.Base, to avoid  
> orphans
> Simon Marlow <marlowsd at gmail.com>**20090722102130
> Ignore-this: a7d85ac0025d559674249de0108dbcf4
> ]
> [move "instance Exception Dynamic" so it isn't an orphan
> Simon Marlow <marlowsd at gmail.com>**20090721093854
> Ignore-this: 5ede91ecfec2112c91b699d4de87cd02
> ]
> [Improve the index checking for array accesses; fixes #2120 #2669
> Ian Lynagh <igloo at earth.li>**20090719153228
> As well as checking that offset we are reading is actually inside the
> array, we now also check that it is "in range" as defined by the Ix
> instance. This fixes confusing behaviour (#2120) and improves some  
> error
> messages (#2669).
> ]
> [Make chr say what its argument was, if it's a bad argument
> Ian Lynagh <igloo at earth.li>**20090718151049]
> [remove unused warning
> Simon Marlow <marlowsd at gmail.com>**20090715124416
> Ignore-this: 31f613654089d0f4a44363946087b41e
> ]
> [warning fix: -fno-implicit-prelude -> -XNoImplicitPrelude
> Simon Marlow <marlowsd at gmail.com>**20090715122839
> Ignore-this: dc8957249731d5bcb71c01899e5adf2b
> ]
> [Add hGetEncoding :: Handle -> IO (Maybe TextEncoding)
> Simon Marlow <marlowsd at gmail.com>**20090715122519
> Ignore-this: 14c3eff996db062da1199739781e4708
> as suggested during the discussion on the libraries list
> ]
> [Add more documentation to mkTextEncoding
> Simon Marlow <marlowsd at gmail.com>**20090715122414
> Ignore-this: 97253b2624267df3a246a18121e8ea81
> noting that "//IGNORE" and "//TRANSLIT" suffixes can be used with GNU
> iconv.
> ]
> [Add the utf8_bom codec
> Simon Marlow <marlowsd at gmail.com>**20090715122257
> Ignore-this: 1c9396cd805201fe873a39382ced79c7
> as suggested during the discussion on the libraries list.
> ]
> [Export Unicode and newline functionality from System.IO; update  
> Haddock docs
> Simon Marlow <marlowsd at gmail.com>**20090713113104
> Ignore-this: c3f017a555335aa55d106253393f72e2
> ]
> [add a comment about the non-workingness of CHARBUF_UTF16
> Simon Marlow <marlowsd at gmail.com>**20090707124406
> Ignore-this: 98d00411b68d688b3b4cffc9507b1f35
> ]
> [Fix build on Windows
> Ian Lynagh <igloo at earth.li>**20090711004351]
> [Fix some "warn-unused-do-bind" warnings where we want to ignore the  
> value
> Ian Lynagh <igloo at earth.li>**20090710204513]
> [Use throwErrnoIfMinus1_ when calling getrusage
> Ian Lynagh <igloo at earth.li>**20090710204221]
> [Remove an unused import
> Ian Lynagh <igloo at earth.li>**20090710153345]
> [reportStackOverflow now returns IO ()
> Ian Lynagh <igloo at earth.li>**20090710153257
> It used to do "return undefined" to return IO a.
> ]
> [GHC.Conc.reportError now returns IO ()
> Ian Lynagh <igloo at earth.li>**20090710152646
> It used to return IO a, by "return undefined".
> ]
> [Fix some "warn-unused-do-bind" warnings where we want to ignore the  
> value
> Ian Lynagh <igloo at earth.li>**20090710152526]
> [Minor SampleVar refactoring
> Ian Lynagh <igloo at earth.li>**20090710151438]
> [Fix "warn-unused-do-bind" warnings in GHC/IO/Handle/Text.hs
> Ian Lynagh <igloo at earth.li>**20090710122905]
> [Fix some "warn-unused-do-bind" warnings where we just want to  
> ignore the result
> Ian Lynagh <igloo at earth.li>**20090710005638]
> [Use the result of writeCharBuf in GHC/IO/Encoding/Latin1.hs too
> Ian Lynagh <igloo at earth.li>**20090710004032]
> [Minor code tidyups in GHC.Conc
> Ian Lynagh <igloo at earth.li>**20090710003801]
> [Fix "warn-unused-do-bind" warning in GHC.Conc
> Ian Lynagh <igloo at earth.li>**20090710003530
> If we fail to communicate with the IO manager then we print a warning
> using debugErrLn from the ghc-prim package.
> ]
> [Fix "warn-unused-do-bind" warnings in System.Posix.Internals
> Ian Lynagh <igloo at earth.li>**20090709164546]
> [Fix "warn-unused-do-bind" warnings where we really do want to  
> ignore the result
> Ian Lynagh <igloo at earth.li>**20090709163912]
> [Add back imports needed on Windows
> Ian Lynagh <igloo at earth.li>**20090707181924]
> [Remove unused imports
> Ian Lynagh <igloo at earth.li>**20090707115810]
> [Remove unused imports from base
> simonpj at microsoft.com**20090706111842
> Ignore-this: f9b5f353e3bb820f787c56d615b28765
>
> These unused imports are detected by the new unused-import code
>
> ]
> [Use the result of writeCharBuf
> Simon Marlow <marlowsd at gmail.com>**20090706133303
> Ignore-this: 52288dd559bf4c4f313df6197091d935
>
> This only makes a difference when CHARBUF_UTF16 is in use, which it
> normally isn't.  I suspect CHARBUF_UTF16 doesn't currently work for
> other reasons (CHARBUF_UTF16 was an experiment before I wrote the
> GHC.IO.Encoding.UTF* codecs), but this patch at least makes it
> slightly closer to working.
> ]
> [Remove some cruft from Data.HashTable
> Ian Lynagh <igloo at earth.li>**20090706181630]
> [Add 'eof' to Text.ParserCombinators.ReadP
> simonpj at microsoft.com**20090706111801
> Ignore-this: 2aea7b848e00c894761bc4011adaa95d
>
> Add a ReadP parser that succeeds at the end of input. Very useful!
>
> ]
> [Don't export CLDouble for GHC; fixes trac #2793
> Ian Lynagh <igloo at earth.li>**20090705155120
> We never really supported CLDouble (it was a plain old double  
> underneath),
> and pretending that we do does more harm than good.
> ]
> [a byte between 0x80 and 0xBF is illegal immediately (#3341)
> Simon Marlow <marlowsd at gmail.com>**20090702081415
> Ignore-this: dc19ef59a1a21118d5a7dd38aa2f611c
> ]
> [avoid a warning
> Simon Marlow <marlowsd at gmail.com>**20090630084134
> Ignore-this: c92a45ee216faf01327feae9fe06d6e2
> ]
> [Add a wrapper for libiconv.
> Matthias Kilian <kili at outback.escape.de>**20090629183634
> Ignore-this: 23c6047c0d71b745b495cc223574a47f
> ]
> [#include <sys/times.h> if we have it (should fix build problems)
> Simon Marlow <marlowsd at gmail.com>**20090629085351
> Ignore-this: a35e93b37ca9595c73460243180f4b9d
> ]
> [set binary mode for existing FDs on Windows (fixes some GHCi test  
> failures)
> Simon Marlow <marlowsd at gmail.com>**20090626120522
> Ignore-this: 580cf636e9c77d8427aff6861d089481
> ]
> [Move directory-related stuff to the unix package
> Simon Marlow <marlowsd at gmail.com>**20090625120325
> Ignore-this: b997b3cbce0a46ca87ad825bbdc0a411
> now that it isn't used on Windows any more.
> ]
> [TAG 2009-06-25
> Ian Lynagh <igloo at earth.li>**20090625160056]
> Patch bundle hash:
> e934807d5e23dd06c0f5be2a213b0806d2fd4810
> -----BEGIN PGP SIGNATURE-----
> Version: GnuPG v1.4.9 (GNU/Linux)
>
> iEYEAREKAAYFAktHqCAACgkQvpDo5Pfl1oJfFwCeOmXae1y/6CH9/OJgHjvsHbab
> 2QwAoISiWb+2BMZcFiOthLO//z88mHqs
> =vKR7
> -----END PGP SIGNATURE-----
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



More information about the Libraries mailing list