We've talked a bit about further tuning the ForiengPtr type for its use
in ByteString. Now I've got some numbers.
I added the following two cases to the ForignPtr type,
| PlainMallocPtr (MutableByteArray# RealWorld)
| RawAddress
The first case is for usual ByteStrings, allocated on the Haskell heap.
The later is an optimised tweak for turning "foo"# strings into
ByteStrings.
Overall, the results weren't stunning.
http://www.cse.unsw.edu.au/~dons/tmp/foreignptr-patch.png
Here we graph the running time for a range of ByteString functions. The
red line is the current code, the green line is with the optimised
ForeignPtr.
As you can, it gains a few percent on some functions. Small enough that
its probably not worth the effort for now. I've attached the patch I
used, in case anyone has some suggestions, but I don't think it should
be applied.
If we compare this with the changes between the stable and head branch:
http://www.cse.unsw.edu.au/~dons/tmp/stable_head_lazy.png
Red line is the current code, wit the 6.4.2 compiler.
Green line is the new lazy, cache-sized chunk bytestring, with the 6.4.2
compiler, not yet in fptools.
And the blue line is the current code, compiled with the head.
As we see here, red versus blue, the head offers some good speed ups
over a number of functions. The complexity of the lazy code is often
better though, so it wins on a few functions. What will be interesting
is to compile the lazy bytestring type with the head.
-- Don
New patches:
[ForeignPtr patch. Small gains
Don Stewart <[EMAIL PROTECTED]>**20060520043108] {
hunk ./Data/ByteString.hs 275
+#if __GLASGOW_HASKELL__ >= 605
+import GHC.ForeignPtr (mallocPlainForeignPtrBytes,newRawForeignPtr)
+#endif
+
hunk ./Data/ByteString.hs 1664
+#if __GLASGOW_HASKELL__ >= 605
+ p <- newRawForeignPtr cstr
+#else
hunk ./Data/ByteString.hs 1668
+#endif
hunk ./Data/ByteString.hs 1682
+#if __GLASGOW_HASKELL__ >= 605
+ p <- newRawForeignPtr cstr
+#else
hunk ./Data/ByteString.hs 1686
+#endif
hunk ./Data/ByteString.hs 1712
+#if __GLASGOW_HASKELL__ >= 605
+ fp <- newRawForeignPtr (castPtr cstr)
+#else
hunk ./Data/ByteString.hs 1716
+#endif
hunk ./Data/ByteString.hs 1725
+#if __GLASGOW_HASKELL__ >= 605
+ fp <- newRawForeignPtr (castPtr ptr)
+#else
hunk ./Data/ByteString.hs 1729
+#endif
hunk ./Data/ByteString.hs 1799
- fp <- mallocForeignPtrArray (len+1)
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 605
+ fp <- mallocPlainForeignPtrBytes (len+1) -- optimised, no finalizer style.
+#else
+ fp <- mallocForeignPtrBytes (len+1) -- normal ForeignPtr
+#endif
hunk ./Data/ByteString.hs 2126
- fp <- mallocForeignPtrArray (l+1)
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 605
+ fp <- mallocPlainForeignPtrBytes (l+1) -- optimised, no finalizer style.
+#else
+ fp <- mallocForeignPtrBytes (l+1) -- normal ForeignPtr
+#endif
hunk ./GHC/ForeignPtr.hs 22
+ newRawForeignPtr,
hunk ./GHC/ForeignPtr.hs 24
+ mallocPlainForeignPtr,
hunk ./GHC/ForeignPtr.hs 26
+ mallocPlainForeignPtrBytes,
hunk ./GHC/ForeignPtr.hs 78
+ | PlainMallocPtr (MutableByteArray# RealWorld)
+ | RawAddress
hunk ./GHC/ForeignPtr.hs 148
+mallocPlainForeignPtr :: Storable a => IO (ForeignPtr a)
+-- ^ Allocate some memory and return a 'ForeignPtr' to it. The memory
+-- will be released automatically when the 'ForeignPtr' is discarded.
+--
+-- GHC notes: 'mallocPlainForeignPtr' has a heavily optimised
+-- implementation in GHC. It uses pinned memory in the garbage
+-- collected heap, as for mallocForeignPtr. Unlike mallocForeignPtr, a
+-- ForeignPtr created with mallocPlainForeignPtr carries no finalizers.
+-- It is not possible to add a finalizer to a ForeignPtr created with
+-- mallocPlainForeignPtr. This is useful for ForeignPtrs that will live
+-- only inside Haskell (such as those created for packed strings).
+-- Attempts to add a finalizer to a ForeignPtr created this way, or to
+-- finalize such a pointer, will have no effect.
+--
+mallocPlainForeignPtr = doMalloc undefined
+ where doMalloc :: Storable b => b -> IO (ForeignPtr b)
+ doMalloc a = IO $ \s ->
+ case newPinnedByteArray# size s of { (# s, mbarr# #) ->
+ (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
+ (PlainMallocPtr mbarr#) #)
+ }
+ where (I# size) = sizeOf a
+
hunk ./GHC/ForeignPtr.hs 182
+-- | This function is similar to 'mallocForeignPtrBytes', except that
+-- the internally an optimised ForeignPtr representation with no
+-- finalizer is used.
+mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a)
+mallocPlainForeignPtrBytes (I# size) = IO $ \s ->
+ case newPinnedByteArray# size s of { (# s, mbarr# #) ->
+ (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#))
+ (PlainMallocPtr mbarr#) #)
+ }
+
hunk ./GHC/ForeignPtr.hs 235
+addForeignPtrConcFinalizer_ _ _ = return () -- or error?
hunk ./GHC/ForeignPtr.hs 250
+newRawForeignPtr :: Ptr a -> IO (ForeignPtr a)
+-- ^Turns a plain memory reference into a foreign pointer with no
+-- finalizers or other internal structure. Useful for when you care
+-- critically about space, and are sure you won't need to deallocate the
+-- value.
+newRawForeignPtr (Ptr obj) = return (ForeignPtr obj RawAddress)
+
hunk ./GHC/ForeignPtr.hs 318
- (MallocPtr _ ref) -> ref
+ (MallocPtr _ ref) -> ref
+ _ -> error "GHC.ForeignPtr: attempt to finalize a
ForeignPtr without finalizers"
}
Context:
[simplify indexing in Data.Sequence
Ross Paterson <[EMAIL PROTECTED]>**20060518154316]
[Move Eq, Ord, Show instances for ThreadId to GHC.Conc
Simon Marlow <[EMAIL PROTECTED]>**20060518113339
Eliminates orphans.
]
[Better error handling in the IO manager thread
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**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).
]
[add import Prelude to get dependencies right for Data/Fixed.hs
Duncan Coutts <[EMAIL PROTECTED]>**20060517222044
Hopefully this fixes parallel builds.
]
[Sync with FPS head, including the following patches:
Don Stewart <[EMAIL PROTECTED]>**20060520030436
Thu May 18 15:45:46 EST 2006 [EMAIL PROTECTED]
* Export unsafeTake and unsafeDrop
Fri May 19 11:53:08 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Add foldl1'
Fri May 19 13:41:24 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Add fuseable scanl, scanl1 + properties
Fri May 19 18:20:40 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Spotted another chance to use unsafeTake,Drop (in groupBy)
Thu May 18 09:24:25 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* More effecient findIndexOrEnd based on the impl of findIndex
Thu May 18 09:22:49 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* Eliminate special case in findIndex since it's handled anyway.
Thu May 18 09:19:08 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* 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 <[EMAIL PROTECTED]>
* Handle n < 0 in drop and splitAt. Spotted by QC.
Tue May 16 22:46:22 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Handle n <= 0 cases for unfoldr and replicate. Spotted by QC
Tue May 16 21:34:11 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* mapF -> map', filterF -> filter'
]
[copyCString* should be in IO. Spotted by Tomasz Zielonka
Don Stewart <[EMAIL PROTECTED]>**20060518012154]
[Fix negative index handling in splitAt, replicate and unfoldrN. Move mapF,
filterF -> map', filter' while we're here
Don Stewart <[EMAIL PROTECTED]>**20060517020150]
[Use our own realloc. Thus reduction functions (like filter) allocate on the
Haskell heap. Makes around 10% difference.
Don Stewart <[EMAIL PROTECTED]>**20060513051736]
[Last two CInt fixes for 64 bit, and bracket writeFile while we're here
Don Stewart <[EMAIL PROTECTED]>**20060512050750]
[Some small optimisations, generalise the type of unfold
Don Stewart <[EMAIL PROTECTED]>**20060510043309
Tue May 9 22:36:29 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* Surely the error function should not be inlined.
Tue May 9 22:35:53 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* Reorder memory writes for better cache locality.
Tue May 9 23:28:09 EST 2006 Duncan Coutts <[EMAIL PROTECTED]>
* 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 <[EMAIL PROTECTED]>
* 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
]
[add GHC.Dynamic
Simon Marlow <[EMAIL PROTECTED]>**20060509082739]
[Make length a good consumer
[EMAIL PROTECTED]
Make length into a good consumer. Fixes Trac bug #707.
(Before length simply didn't use foldr.)
]
[Trim imports
[EMAIL PROTECTED]
[Make unsafePerformIO lazy
[EMAIL PROTECTED]
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.
]
[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 <[EMAIL PROTECTED]>**20060509023425]
[Sync with FPS head.
Don Stewart <[EMAIL PROTECTED]>**20060508122322
Mon May 8 10:40:14 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* 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 <[EMAIL PROTECTED]>
* Import nicer loop/loop fusion rule from ghc-ndp
Mon May 8 17:36:07 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Fix stack leak in split on > 60M strings
Mon May 8 17:50:13 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* 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 <[EMAIL PROTECTED]>**20060508010311]
[Fixed import list syntax
Sven Panne <[EMAIL PROTECTED]>**20060507155008]
[Faster filterF, filterNotByte
[EMAIL PROTECTED]
[Merge "unrecognized long opt" fix from 6.4.2
Sven Panne <[EMAIL PROTECTED]>**20060506110519]
[Much faster find, findIndex. Hint from sjanssen
[EMAIL PROTECTED]
[
[EMAIL PROTECTED]
Sat May 6 13:01:34 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Do loopU realloc on the Haskell heap. And add a really tough stress test
Sat May 6 12:28:58 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Use simple, 3x faster concat. Plus QC properties. Suggested by sjanssen
and dcoutts
Sat May 6 15:59:31 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* 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.
]
[fix for non-GHC
Ross Paterson <[EMAIL PROTECTED]>**20060504093044]
[use bracket in appendFile (like writeFile)
Ross Paterson <[EMAIL PROTECTED]>**20060504091528]
[writeFile: close the file on error
Simon Marlow <[EMAIL PROTECTED]>**20060504084505
Suggested by Ross Paterson, via Neil Mitchell
]
[Add array fusion versions of map, filter and foldl
[EMAIL PROTECTED]
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.
]
[improve performance of Integer->String conversion
Simon Marlow <[EMAIL PROTECTED]>**20060503113306
See
http://www.haskell.org//pipermail/libraries/2006-April/005227.html
Submitted by: [EMAIL PROTECTED]
]
[inline withMVar, modifyMVar, modifyMVar_
Simon Marlow <[EMAIL PROTECTED]>**20060503111152]
[Sync with FPS head
[EMAIL PROTECTED]
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 [EMAIL PROTECTED]
* Fix foldr1 in Data.ByteString and Data.ByteString.Char8
Mon May 1 11:51:16 EST 2006 Don Stewart <[EMAIL PROTECTED]>
* Add group and groupBy. Suggested by conversation between sjanssen and
petekaz on #haskell
Mon May 1 16:42:04 EST 2006 [EMAIL PROTECTED]
* Fix groupBy to match Data.List.groupBy.
Wed May 3 15:01:07 EST 2006 [EMAIL PROTECTED]
* 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!
]
[Fix string truncating in hGetLine -- it was a pasto from Simon's code
Simon Marlow <[EMAIL PROTECTED]>**20060503103504
(from Don Stewart)
]
[Merge in Data.ByteString head. Fixes ByteString+cbits in hugs
Don Stewart <[EMAIL PROTECTED]>**20060429040733]
[Import Data.ByteString from fps 0.5.
Don Stewart <[EMAIL PROTECTED]>**20060428130718
Fast, packed byte vectors, providing a better PackedString.
]
[fix previous patch
Ross Paterson <[EMAIL PROTECTED]>**20060501154847]
[fixes for non-GHC
Ross Paterson <[EMAIL PROTECTED]>**20060501144322]
[fix imports for mingw32 && !GHC
Ross Paterson <[EMAIL PROTECTED]>**20060427163248]
[RequireOrder: do not collect unrecognised options after a non-opt
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**20060426072521]
[add Data.Fixed module
Ashley Yakeley <[EMAIL PROTECTED]>**20060425071853]
[add instances
Ross Paterson <[EMAIL PROTECTED]>**20060424102146]
[add superclasses to Applicative and Traversable
Ross Paterson <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**20060410111443]
[GHC.Base.breakpoint
Lemmih <[EMAIL PROTECTED]>**20060407125827]
[Track the GHC source tree reorganisation
Simon Marlow <[EMAIL PROTECTED]>**20060407041631]
[in the show instance for Exception, print the type of dynamic exceptions
Simon Marlow <[EMAIL PROTECTED]>**20060406112444
Unfortunately this requires some recursve module hackery to get at
the show instance for Typeable.
]
[implement ForeignEnvPtr, newForeignPtrEnv, addForeignPtrEnv for GHC
Simon Marlow <[EMAIL PROTECTED]>**20060405155448]
[add forkOnIO :: Int -> IO () -> IO ThreadId
Simon Marlow <[EMAIL PROTECTED]>**20060327135018]
[Rework previous: not a gcc bug after all
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**20060323134514
See http://gcc.gnu.org/bugzilla/show_bug.cgi?id=26824
]
[commit mysteriously missing parts of "runIOFastExit" patch
Simon Marlow <[EMAIL PROTECTED]>**20060321101535]
[add runIOFastExit :: IO a -> IO a
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**20060315160232
Implementation for Hugs is missing, but should be easy. We need this
for the forthcoming nested data parallelism implementation.
]
[Added 'alter'
[EMAIL PROTECTED]
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 <[EMAIL PROTECTED]>**20060315092942
as discussed on the libraries list.
]
[Simplify Eq, Ord, and Show instances for UArray
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>
]
[Oops typo in intSet notMember
[EMAIL PROTECTED]
[IntMap lookup now returns monad instead of Maybe.
[EMAIL PROTECTED]
[Added notMember to Data.IntSet and Data.IntMap
[EMAIL PROTECTED]
[add Data.Set.notMember and Data.Map.notMember
John Meacham <[EMAIL PROTECTED]>**20060309191806]
[addToClockTime: handle picoseconds properly
Simon Marlow <[EMAIL PROTECTED]>**20060310114532
fixes #588
]
[make head/build rule apply to all types, not just Bool.
John Meacham <[EMAIL PROTECTED]>**20060303045753]
[Avoid overflow when normalising clock times
Ian Lynagh <[EMAIL PROTECTED]>**20060210144638]
[Years have 365 days, not 30*365
Ian Lynagh <[EMAIL PROTECTED]>**20060210142853]
[declare blkcmp() static
Simon Marlow <[EMAIL PROTECTED]>**20060223134317]
[typo in comment in Foldable class
Ross Paterson <[EMAIL PROTECTED]>**20060209004901]
[simplify fmap
Ross Paterson <[EMAIL PROTECTED]>**20060206095048]
[update ref in comment
Ross Paterson <[EMAIL PROTECTED]>**20060206095139]
[Give -foverlapping-instances to Data.Typeable
[EMAIL PROTECTED]
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
[EMAIL PROTECTED]
[When splitting a bucket, keep the contents in the same order
Simon Marlow <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**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 <[EMAIL PROTECTED]>**20060124131121
Patch originally from Dinko Tenev <[EMAIL PROTECTED]>, 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 <[EMAIL PROTECTED]>**20060112154126]
Patch bundle hash:
1d68881d18639140de28e115eee99dec5ac503df
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc