-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 New patches: [This patch adds a timeout function to the base libraries. Trac #980 is Peter Simons **20070126222615 concerned with this issue. The design guideline for this implementation is that 'timeout N E' should behave exactly the same as E as long as E doesn't time out. In our implementation, this means that E has the same myThreadId it would have without the timeout wrapper. Any exception E might throw cancels the timeout and propagates further up. It also possible for E to receive exceptions thrown to it by another thread. ] { addfile ./System/Timeout.hs hunk ./System/Timeout.hs 1 +{-# OPTIONS -fglasgow-exts #-} +------------------------------------------------------------------------------- +-- | +-- Module : System.Timeout +-- Copyright : (c) 2006 Taral +-- License : BSD-style (see the file libraries/base/LICENSE) +-- +-- Maintainer : libraries@haskell.org +-- Stability : experimental +-- Portability : non-portable +-- +-- Attach a timeout event to arbitrary 'IO' computations. +-- +------------------------------------------------------------------------------- + +module System.Timeout ( timeout ) where + +import Control.Concurrent (forkIO, threadDelay, myThreadId, killThread) +import Control.Exception (handleJust, throwDynTo, dynExceptions, bracket) +import Control.Monad (guard) +import Data.Dynamic (Typeable, fromDynamic) +import Data.Unique (Unique, newUnique) + +-- An internal type that is thrown as a dynamic exception to interrupt the +-- running IO computation when the timeout has expired. + +data Timeout = Timeout Unique deriving (Eq, Typeable) + +-- |Wrap an 'IO' computation to time out and return @Nothing@ if it hasn't +-- succeeded after @n@ microseconds. If the computation finishes before the +-- timeout expires, @Just a@ is returned. Timeouts are specified in microseconds +-- (@1\/10^6@ seconds). Negative values mean \"wait indefinitely\". When +-- specifying long timeouts, be careful not to exceed @maxBound :: Int@. + +timeout :: Int -> IO a -> IO (Maybe a) +timeout n f + | n < 0 = fmap Just f + | n == 0 = return Nothing + | otherwise = do + pid <- myThreadId + ex <- fmap Timeout newUnique + handleJust (\e -> dynExceptions e >>= fromDynamic >>= guard . (ex ==)) + (\_ -> return Nothing) + (bracket (forkIO (threadDelay n >> throwDynTo pid ex)) + (killThread) + (\_ -> fmap Just f)) } Context: [Add Kleisli composition Don Stewart **20061113015442] [IsString is GHC-only (so why is it in the Prelude?) Ross Paterson **20070123183007] [Applicative and Monad instances for Tree Ross Paterson **20070115174510] [Add IsString class for overloaded string literals. lennart@augustsson.net**20061221210532] [Added examples, more detailed documentation to Data.List Extracting sublists functions Andriy Palamarchuk **20061204164710] [fix threadDelay Simon Marlow **20070117091702 In "Add support for the IO manager thread" I accidentally spammed part of "Make sure the threaded threadDelay sleeps at least as long as it is asked", which is why the ThreadDelay001 test has been failing. ] [update section on "blocking" Simon Marlow **20070116124328] [Fix crash with (minBound :: Int*) `div (-1) as result is maxBound + 1. Ian Lynagh **20070115142005] [version of example using Tomasz Zielonka's technique Ross Paterson **20070105175907] [Added Unknowns for higher kinds Pepe Iborra **20061108155938] [Improved the Show instance for Unknown Pepe Iborra **20060813111816] [Show instance for GHC.Base.Unknown mnislaih@gmail.com**20060801233530] [Introduce Unknowns for the closure viewer. Add breakpointCond which was missing mnislaih@gmail.com**20060725174537] [Fix missing comma in Fractional documentation Alec Berryman **20061201173237] [Mention that throwTo does not guarantee promptness of delivery simonpj@microsoft**20061211123215] [Add note about synhronous delivery of throwTo simonpj@microsoft**20061211122257] [documentation for installHandler Simon Marlow **20061205154927 merge to 6.6 ] [dos2unix Simon Marlow **20061204095439] [don't try to compile this on Unix Simon Marlow **20061204095427] [TAG 6.6 release Ian Lynagh **20061011124740] [TAG Version 2.1 Ian Lynagh **20061009114014] [Bump version number Ian Lynagh **20061009114009] [Add support for the IO manager thread on Windows Simon Marlow **20061201152042 Fixes #637. The test program in that report now works for me with -threaded, but it doesn't work without -threaded (I don't know if that's new behaviour or not, though). ] [deriving (Eq, Ord, Enum, Show, Read, Typeab) for ConsoleEvent Simon Marlow **20061201144032] [Make sure the threaded threadDelay sleeps at least as long as it is asked to Ian Lynagh **20061128204807] [Add comments about argument order to the definitions of gmapQ and constrFields simonpj@microsoft**20061124164505] [Hugs: add Control.Parallel.Strategies Ross Paterson **20061124161039] [Move instance of Show Ptr to Ptr.hs (fewer orphans) simonpj@microsoft.com**20061124100639] [Add type signatures simonpj@microsoft.com**20061124100621] [Add an example of the use of unfoldr, following doc feedback from dozer Don Stewart **20061124011249] [trim imports Ross Paterson **20061123190352] [Data.Graph is now portable (enable for nhc98) Malcolm.Wallace@cs.york.ac.uk**20061123174913] [remove Data.FunctorM and Data.Queue Ross Paterson **20061112001046 These were deprecated in 6.6, and can thus be removed in 6.8. ] [make Data.Graph portable (no change to the interface) Ross Paterson **20061122010040 The algorithm now uses STArrays on GHC and IntSets elsewhere. (Hugs has STArrays, but avoiding them saves a -98, and boxed arrays aren't fast under Hugs anyway.) ] [One less unsafeCoerce# in the tree Don Stewart **20061120120242] [typo in comment Ross Paterson **20061120115106] [fix shift docs to match ffi spec Ross Paterson **20061117003144] [(nhc98) use new primitive implementations of h{Put,Get}Buf. Malcolm.Wallace@cs.york.ac.uk**20061116173104] [The wrong 'cycle' was exported from Data.ByteString.Lazy.Char8, spotted by sjanssen Don Stewart **20061110021311] [LPS chunk sizes should be 16 bytes, not 17. Don Stewart **20061110021254] [Update comments on Prelude organisation in GHC/Base.lhs Ian Lynagh **20061115001926] [Control.Parallel.Strategies clean-up: Added export list to avoid exporting seq, fixed import list strangeness that haddock choked on, and moved the deprecated functions to a separate section. bringert@cs.chalmers.se**20061113224202] [Control.Parallel.Strategies: added NFData instances for Data.Int.*, Data.Word.*, Maybe, Either, Map, Set, Tree, IntMap, IntSet. bringert@cs.chalmers.se**20061113221843] [Control.Parallel.Strategies: deprecate sPar, sSeq, Assoc, fstPairFstList, force and sforce. bringert@cs.chalmers.se**20061113215219 Code comments indicated that sPar and sSeq have been superceded by sparking and demanding, and that Assoc, fstPairFstList, force and sforce are examples and hacks needed by the Lolita system. ] [add Control.Monad.Instances to nhc98 build Malcolm.Wallace@cs.york.ac.uk**20061113113221] [Control.Parallel.Strategies: clarified documentation of parListChunk. bringert@cs.chalmers.se**20061112232904] [Added and cleaned up Haddock comments in Control.Parallel.Strategies. bringert@cs.chalmers.se**20061112220445 Many of the definitions in Control.Parallel.Strategies had missing or unclear Haddock comments. I converted most of the existing plain code comments to haddock comments, added some missing documentation and cleaned up the existing Haddock mark-up. ] [Fix broken pragmas; spotted by Bulat Ziganshin Ian Lynagh **20061111205916] [add doc link to bound threads section Ross Paterson **20060929103252] [hide Data.Array.IO.Internals Ross Paterson **20061111113248 It's hidden from haddock, and everything it exports is re-exported by Data.Array.IO. ] [add Data.Function Malcolm.Wallace@cs.york.ac.uk**20061110142710] [add Data.Function Ross Paterson **20061110141354] [whitespace only Ross Paterson **20061110141326] [move fix to Data.Function Ross Paterson **20061110141120] [import Prelude Ross Paterson **20061110140445] [Added Data.Function (Trac ticket #979). Nils Anders Danielsson **20061110122503 + A module with simple combinators working solely on and with functions. + The only new function is "on". + Some functions from the Prelude are re-exported. ] [__hscore_long_path_size is not portable beyond GHC Malcolm.Wallace@cs.york.ac.uk**20061110113222] [redefine writeFile and appendFile using withFile Ross Paterson **20061107140359] [add withFile and withBinaryFile (#966) Ross Paterson **20061107134510] [remove conflicting import for nhc98 Malcolm.Wallace@cs.york.ac.uk**20061108111215] [Add intercalate to Data.List (ticket #971) Josef Svenningsson **20061102122052] [non-GHC: fix canonicalizeFilePath Ross Paterson **20061107133902 I've also removed the #ifdef __GLASGOW_HASKELL__ from the proper Windows versions of a few functions. These will need testing with Hugs on Windows. ] [enable canonicalizePath for non-GHC platforms Simon Marlow **20061107121141] [Update documentation for hWaitForInput Simon Marlow **20061107111430 See #972 Merge to 6.6 branch. ] [Use unchecked shifts to implement Data.Bits.rotate Samuel Bronson **20061012125553 This should get rid of those cases, maybe lower the size enough that the inliner will like it? ] [fix Haddock module headers Ross Paterson **20061106124140] [fix example in docs Ross Paterson **20061106115628] [Add intercalate and split to Data.List Josef Svenningsson *-20061024172357] [Data.Generics.Basics is GHC-only Ross Paterson **20061102111736] [#ifdef around non-portable Data.Generics.Basics Malcolm.Wallace@cs.york.ac.uk**20061102103445] [Add deriving Data to Complex simonpj@microsoft**20061101102059] [minor clarification of RandomGen doc Ross Paterson **20061030230842] [rearrange docs a bit Ross Paterson **20061030161223] [Add intercalate and split to Data.List Josef Svenningsson **20061024172357] [Export pseq from Control.Parallel, and use it in Control.Parallel.Strategies Simon Marlow **20061027150141] [`par` should be infixr 0 Simon Marlow **20061027130800 Alas, I didn't spot this due to lack of testing, and the symptom is that an expression like x `par` y `seq z will have exactly the wrong parallelism properties. The workaround is to add parantheses. I think we could push this to the 6.6 branch. ] [fix example in comment Ross Paterson **20061023163925] [Use the new Any type for dynamics (GHC only) simonpj@microsoft**20061019160408] [add Data.Sequence to nhc98 build Malcolm.Wallace@cs.york.ac.uk**20061012135200] [Remove Data.FiniteMap, add Control.Applicative, Data.Traversable, and Malcolm.Wallace@cs.york.ac.uk**20061012095605 Data.Foldable to the nhc98 build. ] [STM invariants tharris@microsoft.com**20061007123253] [Inline shift in GHC's Bits instances for {Int,Word}{,8,16,32,64} Samuel Bronson **20061009020906] [Don't create GHC.Prim when bootstrapping; we can't, and we don't need it Ian Lynagh **20061004165355] [Data.ByteString: fix lazyness of take, drop & splitAt Don Stewart **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@gmail.com**20060917013530] [Hugs only: unbreak typeRepKey Ross Paterson **20060929102743] [make hGetBufNonBlocking do something on Windows w/ -threaded Simon Marlow **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 **20060927100342 See feature request #880 ] [fix header comment Ross Paterson **20060926135843] [Add strict versions of insertWith and insertWithKey (Data.Map) jeanphilippe.bernardy@gmail.com**20060910162443] [doc tweaks, including more precise equations for evaluate Ross Paterson **20060910115259] [Sync Data.ByteString with stable branch Don Stewart **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 **20060904231425] [remove obsolete Hugs stuff Ross Paterson **20060904223944] [Cleaner isInfixOf suggestion from Ross Paterson John Goerzen **20060901143654] [New function isInfixOf that searches a list for a given sublist John Goerzen **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@gmail.com**20060903133440] [fix hDuplicateTo on Windows Simon Marlow **20060901150016 deja vu - I'm sure I remember fixing this before... ] [Improve documentation of atomically simonpj@microsoft**20060714120207] [Add missing method genRange for StdGen (fixes #794) simonpj@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 **20060831125219] [remove some outdated comments Simon Marlow **20060831104200] [import Control.Arrow.ArrowZero to help nhc98's type checker Malcolm.Wallace@cs.york.ac.uk**20060831101105] [remove Text.Regex(.Posix) from nhc98 build Malcolm.Wallace@cs.york.ac.uk**20060831101016] [add Data.Foldable.{msum,asum}, plus tweaks to comments Ross Paterson **20060830163521] [fix doc typo Ross Paterson **20060830134123] [add Data.Foldable.{for_,forM_} and Data.Traversable.{for,forM} Ross Paterson **20060830133805 generalizing Control.Monad.{forM_,forM} ] [Make length a good consumer simonpj@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 **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 **20060828011515] [add advice on avoiding import ambiguities Ross Paterson **20060827170407] [expand advice on importing these modules Ross Paterson **20060827164044] [add Haddock marker Ross Paterson **20060827115140] [Clarify how one hides Prelude.catch Don Stewart **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 **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 **20060825110610] [document minimal complete definition for Bits Ross Paterson **20060824140504] [C regex library bits have moved to the regex-posix package Simon Marlow **20060824132311] [Add shared Typeable support (ghc only) Esa Ilari Vuokko **20060823003126] [this should have been removed with the previous patch Simon Marlow **20060824121223] [remove Text.Regx & Text.Regex.Posix Simon Marlow **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 **20060824041326] [Add spec rules for sections in Data.ByteString Don Stewart **20060824012611] [Sync Data.ByteString with current stable branch, 0.7 Don Stewart **20060823143338] [add notes about why copyFile doesn't remove the target Simon Marlow **20060823095059] [copyFile: try removing the target file before opening it for writing Simon Marlow *-20060822121909] [copyFile: try removing the target file before opening it for writing Simon Marlow **20060822121909] [add alternative functors and extra instances Ross Paterson **20060821152151 * Alternative class, for functors with a monoid * instances for Const * instances for arrows ] [generate Haddock docs on all platforms Simon Marlow **20060821131612] [remove extra comma from import Ross Paterson **20060819173954] [fix docs for withC(A)StringLen Ross Paterson **20060818170328] [use Haskell'98 compliant indentation in do blocks Malcolm.Wallace@cs.york.ac.uk**20060818130810] [use correct names of IOArray operations for nhc98 Malcolm.Wallace@cs.york.ac.uk**20060818130714] [add mapMaybe and mapEither, plus WithKey variants Ross Paterson **20060817235041] [remove Text.Html from nhc98 build Malcolm.Wallace@cs.york.ac.uk**20060817135502] [eliminate more HOST_OS tests Ross Paterson **20060815190609] [Hugs only: disable unused process primitives Ross Paterson **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 **20060812103835] [revert removal of ghcconfig.h from package.conf.in Ross Paterson **20060812082702 as it's preprocessed with -undef (pointed out by Esa Ilari Vuokko) ] [fix Data.HashTable for non-GHC Ross Paterson **20060811231521] [remove deprecated 'withObject' Simon Marlow **20060811152350] [Jan-Willem Maessen's improved implementation of Data.HashTable Simon Marlow **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@aedion.de**20060811144629] [Warning police: Removed useless catch-all clause sven.panne@aedion.de**20060811142208] [reduce dependency on ghcconfig.h Ross Paterson **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 **20060810182902] [move Text.Html to a separate package Simon Marlow **20060810113017] [bump version to 2.0 Simon Marlow **20060810112833] [Remove deprecated Data.FiniteMap and Data.Set interfaces Simon Marlow **20060809153810] [move altzone test from ghc to base package Ross Paterson **20060809124259] [remove unnecessary #include "ghcconfig.h" Ross Paterson **20060809123812] [Change the API of MArray to allow resizable arrays Simon Marlow **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 **20060808100708] [add traceShow (see #474) Simon Marlow **20060807155545] [remove spurious 'extern "C" {' Simon Marlow **20060724160258] [Fix unsafeIndex for large ranges Simon Marlow **20060721100225] [disambiguate uses of foldr for nhc98 to compile without errors Malcolm.Wallace@cs.york.ac.uk**20060711161614] [make Control.Monad.Instances compilable by nhc98 Malcolm.Wallace@cs.york.ac.uk**20060711160941] [breakpointCond Lemmih **20060708055528] [UNDO: Merge "unrecognized long opt" fix from 6.4.2 Simon Marlow **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 **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 **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 **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 **20060609075924] [comments for Applicative and Traversable Ross Paterson **20060622170436] [default to NoBuffering on Windows for a read/write text file Simon Marlow **20060622144446 Fixes (works around) #679 ] [remove dead code Simon Marlow **20060622144433] [clarify and expand docs Simon Marlow **20060622112911] [Add minView and maxView to Map and Set jeanphilippe.bernardy@gmail.com**20060616180121] [add signature for registerDelay Ross Paterson **20060614114456] [a few doc comments Ross Paterson **20060613142704] [Optimised foreign pointer representation, for heap-allocated objects Don Stewart **20060608015011] [Add the inline function, and many comments simonpj@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 **20060525111604] [export breakpoint Simon Marlow **20060525090456] [Merge in changes from fps head. Highlights: Don Stewart **20060525065012 Wed May 24 15:49:38 EST 2006 sjanssen@cse.unl.edu * instance Monoid ByteString Wed May 24 15:04:04 EST 2006 Duncan Coutts * Rearange export lists for the .Char8 modules Wed May 24 14:59:56 EST 2006 Duncan Coutts * Implement mapAccumL and reimplement mapIndexed using loopU Wed May 24 14:47:32 EST 2006 Duncan Coutts * 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@cse.unl.edu * Add unfoldr to ByteString and .Char8 A preliminary implementation of unfoldr. Wed May 24 01:39:41 EST 2006 Duncan Coutts * Reorder the export lists to better match the Data.List api Tue May 23 14:04:32 EST 2006 Don Stewart * pack{Byte,Char} -> singleton. As per fptools convention Tue May 23 14:00:51 EST 2006 Don Stewart * elemIndexLast -> elemIndexEnd Tue May 23 13:57:34 EST 2006 Don Stewart * 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 * 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 * Minor doc tidyup. Use haddock markup better. Tue May 23 11:00:31 EST 2006 Don Stewart * Simplify the join() implementation. Spotted by Duncan. ] [add a way to ask the IO manager thread to exit Simon Marlow **20060524121823] [Sync with FPS head, including the following patches: Don Stewart **20060520030436 Thu May 18 15:45:46 EST 2006 sjanssen@cse.unl.edu * Export unsafeTake and unsafeDrop Fri May 19 11:53:08 EST 2006 Don Stewart * Add foldl1' Fri May 19 13:41:24 EST 2006 Don Stewart * Add fuseable scanl, scanl1 + properties Fri May 19 18:20:40 EST 2006 Don Stewart * Spotted another chance to use unsafeTake,Drop (in groupBy) Thu May 18 09:24:25 EST 2006 Duncan Coutts * More effecient findIndexOrEnd based on the impl of findIndex Thu May 18 09:22:49 EST 2006 Duncan Coutts * Eliminate special case in findIndex since it's handled anyway. Thu May 18 09:19:08 EST 2006 Duncan Coutts * 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 * Handle n < 0 in drop and splitAt. Spotted by QC. Tue May 16 22:46:22 EST 2006 Don Stewart * Handle n <= 0 cases for unfoldr and replicate. Spotted by QC Tue May 16 21:34:11 EST 2006 Don Stewart * mapF -> map', filterF -> filter' ] [haddock fix Ross Paterson **20060518154723] [simplify indexing in Data.Sequence Ross Paterson **20060518154316] [Move Eq, Ord, Show instances for ThreadId to GHC.Conc Simon Marlow **20060518113339 Eliminates orphans. ] [Better error handling in the IO manager thread Simon Marlow **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 **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 **20060518012154] [add import Prelude to get dependencies right for Data/Fixed.hs Duncan Coutts **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 **20060517020150] [Use our own realloc. Thus reduction functions (like filter) allocate on the Haskell heap. Makes around 10% difference. Don Stewart **20060513051736] [Last two CInt fixes for 64 bit, and bracket writeFile while we're here Don Stewart **20060512050750] [Some small optimisations, generalise the type of unfold Don Stewart **20060510043309 Tue May 9 22:36:29 EST 2006 Duncan Coutts * Surely the error function should not be inlined. Tue May 9 22:35:53 EST 2006 Duncan Coutts * Reorder memory writes for better cache locality. Tue May 9 23:28:09 EST 2006 Duncan Coutts * 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 * 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 **20060510001826 plus much tweaking of imports to avoid cycles ] [add WordPtr and IntPtr types to Foreign.Ptr, with associated conversions Simon Marlow **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 **20060509092427] [add GHC.Dynamic Simon Marlow **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 **20060509023425] [Make length a good consumer simonpj@microsoft**20060508142726 Make length into a good consumer. Fixes Trac bug #707. (Before length simply didn't use foldr.) ] [Trim imports simonpj@microsoft**20060508142557] [Make unsafePerformIO lazy simonpj@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 **20060508122322 Mon May 8 10:40:14 EST 2006 Don Stewart * 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 * Import nicer loop/loop fusion rule from ghc-ndp Mon May 8 17:36:07 EST 2006 Don Stewart * Fix stack leak in split on > 60M strings Mon May 8 17:50:13 EST 2006 Don Stewart * 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 **20060508010311] [Fixed import list syntax Sven Panne **20060507155008] [Faster filterF, filterNotByte dons@cse.unsw.edu.au**20060507042301] [Much faster find, findIndex. Hint from sjanssen dons@cse.unsw.edu.au**20060507033048] [Merge "unrecognized long opt" fix from 6.4.2 Sven Panne **20060506110519] [ dons@cse.unsw.edu.au**20060506061029 Sat May 6 13:01:34 EST 2006 Don Stewart * Do loopU realloc on the Haskell heap. And add a really tough stress test Sat May 6 12:28:58 EST 2006 Don Stewart * Use simple, 3x faster concat. Plus QC properties. Suggested by sjanssen and dcoutts Sat May 6 15:59:31 EST 2006 Don Stewart * 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@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 **20060504093044] [use bracket in appendFile (like writeFile) Ross Paterson **20060504091528] [writeFile: close the file on error Simon Marlow **20060504084505 Suggested by Ross Paterson, via Neil Mitchell ] [Sync with FPS head dons@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@cse.unl.edu * Fix foldr1 in Data.ByteString and Data.ByteString.Char8 Mon May 1 11:51:16 EST 2006 Don Stewart * Add group and groupBy. Suggested by conversation between sjanssen and petekaz on #haskell Mon May 1 16:42:04 EST 2006 sjanssen@cse.unl.edu * Fix groupBy to match Data.List.groupBy. Wed May 3 15:01:07 EST 2006 sjanssen@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 **20060503113306 See http://www.haskell.org//pipermail/libraries/2006-April/005227.html Submitted by: bertram.felgenhauer@googlemail.com ] [inline withMVar, modifyMVar, modifyMVar_ Simon Marlow **20060503111152] [Fix string truncating in hGetLine -- it was a pasto from Simon's code Simon Marlow **20060503103504 (from Don Stewart) ] [Merge in Data.ByteString head. Fixes ByteString+cbits in hugs Don Stewart **20060429040733] [Import Data.ByteString from fps 0.5. Don Stewart **20060428130718 Fast, packed byte vectors, providing a better PackedString. ] [fix previous patch Ross Paterson **20060501154847] [fixes for non-GHC Ross Paterson **20060501144322] [fix imports for mingw32 && !GHC Ross Paterson **20060427163248] [RequireOrder: do not collect unrecognised options after a non-opt Simon Marlow **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 **20060426072521] [add Data.Fixed module Ashley Yakeley **20060425071853] [add instances Ross Paterson **20060424102146] [add superclasses to Applicative and Traversable Ross Paterson **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 **20060410111443] [GHC.Base.breakpoint Lemmih **20060407125827] [Track the GHC source tree reorganisation Simon Marlow **20060407041631] [in the show instance for Exception, print the type of dynamic exceptions Simon Marlow **20060406112444 Unfortunately this requires some recursve module hackery to get at the show instance for Typeable. ] [implement ForeignEnvPtr, newForeignPtrEnv, addForeignPtrEnv for GHC Simon Marlow **20060405155448] [add forkOnIO :: Int -> IO () -> IO ThreadId Simon Marlow **20060327135018] [Rework previous: not a gcc bug after all Simon Marlow **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 **20060323134514 See http://gcc.gnu.org/bugzilla/show_bug.cgi?id=26824 ] [commit mysteriously missing parts of "runIOFastExit" patch Simon Marlow **20060321101535] [add runIOFastExit :: IO a -> IO a Simon Marlow **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 **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 **20060315160232 Implementation for Hugs is missing, but should be easy. We need this for the forthcoming nested data parallelism implementation. ] [Added 'alter' jeanphilippe.bernardy@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 **20060315092942 as discussed on the libraries list. ] [Simplify Eq, Ord, and Show instances for UArray Simon Marlow **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 ] [Oops typo in intSet notMember jeanphilippe.bernardy@gmail.com**20060311224713] [IntMap lookup now returns monad instead of Maybe. jeanphilippe.bernardy@gmail.com**20060311224502] [Added notMember to Data.IntSet and Data.IntMap jeanphilippe.bernardy@gmail.com**20060311085221] [add Data.Set.notMember and Data.Map.notMember John Meacham **20060309191806] [addToClockTime: handle picoseconds properly Simon Marlow **20060310114532 fixes #588 ] [make head/build rule apply to all types, not just Bool. John Meacham **20060303045753] [Avoid overflow when normalising clock times Ian Lynagh **20060210144638] [Years have 365 days, not 30*365 Ian Lynagh **20060210142853] [declare blkcmp() static Simon Marlow **20060223134317] [typo in comment in Foldable class Ross Paterson **20060209004901] [simplify fmap Ross Paterson **20060206095048] [update ref in comment Ross Paterson **20060206095139] [Give -foverlapping-instances to Data.Typeable simonpj@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@microsoft.com**20060203175759] [When splitting a bucket, keep the contents in the same order Simon Marlow **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 **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 **20060124131121 Patch originally from Dinko Tenev , 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 **20060112154126] Patch bundle hash: 64fddd612c134d7f00fe92b3503750b7401ae429 -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.2 (GNU/Linux) iQEVAwUBRbqD70G8KP6ZCJ1yAQKlbAf/VTgmPfAVLnG8T6U5VR2uZmwOi6ma5coD uwzRk0WxhdCLJzUXdjeXQf4PNHcGvg9jK4t+1z/RZwUVlX+F4gVWw0e0WYzsC1Ze C5eUH3NgnWIV9jITPpsPEupaFt0iF+yOatR9+82EYIW1xYhLMz6KvOrmSOyQ5O1e 5XmqXAGSIj3YKVioYlGHeSa+NIkEhv5gAiDbyuX6HiT+qelF6CL45kWYFKer4VGx Zkj52YdsoaCsOccZoLwbZz5z0pmLZV8sni55YseWzdJmFjEmb94UvJKq+fnL+YnL y2Ahvp87DWj857mocWZEWlmwFhYB+M2izRfrK0LOqJJKKwpvd4Bzqw== =q0wa -----END PGP SIGNATURE-----