[commit: packages/bytestring] master's head updated: Merge pull request #38 from DaveCTurner/patch-1 (08d5c3a)

git at git.haskell.org git at git.haskell.org
Fri Jan 23 22:44:06 UTC 2015


Repository : ssh://git@git.haskell.org/bytestring

Branch 'master' now includes:

     1f9a3a1 new APIs from Pugs: idx, lineIdxs, packChar, elems
     6d4cf90 Added more documentation to betweenLines.
     bfd349a Changed FastFastString to FastPackedString in some error messages.
     deb0e46 Include index and string length in index and indexWord8 error messages.
     a272568 Added copy function.
     c5f683f Added QuickCheck property for copy.
     9474a49 Added inits and tails, with QuickCheck properties.
     a540a51 Added isSubstringOf, findSubstring and findSubstrings, with QuickCheck property. Implemented using the Knuth-Morris-Pratt algorithm.
     dc8d7e9 Some clean-up of findSubstrings.
     178a1dd Splitting lines with CRLF
     fde3fb9 Add replicate. been hanging around in hmp3 for a while
     703b121 add some new functions. and use inlinePerformIO, courtesy Simon M
     616c7bc Faster map, factor out cbits, and general cleanup
     2472930 mergeo
     c9f9432 Make no-mmap the default
     19aadae Tweak some functions, based on benchmarks
     d0a7235 tweak
     c981e16 benchmark tweaks
     3e20f36 typo in cabal file
     5a3b30e And also test Data.PackedString while we're here
     7b78404 and flush
     c1ad58d more flushing
     4921ec8 Some tests won't run in the benchmark
     ab27092 benchmark results
     658bbc5 And bump version
     2c1aa8c And benchmark against previous version
     c06335f comment only
     670ad36 Replace C maximum and minimum with fast Haskell versions
     e337942 Also run benchmarks by default
     b641fc6 BSD license everything. Remove some more cbits
     e35498a Comments, and clean up a warning
     52f60d8 Use plusPtr, instead of advancePtr, as Bulat suggested
     ba5cc13 update benchmark results with non-cbit code
     fdb9390 Squash space leak in findIndicies
     f33f91c typo in STRICT1 macro
     81c26f8 Update bench times with new fast elemIndicies
     602881f mention speed of box the benchmarking was done on
     720a302 Add SCC tags to Bench.hs, so we can optimise on space too
     0272fd7 More efficient tails and much better elemIndices on space and tiem
     0af4b9f Add filterChar, a space and time efficient version of filter . (==), + properties
     cad2a5b elemIndices benches updated
     7ca5914 Tweak Bench.hs
     95c2ea1 1G stress test results
     59c7ac2 and results for 0.5G strs
     d0460ec typo
     8f55718 USE_MMAP should wrap some cbits too
     7b6c506 And guard the .h file , just for good measure
     a2932ce Restore fast C versions of maximum and minimum. But make them optional
     621fb7a +unsafeIndex, and Simon's 'split', which has nicer algorithmic properties
     157b3c1 Merge Simon's QC tests with our own. Combine all testing into 'make' target
     e9523c3 hmm. can't use -Defs in cbits, for current cabal, at least
     2b0ef36 Clean up todo lsit
     1bdcbd1 More emphasis on Word8.
     986707f More docs
     7da8c03 Bump version
     bd5c752 1 less todo
     44c1a30 doc tweaks
     03df26c wibbles
     7c6b651 Return rest of string in readInt
     3d360b8 And update qc test
     097150c Benchmark for ghc 6.6
     71305af Fix compiling for GHC 6.5
     4cbc1e0 HEADS UP: Module renamed: Data.ByteString
     c4c094a getLine, getContents, faster elemIndices and lineIndices
     844c496 more benchmarks, more properties
     aa8cba1 Merge splitWith and breakAll. splitWith is faster. Hence encode words as tokens isSpace
     7f3f681 Update speed
     c9c8614 Faster version of 'split'
     84000f3 Update timings
     7cd4d62 Reexport ByteString through FastPackedString. Solves versioning issues. Idea from Einar
     8bf1b77 Add join2, a specialised join. And a ByteString getArgs (!)
     1ba2c76 Docs only
     73308dd Add wc -l benchmark
     9161cbe Export unsafeIndexWord8. Sometimes useful
     be4fa54 wibble
     1dd7b8a Add bytestring putStr and putStrLn. Just synonyms
     d350ebb Add zip, zipWith, unzip + QC properties
     780913b Benchmark zip and zipWith
     482a72f Add revcomp benchmark
     5a03914 Comments and cleanup
     948b21e 5x faster replicate. Uses memset
     6930e7f More benchmarks
     d3d9afa Most of the todos are done
     ba0319b Bump version
     ebd90fb benchmark
     4347862 And also make a legacy synonym for FastString. Einar's idea again
     0dfd75b Move options back into pragma. Helps standalone use.
     b54a570 Docs, and 'construct' is now called 'packCStringFinalizer'
     f7b877e Add notElem + QC property
     515a3a5 Add filterNotChar == filter . (/=) , but 5x faster
     0800d9d whitespace only
     81458f8 space leak squashed in elemIndexLast
     7ccd18c Much more efficient breakLast
     5e5f970 Add bench case for elemIndexLast
     5040bb5 HEADS UP : split Word8 and Char between Data.ByteString and Data.PackedString.Latin1
     10d901d HEADS UP: the split is now : Data.ByteString and Data.ByteString.Char, the latter provides Char ops (and exports pure ByteString ops too)
     18c9acf typo
     3e479df typo
     e34e449 complexity wrong in packChar/Byte
     870a179 Also export IO functions through Data.ByteString.Char
     b08d519 typo
     ebb519f filterChar * and friends aren't using predicates, pointed out by Duncan
     dc26ca7 typo
     4f1e432 typo
     ad2c639 Inline pragmas speed up some things
     01c29e7 complexity annotations
     fece71a tweak inlines, based on empirical studies
     ee1b13a Add some #ifdefs for GHC specific things
     e38cbad HEADS UP: Data.ByteString.Char -> Data.ByteString.Latin1. All functions needing Char.* now in Latin1.
     1ac0cb6 Better comments. 100% faster isSuffixOf (only look at the end of the string), and 30% faster append (don't use concat, just memcpy)
     c28f981 Also move readInt* into Latin1.hs. It drops spaces.
     b9b7af4 wibble
     9e020ea Can't append in one memcpy. Bad on memory pressure
     3397941 Update bench mark times
     a3f38e9 Benchmakr Char and Word8 layer simultaneously
     cb81626 No need for separate Byte column. they run at the same speed
     0b6bfd3 strictness on split doubles speed
     28e4c98 comment only
     dfbe46c comment
     8202887 wibble
     b8b6b83 Ok. Finally. John, Einar and I all prefer ByteString.Char8. So that's what it is. Don't make any claims about latin1 or encodings or nought.
     9bbed39 Implement count :: Word8 -> ByteString -> Int. Makes for 1 liner filterChar, and 3 x faster too. Idea from Ketil
     e8c12f4 Export packAddress* via Char8 too
     19dc69a Use Foreign.Concurrent.newForeignPtr whenever using GHC. Means ByteString now runs interpreted in ghci successfully
     5f60a82 Add QC properties for (w2c . c2w) == id , and (c2w . w2c) == id
     7a4bed3 comment only
     af442f4 A more elegant 'count'
     ce1731f Use memcmp for compareBytes. It really is 4x faster now I check
     54ceebb And use faster (?) Char8 pack, after consultation with Einar
     46fff40 update benchmarks. looks good
     95e80d6 Use Ketil's idea for a custom Word8 isSapce
     8a254b3 point free Char8 makes the code simpler
     426170c comment only
     6a7a56d bump version
     201e25b comment only
     15daeef hGetNonBlock is glasgow-specific
     d18bc46 Fix portability to hugs. Only a few cppism and a pattern type annotation had crept in.
     b9424fd Make Quick.hs hugs friendly
     db24189 comment on pack's performance
     523b919 space only
     fdd841f Fix minor bug in splitWith on hugs only
     e8c1c14 Use Simon's qc framework. more amenable to testsuite error diffs
     fd76a0a typo
     48bcb8f comment
     b579c05 AudreyT's copyCStringLen patch
     c29225b Add cbits version of count, around 30% over memchr version
     fcd1432 typo
     6ca11b5 Fix indenting for YHC
     73f5e60 Unnecessary header import
     ec9e7a5 HEADS UP: remove mmapFile for now. Not portable enough. Enable cbits by default for hugs and ghc
     b911d08 Notes about porting to yhc and nhc
     edebcfe comments only
     3ae785c Fix rounding-pasto error causing string truncation in hGetLine
     aa01d97 Add spellcheck test from packedstring
     46b76d4 More info on running the testsuite
     2c5c7b6 Fix foldr1 in Data.ByteString and Data.ByteString.Char8
     dd51fa8 More foldl1/foldr1 properties, thanks to sjanssen
     0fb73f8 Add group and groupBy. Suggested by conversation between sjanssen and petekaz on #haskell
     3887603 And quickcheck and benchmark them
     c30df57 Another benchmark
     004c130 Another groupBy test. Suggested by sjanssen
     9848554 Bit faster if we filter before we map
     d2af22c Fix groupBy to match Data.List.groupBy.
     7bcaf68 Add -fglasgow-exts to OPTIONS_GHC
     f6f6964 comments only
     28b992e Migrate to counting sort.
     1f0fa7a Benchmarks for the new sort.
     56e53f5 couple of wibbles. and remove the stdlib header. not needed at all now
     d6ad48b sort goes from 13.9s to 0.16s over 20M. update benchmark numbers
     bd6f4ec todo is empty now
     ef5cbd4 have linesort run in 'make' under tests/ too
     14a6d8b clean up makefile
     e44e278 Array fusion for maps. We can now fuse map f (map g (map h ... ) into map (f . g . h ..) More functional array fusion to come.
     a5a1eea Add test for map fusion
     d598761 A better fusion test
     a084e72 Add gloop, a generic bytestring loop operator, and another RULE
     fd15070 simpler not elem
     c0f9fcd Some short cut cases in eq and cmp. Suggested by dcoutts, ndm and musasabi
     f18dfa0 Full array fusion for pipelines of maps and filters
     45a3e39 Add array fusion version of foldl.
     7b10a75 Fix build on hugs
     fde6eb2 Oh. oops. \a0 should be in the isSpace function. spotted by QuickCheck
     76efd07 comment only
     ede400e generalise some tests
     087f721 Use simple, 3x faster concat. Plus QC properties. Suggested by sjanssen and dcoutts
     7473f73 Do realloc on the Haskell heap. And add a really tough stress test
     d21a37d RULE to rewrite length . lines -> count
     60612c0 Misc wibbles
     844214f wibble
     a5b9af9 Remove some dead code
     71c4b43 dcoutt's packByte bug squashed
     47c23e3 Squish orphan rules warning
     21aa2a0 Add inline/unsafe bug test
     2cebdbd steal some more properties from the ndp quickchecks
     e0039af Start on fps 0.7
     7b06786 untab
     1b22799 Much improved find and findIndex. Idea from sjanssen. + QC properties
     5f0e191 filterF is fast enough now we can defined filterNotByte in terms of it
     dbfd6a3 Fix import syntax for hugs. From sven panne
     ade2948 Fix all uses for Int that should be CInt or CSize in ffi imports. Spotted by Igloo, dcoutts
     c07011c update timings
     b499779 Import nicer loop/loop fusion rule from ghc-ndp
     63864ec Fix stack leak in split on > 60M strings
     8999bb7 Try same fix for stack overflow in elemIndices
     764aaa8 Give unlines a chance to handle 0.5G
     13a3e5f Help out splitWith a bit
     60566dd Fix for picky CPP
     01cafa8 hide INLINE [1] from non-ghc compilers. pointed out by Einar
     04f87bc Critical INLINE on words exposes splitWith and halves running time
     4f1108c Better results on big arrays
     db321fc Reorder memory writes for better cache locality.
     014feab Surely the error function should not be inlined.
     352a0ba Generalise the type of unfoldrN
     6f145b9 merge-o
     5b315d5 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
     a0f4a54 Missing RULES pragma. doh
     e6a9f25 An Int constraint on the fusion rule can't hurt
     5714348 clearer RULE names
     24aa034 Test length/loop fusion
     26c4272 Disable length/loop fusion for the time begin. Too many allocs
     0ba8574 Partial implementation of Data.ByteString.Lazy
     507fe45 More ByteString.Lazy updates
     0e80679 group, join & indexing functions for .Lazy
     793f858 Factor error functions & strings.
     0f70003 Export a couple of things needed by Lazy.hs and Char8.hs
     c018ddc -Wall police
     5942797 More blurb on Lazy.hs
     a6b9b3a Bug in foldr (it was folding from the left) spotted by QuickCheck
     28ff585 Handle negative indices to take correctly. Spotted by QuickCheck
     1fd1e67 Add Lazy.filter
     77457be whitespace only
     ed8a704 Add QuickCheck properties for Data.ByteString.Lazy. Try runhaskell Lazy.hs in tests/
     8ac4b82 Fix deriving Show for hugs, now QC/Lazy tests pass on hugs too
     aed142b Also compile the QC/Lazy tests. Good for your stress
     e8b1fa8 A better Arbitrary instance
     0e75785 Change a couple more Int to CInt. Fixes compare on 64bit arches.
     619d36c Fix reverse and reverse QC check
     41e31a0 Optimise foldr1 foldl1 cases by relying on invariant
     5fd7e40 More Lazy updates.
     bdb59e2 Test a smaller range of Word8 in Lazy,hs, hoping to hit pivot elements more often. Clean up Quick.hs
     eb3dca3 Comment out splitWith until we work out how to do it.
     67a9972 QC properties for find, findIndex/find, elem, notElem, filterByte, filterNotByte
     edf009e HEADS UP: Add lazy IO functions. Haskell breaks the 4G barrier!
     7aebe35 Add IO with tunable chunk size
     0cca072 Add a Lazy.hs IO benchmark
     e014bb4 make haddock happy
     106ac9e Fix Int/Int64 types in Lazy tests
     a7d56fa Fix and tidy split & slitWith
     657edfc Add invariant checking and prop_split to QC tests of Lazy
     6b6087b Do our own realloc, and thus generate() can use the Haskell heap. Makes abotu 10% for reduction functions that use generate
     a7783a1 whitespace
     fe6ca78 Tweak test
     438b9cb Fix type of snoc in docs
     b7e5cf7 Add an alternative framework for QCing the Lazy module
     6471146 Add some zipping ops to .Lazy
     9d0ee20 Increase default chunksize to 128k, assuming everyone's cache is at least this big.
     6ff5940 More useful lazyio.hs
     84c57b5 Handle invariant failures in init and concatMap
     48b70f3 Add new tests to testsuite
     da78888 new realloc helps timings
     53a573b Add isPrefixOf to Lazy
     4ec8f29 Add QC test for isPrefixOf
     a311ea9 -Wall police. Manually fuse filter (not.null) . map f. More comments
     59c5c11 more tests
     20790a9 more tests
     769d735 Bump down default chunk size to 64k. Should be enough room for other programs
     de276e1 dead code elimination
     d89f66e Add 'make plot' target in tests/ that draws pretty graphs of Lazy vs Vanilla bytestrings
     0e700f6 Disable group/groupBy. There's a bug. Spotted by ADEpt. I dislike this function anyway. Too inefficient ;)
     5e687e4 Make "mycheck" generate different randoms each run. Moved test helpers common to both testsuites to separate module.
     cc22442 Merge ADEpts patch
     49af360 Missing --make in tests/
     5bf5bbf Probably fix for group/groupBy
     6f22d7b change code to make comment unnecessary
     6553da1 Remove special cases from split/splitWith. This improves the performance of L.split. For some reason L.splitWith is much slower than P.spltWith where as L.split is only marginally slower than P.split.
     32acc3e Add group & groupBy to benchmark The lazy version performs reasonably well.
     302caa3 disable groupBy for now. Note bug in groupBy (/=) when chunk size is 1 byte
     5130d5e -Wall police, and tweak Lazy.hs
     db21e25 Reorder Bench.hs slightly
     dade9de Tweak the graph output slightly
     2dcdc54 Fix sily copy'n'paste bug in Lazy.groupBy
     c70e7fb Fix -Wall groupBy warnings and re-enable groupBy benchmark
     116ba7a mapF -> map', filterF -> filter'
     93893c1 tweak tests
     191a625 Comment about the shift/peek::Word32 approach being slower
     7cb7c36 Move -fno-warn-orphans into OPTIONS pragma
     d6683f9 Tweak bench output
     6ef68ff Handle n <= 0 cases for unfoldr and replicate. Spotted by QC
     2ed2fb5 Handle n < 0 in drop and splitAt. Spotted by QC.
     47cb4da Lots more QC tests using the new framework
     39ed4c1 Add 'make fast' test target, just runs the QC tests 4 ways
     d43ba5c bug in comment
     39f8b07 More QuickChecks
     5d842dd More messing in the tests/
     de50e72 INLINE on Lazy.find,findIndex squashes whatever was happening, and they now run at ByteString speeds
     fbb21d1 INLINE also fixes splitWith
     409688f Since we can't fuse Lazy.map or Lazy.filter, use the fast P.map' and P.filter'
     39e9ff5 Clarify performance of lazy, now we've squashed the leaks
     5258db4 Add lazy foldl', with QC and benchmarks
     55ebf8a Comment out unimplemented things
     3bd80c4 Note that groupBy is still broken on defaultChunkSize=1
     62e2396 Fix Lazy.groupBy again The problem was happening for operators that are not equivalence relations eg (<). One bug was that it was using the operator the wrong way wround. The more subtle problem was that it was using the final element in the group to compare against rather than the first as Data.List.groupBy does. For example groupBy (<) [0,10,5] = [[0,10,5]] rather than [[0,10],[5]] this is because we compare 0 & 5 rather than 10 & 5 since the first element in the group is the one that is used as the representative element.
     03ef076 Whitespace changes
     e69bb20 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.
     4eb89f6 Eliminate special case in findIndex since it's handled anyway.
     defbd23 More effecient findIndexOrEnd based on the impl of findIndex
     e33c22c copyCString* in IO, and fix buglet in splitAt (degenerate cases the wrong way around)
     5a3ebc9 assertion test wrong way around. spotted by hugs (!)
     6a7c420 Use readFile, it'll avoid realloc issues
     fb9e23b Comment on when to use readFile over hGetContents
     9f5671f Export unsafeTake and unsafeDrop
     4325aef Make Lazy.replicate more efficient for large inputs
     c398265 Add lazy hGetLines to Data.ByteString
     d22b560 Add test for hGetLines. A faster, lazier wc -l
     0c72a33 Comment
     b8b88fc tweak
     e5182d5 Fix invariant violation in new replicate
     097bd22 asthetic tweaks to bench code, also add B.findIndexOrEnd
     a36ea23 Use Lazy.replicate in Lazy.filterByte
     1ff1260 Make sure to optimise the cbits
     aeedd0b Add files to help us compare the api of list vs. fps
     6919b5b Add iterate, repeat & cycle to .Lazy These are more infinite list functions using sjanssen's trick. Also add a smaller chunk size for use with these functions to make it a bit less wasteful of space (currently 4k vs 64k).
     0780594 Handle merge
     e96bb33 And make Duncan's patches type check
     871266e Add foldl1'
     d1118a9 More Properties.hs
     9b8cc7d Update api diff
     630739d Make the api easier to diff (try vimdiff *.api)
     60a1e69 Comment fix.
     3864856 Data.ByteString.Internal Contains functions which might be useful in several modules, but aren't appropriate to expose to users of ByteString.  For example: inlinePerformIO; various C functions.
     1f81030 Add fuseable scanl, scanl1 + properties
     7c01d4e Clean up api list
     c03b740 export scanEFL
     93e79b4 Merge Quick.hs into Properties.hs, the grand, unified properties list
     c677899 And clean up makefile. Add make fast target, for a quick, quick check
     6d95a27 And make Interal.hs hugs-friendly
     ef1fe9e Update readme to reflect new test structure
     4f4c664 Comment on the inappropriatness of concatMap on ByteStrings
     898ba3c Spotted another chance to use unsafeTake,Drop (in groupBy)
     f983e12 Sadly cc-options get applied to .hs files too which will break things. Such aggressive gcc flags are only appopriate for the fpstring.c module. Incidentally, -optc-O2 will also break on some arches due to mangler issues.
     d611123 Add Lazy.interact
     ac257c4 Use List function rather than inlined definition. (And this time it type-checks!)
     5a2f1f4 Hide Prelude.interact..
     8b85599 Tweak api
     7aa7c2b Move c2w, w2c into Internal, now Data.ByteString.Lazy.Char8 needs them too
     7ece59b Move more Char8 things into Internal.hs
     e729786 Add Data.ByteString.Lazy.Char8
     6cae62e Whitespace only
     10cc6e5 Plot with boxes. Clearer
     d6a750f Add SCC pragmas so make prof keeps working
     701937a Minor doc tidyup. Use haddock markup better. Remove untrue comment about CStrings in .Lazy. Note dons as author of .Lazy too.
     8c5c0a5 Simplify the join() implementation. Spotted by Duncan.
     d382afb Add a TODO list of things duncan and I talked about on irc
     917b833 More stuff to do
     ea4872e Abolish elems. It's name implied it was unpack, but its type didn't. it made no sense
     782192d wibble in todo list
     6b591c2 In the search for a more orthogonal api, we kill breakFirst/breakLast, which were of dubious value.
     2cafe9e elemIndexLast -> elemIndexEnd
     315cdc4 pack{Byte,Char} -> singleton. As per fptools convention
     169fdb2 Start a bit on the null terminated string property
     698fa97 Tweak todo
     81b2612 Reorder the export lists to better match the Data.List api If this seems a good idea, I'll do it for the .Char8 modules too.
     62669b3 Comment only.
     781e0f7 Another comment.
     e73d499 Add unfoldr to ByteString and .Char8 A preliminary implementation of unfoldr. Things that still need to be done: 1.  Tests for unfoldr. 2.  unfoldr currently reallocates a new buffer twice the size of the     old one, dcoutts has suggested an approach using concat.  We need     to compare the performance of these two approaches. 3.  unfoldr for .Lazy.
     9d8ad14 Merge dcoutt's and sjanssens's patch
     dfa86c4 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. This also helps with maintaining the invariant in .Lazy Implement unfoldrr and Lazy.unfoldr in terms of unfoldrN. Use fibonacci growth for the chunk size in unfoldr and simple quadratic growth for Lazy.unfoldr and in the latter case an upper bound on the chunk size. upper
     cdc2537 Doh! revert change to type used during debugging.
     a1493e6 Implement mapAccumL and reimplement mapIndexed using loopU Not fully tested yet.
     9bbdc07 Implement coalescing in cons Not perf tested yet. The coalescing threshold needs testing to find the ideal value.
     f2b04e5 Rearange export lists for the .Char8 modules and minor tidyups for the exprt lists of the other two modules.
     f171627 instance Monoid ByteString
     b670ef0 Swap the result tuple in loopU because it's obviously the wrong way round! ;-)
     245fdaa Add loopU for lazy ByteStrings This reuses much of the fusion machinery from the ByteString module so we only need to add loopU and the loop/loop fusion RULE.
     f98a041 Use loopU to make several ByteString.Lazy funcions fusable This is really just an experiment, though the QC tests still seem to be working, and the fuse test indicates that the fusion RULES are working.
     d643b04 export mapAccumEFL, mapIndexEFL for use in .Lazy
     8ca4f38 Add Lazy.inits and tails, including QC tests
     f252ebf Add Lazy.foldl1' And fix docs for foldl'
     41bff3f Documentation fix.
     f274442 Remove the api files, we know what's missing now
     17b17c2 Disable coalescing cons. Its too strict. Add QC test for diverging cons.
     44abde3 Add properties for unfoldr, mapAccumL and foldl1'
     9a2dc40 Make hugs happy
     ee2cff6 Further simplify the instances for ModeledBy
     e42c66c Dont need undecidable instances, just overlapping ones
     af239b0 Lots of commentary on how the model checking quickchecks works
     02bdf26 unfoldr is done. push of todo list
     09c41e3 Use the NatTrans class from Gofer to write a generic Model instance for types of kind * -> *
     19e0156 Note that foldl . map with lazy fusion seems to run slower. foldl'.map seems fine though
     4e443d1 Export some more fusion utilities, so we can QC them
     167a525 Convert all RULES into QC properties, and check them
     7d564eb And QC tests reveal my hacking lines/count rule was wrong if there's no \n in the string. Disable it.
     2eccd39 Make hugs happy
     2776fa3 Add breakEnd, (== spanEnd (not.p)). Like break, but from the end of the string
     b7387ec Move the ByteString representation and low-level bits to a Base module Also move the array fusion code. Patch up the import/exports for the other modules.
     f67f57a Make fuseEFL use a StrictPair for much better fusion performance With this change the fusion of fold . map runs about 40 times quicker since the extra strictness allows ghc to avoid allocting lazy pairs.
     5292e59 Prevent fuseEFL from getting inlined too early. This is a patch from ndp upstream.
     deae39d Trivial doc fix/tidy.
     f1f86f4 Do not need -fffi on any module except Internal
     5ed8e02 Re-enable all the fusion tests. Yay, fusion is no longer slower.
     92d6996 Update the fusion properties
     0d298fd Add (commented out) wrapper/loop version of loopU including the loop/loop wrapper elimination RULE
     0b877cf wibbles
     54cd59a Abolish .Internal. Move fusion stuff into .Fusion. And internal stuff into .Base
     e45460d comment wibbles
     5479525 More extensive use of strict pairs, from the ndp branch
     00ece53 Make hugs happy
     74d80bb Reinstante coalescing cons with a bigger warning about its strictness Also remove lazy cons QC test. Fix untrue comment on replicate.
     48cb990 Tiny doc addition
     b542235 Cleanup of existing Fusion code and wdges of new code for a new method. Rename NoAL -> NoAcc. Remove the noAL value, just use the constructor everywhere. rename type EFL to AccEFL and add several other special cases. Don't parameterise AccEFL by the in and out types, it's always Word8 Since we don't have so many 'Word8's all over the place we don't need the type W = Word8 short hand any more.
     cd167ec Enable and export the alternative array fusion system. It's not being used yet in ByteString but it can be tested seperately. It needs a very recent version of ghc-6.5 (May 25 or later) for the RULES matching to work reliably.
     b08de33 Add a couple TODO items to think about
     c049a85 Typo in comment
     32293b3 Typo fix.
     018b622 Heads up. unsafe* now moved to .Base
     e887494 Make haddock happy
     fb9c474 Move rules and loopU for lazy strings into Fusion.hs  too
     d174a2c Simplify type of loopL
     5a400cf Remove duplicated RULES
     2ba790c Fix nasty bug in doDownLoop Copy'n'paste bug. I wasn't calculating the new size of the array correctly which caused the array copying code to segfault.
     a5d3384 Remove big useless comment. We've debugged that problem now.
     7ab76b5 Update type of copyCString,copyCStringLen in export list comment
     63f5fe9 Make ByteString use the new fusion framework That is the V2 fusion framework.
     6998110 Fix to use the V2 fusion api properly (hangover from testing the V3 api)
     67c87a3 Another TODO item
     15a7209 Wibble. And fix bug in fuseMapMapEFL, spotted by QuickCheck
     e43ab40 Add QC properties for all v2 rules. Disable down/* */down rules for now
     0ec2603 Split up the list of tests to make QCing quicker Also add 'module Main where' so everything is exported which also makes QCing individual tests or groups of easier because we can do it in GHCi.
     511f31f Fix down/down loop fusion bug We have to keep track of the offset as well as just the length of the part of th dest array that has been filled in.
     210c656 Don't use inlinePerformIO for loopWrapper due to danger of sharing We really really don't want the dest array to be shared between two loops so use unsafePerformIO rather than inlinePerformIO. We're really depending pretty heavily on GHC optimiser semantics here. This fixes all the QC down loop fusion properties when compiled with -O.
     b417c54 Specify type for 'run', makes hugs happy
     df6c198 Use unsafePerformIO on all functions that allocate. Hopefully avoids sharing issues
     2432192 Fix bug in Lazy.scanl (bizarrely, imo, Haskell's scan returns a list one element longer than the input list)
     6def52b Three (!) pastos in scanr, scanr1. QuickCheck people!
     43c6de1 . Add tests that fusion is working in up/down/map/filter cases. . Clean up QuickCheckUtils a bit. . Add some commentary to the rules
     00bebfd Wibbles/ cleanup in Fusion.hs. Add a marginally faster doMapLoop (only carry one offset)
     2c23181 Add length/loop* fusion, with quickchecked properties. Worth ~10% speedup
     5c2d306 makefile wibble
     59bdb4d wibbles
     360fd6a wibbles
     9ab7341 typo
     cf8297c whitespace only
     1c797d7 wibble
     0aa0c75 Add minimum/maximum fusion too. But disable for now, its still at least 50% down on the C functions
     ca49272 Actually, reenable rules for maximum/minimum. Only around 10% worse in stable. Should be ok in the head.
     c9ca626 Add properties for wrapper elimination and associativity of sequence
     b363bbd Generate random up/down loops, for tougher testing of associativity and wraper elim
     d37ded1 whitespace, and don't flip args in fuseMapMap.
     952abb3 Add fusion properties for all noAcc forms
     ffe7441 missing cpp pragma in tests/
     9fd7507 And make QC properties for map/map fusion match the flipped args
     6e87064 Lazy.hGetNonBlocking
     b3063e3 wibble
     dbaa49c Add a fusion bench mark. Great results
     111da3d And add some big pipelines to illustrate the O(n) versus O(1) overhead fusion gives us
     d13c61f Add cpp to switch between v1 and v2 fusion. Enables us to run benchmarks both ways
     75dd83f Tweak copyright on Lazy.hs. the university of glasgow wasn't involved.
     77d72b0 notice 1 extra byte was allocated on empty and on singleton
     e493aba Comments on what happens in empty string cases for head, tail etc. Prompted by ndm
     98a0ab9 cpp in QuickCheckUtils.hs to handle missing functor instances
     625804b add make hugs target
     18847af Add mallocByteStringWith.
     334f1b5 generate -> createAndResize. Old name was silly.
     f9b2e0f tweak makefile for wc
     a31b144 comments and todos, only
     7282744 Wrong test in hGetN, spotted by bringert
     73dcc5e clean up notNull functions
     e392fcb Changed all functions in Lazy and Lazy.Char8 which deal with indices and lengths to use Int64. (All except mapIndexed that is, I leave the magic to dons).
     1e4528e A couple TODO isses to think about
     59f701e Use mallocForeignPtrBytes rather than mallocForeignPtrArray Since we're always using bytes anyway, saves te comopiler having to specialise the sizeOf (undefined :: Word8).
     1833a24 Add assertions to null & length Assert that the length is not negative. In the case that the assertion is disabled, consider negative lengths as null.
     26e8bc9 Use bracket in readFile, just like we do for writeFile
     cfb8df1 Add assertaions to unsafeHead, unsafeTail and unsafeIndex
     60d9c8e make hGetN and hGetNonBlockingN strict we can't do lazy IO except for hGetContents which reads the whole file and can semi-close the handle. also make hGetNonBlockingN take a maximum size so it matches the version from Data.ByteString.
     71c1a26 Merge
     548a7ca Remove pointless special case from hPut
     f728f47 put all the foreign imports in IO rather than pure This makes the unsafeness more explicit. We were mostly using them in an IO context anyway. Where we do need to use them in a pure context I've added unsafePerformIO
     b98e061 Reorgaise and rename low level ByteString generators rename create to unsafeCreate since it's not in IO rename mallocByteStringWith to create rename createAndResize to createAndTrim add createAndTrim' as a generalisation remove mallocByteString
     4ff9cd7 Fix type of pack in hugs
     7e1075a remove skipIndex. Use one of the elimination forms instead
     4f2c700 Add appendFile for both strict and lazy
     69a4c8f whitespace, wibble
     c0720fe Cleanup QCs to make them more presentable
     3de7b52 Comments on the difficulty of moving compareN/eqN into a single class
     4ca3eb7 Update sum test
     bb35978 Test described on haskell-cafe@
     a9cbc81 Also export appendFile via Char8.hs
     57736a5 Add cpp to switch between the 4 forms of fusion possibilities we currently have. Makes benchmarks much easier to generate
     9307970 Bench wibbles
     c101fce todo item.
     32b8007 make it possible to do fusion profiling too
     63cb7cd Add more strictness in the results of several functions Not sure if it actually help but it looks sensible.
     caaf1a4 Make the code stle for head consistent with tail
     6883f23 Make readChunks strict in a more obvious way
     dd1c02e Add more strictness in the results of a few Char8 functions
     0b93975 Add experimental Haskell impls of of readInt for Char8 and Lazy.Char8 Seems to work but not fully QC'ed (indeed no QC tests added yet) However it gets the same results for the sumfile test so it's probably ok...
     c017dc8 Experimental reimplementation of Lazy.Char8.lines for improved performance Not fully QC'ed but does work with sumfile. Quite a bit faster but significantly more complex (ie a page long rathe than 5 lines)
     211c496 QuickChecks for new readInt impl. And comments, -Wall police
     8c68f2f Remove half-completed, commented out readint
     9b3de58 Add QC properties for lines
     b053d80 wibbles
     5a22e28 HEADS UP: remove null termination pseudo-property
     a172f7a some todo issues dealt with
     c094919 Remove cpp in tests, makes hugs happy
     38de4ff tweak readme
     c453a14 make it easier to experimentally benchmark different chunk sizes
     ef4142c tweak
     6168ac2 Have 'darcs test' run a quick version of the QCs
     7a31d3c Use -optc-O1 in .Lazy*, -optc-O2 breaks with gcc 4.0.4. Spotted by Audrey
     398740e Add support for tuned foreign pointer implementation
     b011854 investigated, patched, done with foreign ptr tuning
     89057e8 Remove test that depends on TH. Rarely used. Not maintained
     4e1be24 Update testsuite instructions
     e91d2d1 update list of things that are run on 'make everything'
     7ee9a4d More readme tweaks
     cc3f6b3 wibble
     fa1edb8 Start documenting how to do this handle flushing/copying trick
     3f4fc55 couple of todo/comments only
     4873f11 some more todos
     fca6a4b Run each benchmark several times Requires changing the 'F' stuff so that it doesn't memoise. Rearange the fusion tests into up,down and noAcc groups. Currently run each test 11 times so we can use 10 runs (after discarding the first run)
     ff6ed37 todos
     8940338 add better hPutStrLn, avoids locking the handle twice on small strings. Suggested by Bulat
     d11989b Comment on the include-dirs relative path issue
     37c1d78 unsafe* shouldn't be exported from Char8
     134f7f0 hGetLines should be exported via char8 too
     7dd1d36 Prepare for merging back into bsae/
     971e486 faster 'darcs check'
     7271765 make hugs happy
     5b712c4 Prefix C calls in fpstring.[hc] with fps_
     e91b0f4 resync Lazy.Char8 and Lazy
     66fb6d4 and fix import Prelude hiding list
     107c58d Add model checking property for mapAccumR
     894a06c more export wibbles
     1046b62 wibble
     8acf611 comments in .cabal file
     0527446 note that bench is temporarily broken.
     5284bd8 wibble in test
     d3845cb wibble
     b8235fc update docs
     2797e1c doc fix
     1dd6afc Add target 'prop-opt', after uncovering as-yet-unfound bug in -O -frules-on
     4319232 Also export appendFile via Lazy.Char8
     861bec1 Dirty the cache before each run and reorder the GC & delay
     b869807 Fix copy'n'pasto in SCC name
     b74a034 Re-export appendFile and import hGetNonBlocking(N).
     d743cbc move unsafeUseAsCString* into Base.hs. Sync Char8 and normal ByteStrings
     2638b40 Add zipWith', a speclialised zipWith. And QC properties for the zip family
     f56dc18 and add a zipwith specialisation test
     a72b40a missing #ifdef __GLASGOW_HASKELL__ in Lazy.Char8
     83e3e34 use just -O2
     aa46c20 no -optc-O2, breaks too often
     93938e0 better zipwith spec test. more notes
     0d102d2 Disable unpack/build fusion for now. It interacts badly with new rules stuff in ghc 6.5
     d4192b5 Fix unpackFoldr bug, twas the seq in the acc which breaks with rules
     8cda65d Further comment on seq and build/foldr
     d98203b portable call to time. Add unpack/head/build/seq test
     1db823f Fix bench. make runbench now works again, using the new dirty cache system
     54d9dec fromIntegral missing in test
     012cbf6 missing import in test
     427b4d3 some things done on the todo list
     7529a84 doc
     64a857e better dirtyCache, idea from roman
     8a237c1 O(1) useAsCStringLen, idea from BulatZ
     ca4c7d4 Clarify comments regarding *AsCString functions
     339db99 Handle TextMode properly on windows. Thanks to BulatZ
     de10f1d tighten import list
     ff644a2 openBinaryFile/openFile distinction
     2e95933 And use openFile/openBinaryFile in .Lazy stuff too
     c4f452b -optc-O1 is no more required (because we don't use -optc-O2 by default)
     ae7c607 Simple implementation of getArgs for non-GHC platforms
     98b6ffd hGetLines now use hIsEOF instead of catching all exceptions
     fe64085 ByteString.Char8 - removed now unnecessary #if_GHCs
     526ee5b 'interact' for strict ByteString
     c117e86 mallocByteString = mallocForeignPtrBytes | mallocPlainForeignPtrBytes
     e558b8b Merge changes
     ff06dcd Add hugs versions of some IO functions, merged from BulatZ's patches
     70c2c1e Simplified and unified lazy hGetContentsN/hGetN/hGetNonBlockingN
     4da0635 wibble in Makefile for clean
     ec8cabd Faster record test
     4e4e54b Merge-o
     41b4849 hugs wibble
     6cc3f27 missing import for hugs
     a4e4c54 todo, fix groupBy (in ghci only?)
     4077a26 Add test for groupby issue
     544d010 testify
     c9f5bb1 run unpackand groupby tests each 'make everything' run
     21a8c13 Lazy.Char8 was exporting interact from Prelude rather than Lazy
     e5b5f00 notes
     a518bfe add some missing functions to Char8
     5a8e0bc this is now the 0.8 branch
     ad407ca remember that we still have to fix groupBy
     fe12d1b Encourage users to use -funbox-strict-fields
     5689d41 comment out some tests we don't use now
     d74369a Sync 0.8 and streams api
     2e0cbb5 wibble
     e32c458 wibbles
     849a213 Add lazy-as-available byte strings
     7835ac8 comment out lengthU rules, now there's no lengthU
     2a57542 Merge
     e1d282a lazy init isn't O(1), I think it should be O(n/c)
     4c4e5ee Rewrite some lazy consumers so they don't cause space leaks
     e10b808 Merge from the unstable branch. API mostly, and hGetSome story. Add fast 'empty()' while I'm here
     35277e7 no more findIndexOrEnd exported
     4b49215 no more joinWithByte
     e720cfc remove some bogus things done better with rules
     a033c64 fix Properties.hs
     58c9c5d hide hGet*N functions in .Lazy
     3fddf55 no more tokens
     b9cbf4f inline words, don't export hGet*N from .Lazy.Char8
     6ab9c0f no more tokens QC
     dc27311 No, I can't just merge createAndTrim straight from unstable
     621678a good bye packWith/unpackWith
     fda06a7 rule for join -> joinByte
     586a265 rules for break/breakByte and span/spanByte
     4ca4656 propeties for the new rules
     cac7a61 add rules for break isSpace -> breakSpace
     b7a677e Add rule for specialise dropWhile isSpace -> dropSpace
     f897002 fix build for hugs
     2903ab6 more hugs fixes
     47836fb fusion wibbles
     674392e update Bench.hs to new api
     469ef32 hide internal module from haddock in Data.ByteString
     a965434 wibbe
     c72f9d3 hide LPS constructor. move lazy bytestring defn in to .Base
     66404de Fix testsuite
     a425ed1 add fromChunks/toChunks
     1e8f6c9 Fix type an implementation of toChunks. It should be returing a list of chunks! :-) Spotted by int-e.
     82fa5da add readInteger for *.Char8, and add appropriate quickcheck properties
     f5846b7 remove leftover strictness annotations. they seemed to hurt more than help.
     1d0da03 remove tokens and mapAccumR from .Lazy
     ef86c74 and another tokens occurence
     078c1e1 fix hugs
     b51f119 fix hugs nice and good
     4a4baee Fix lazyness of take, drop & splitAt. Spotted by Einar Karttunen. Thanks to him and to Bertram Felgenhauer for explaining the problem and the fix to me.
     f7bde9d make cons create 16 byte chunks instead of 17 byte chunks for lazy butestrings
     2188ffa export the right 'cycle'
     8fc2332 import portability fixes from Ross's base commits
     095aad0 remove a slighly suspicious use of unsafeCoerce#
     9a96c2b double check blank lines (since QC isn't generating them for us)
     0779fbc portability: give alternate import modules for nhc98
     85f4119 Workaround for import resolution bug in nhc98. Where there are multiple renamed imports:     import X as P     import Y as P     import Z as P and they all export or re-export the same entity e, nhc98 does not seem to be able to recognise that P.e is a unique entity, despite X.e, Y.e, and Z.e all referring to the same thing.  This patch just introduces an extra module name     import X as S so that S.e is resolvable.
     51c2929 workaround nhc98 import resolution bug for another module
     5b16acf wibbles to fix ghc build
     b7e569a Setup.lhs
     ae0daf1 Fixups for building with nhc98 - inadvertently missed this file earlier.
     1002e53 In teh testsuite, always pass the same GHC options, via ${GHCFLAGS}
     02ed236 Test the library in-place rather than whatever is installed
     2edc6c7 Add a unit tests file, a test that append is lazy in the tail, and make it so. Append was looking at the tails to see whether or not it was [], which forced evaluation of the tail in situations where that is undesirable.
     ebebe2a Add lazybuild test
     cfea341 Hide build noice when running tests
     2511eda HEADS UP: Change CString api
     b4f5c5f add iavor's CString test
     ea619ea remove filterNotByte, and its rules. Its a rather pointless rule (filter -> filterNotByte -> filter)
     f9363cb Make fromForeignPtr take the start so it is truly the inverse of toForeignPtr
     13e5395 transforming
     00c715b adhering to agile principles, requiring a boot-in-place to run the tests on each commit is removed..
     f7da7e0 no boot-in-place
     3f3c27c comment only
     a58f789 Make the lazy cons lazy, and add a cons' for when you want it to be strict
     f82f917 Correct docs for Data.ByteString.Lazy.Char8.cons
     bdbf53c Add cons' to Lazy.Char8 too
     2e228a1 Add complexity to Lazy.cons' docs
     b90d1cb Define headTail :: ByteString -> Maybe (Word8, ByteString)
     f9b78ce headTail -> uncons
     771dc5b Makefile build system for nhc98
     b11229e need things from cbits directory for nhc98  build
     8423510 fps package needs extra stack to build (+ add D.BS.Char8)
     56c0e47 Implement byteswapping, used for endian fiddling. If the ByteString is going to end up being interpreted as a binary representation of a sequence of 4-byte quantities (e.g. Float), then one might need to change the endianness (byte ordering) of the representation.  This patch adds the API call    byteswap :: ByteString -> ByteString for such applications.  It assumes the bytestring will be a multiple of 4 in size.  (If not, the last n<4 bytes will be untouched.)  It also assumes (without checking) that the start of the bytestring has the correct alignment.
     d2ed184 nhc now has hGetBuf/hPutBuf
     f7f3985 append on lazy bytestrings is O(n/c) (just the inital spine is copied0
     1ea65b1 Fix types of foreign imports
     a6b4957 Remove incorrectly typed commented out foreign imports
     bf0efcf old nhc98 Makefiles now obsolete
     7b08784 nhc98 needs extra stack to build for profiling
     c0c31a0 Change package name to bytestring and bump version number, and add myself as another author and maintainer
     6e5d6d4 Expect to use ghc-6.7 so no need for -DSLOW_FOREIGN_PTR and -funbox-strict-fields was never needed in the first place.
     d39e604 also rename fps.cabal -> bytestring.cabal
     b0b36ba Rename .Base module to .Internal
     72266d9 Move definition of empty from Internal to main ByteString module I can't recall why we moved it there in the first place, but it's not necessary any more.
     23b74c8 Split .Internal module into .Unsafe and .Lazy.Internal The Unsafe module exports parts o the public API but that do unchecked things like unsafe indexing, or things with CStrings that have side conditions. But it doesn't really expose the internal representation, for example it does not give away the fact that internally it uses ForeignPtrs. The Internal module now just exports really internal things including the representation, low level construction functions and utilities. The representation of lazy ByteStrings is moved into it's own Internal module which means we can call it ByteString without having to use a type alias. That should make hugs and/or nhc a bit happier.
     7c75495 We no longer use instance of type synonym extension
     8535e69 Change useAsCString so it does not use C malloc and free it was unnecessary
     e95ff44 Fix use of free finaliser in hGetContents The memory was allocated with mallocBytes so it must be freed with free or finalizerFree from the Foreign.Marshal.Alloc module. There is no guarantee that this is the same as the C free function.
     148248e Eliminate newForeignFreePtr just inline its only use.
     452cb77 No longer need to ffi-import C's malloc and free
     488cd64 Use the (re|m)allocBytes rather than (re|m)allocArray functions It's simpler and more direct, we are working with bytes here, not arrays. And remove unused imports.
     39a6287 Remove byteswap function It should not have been added in the first place. It's a fine function to have  but not in the basic ByteString module which we should try and limit to the list api.
     8df5fa4 Implement intersperse for lazy bytestring
     a6b8131 Remove unnecessary import
     38ef212 update some todos
     525fa2d Rename join to intercalate to match the standard Data.List And implement Lazy.Char8 version of intersperse
     5c9dfd6 Don't include undocumented functions into haddoc docs Use the #prune haddock module annotation. Move 'join' in export list to a section with no header so we don't get an empty section where join used to be.
     b0eb4b7 Move some lazy ByteString internals into the .Lazy.Internal module This therefore exposes them in case people need them (eg binary, zlib). It now exports the chunk size constants and the LPS data type invariant and data abstraction functions.
     fcbaaf1 Add Data.ByteString.Fusion to the cabal file
     8491513 Update copyright holders and add more metadata to .cabal file
     f247de8 Sort really does need allocaArray not allocaBytes Since it's an array of CSize not Word Since it's an array of CSize not Word8. Fixes segfault.
     13fb652 Fix Lazy.lines "foo\n\nbar"
     e650399 Add a dep on array
     2ebc807 Add a prologue.txt
     5ff00c9 Fix inlining of intercalate join was just the deprecated alias for the new intercalate
     df60977 Add isInfixOf as an alias of isSubstringOf For api compatability with Data.List
     16c1b07 Update the tests to work with module reorganisation
     84a4642 Add Lazy.mapAccumR and reimplement mapAccumL including tests
     ec17c23 Implement Lazy.groupBy Seems to pass the QC test.
     8dc8815 Rarange modules in .cabal file Hide the .Fusion module so we can change it later without changing the public api. Also, install the .h file.
     813c510 Few updates to the README
     e92a7d4 Remove hacks that are no longer necessary The simplifier no longer discards these I think.
     a12fd51 Add commented out exports for functions we're missing And change the formatting of some exports and docs of exported bits.
     2c2aba4 Add partition for strict and lazy Uses a simple implementation, we can optimise later. Getting the api addition in now is the priority.
     c8bf2c5 -Wall fix: don't import unsed thing
     bf60698 Export isInfixOf, alias for isSubstringOf
     e6fb272 Add Lazy.hPutStr as compatibility alias for hPut To match api of strict module.
     7236250 Add naive implementations of Lazy.unzip and isSuffixOf
     6efaafd Don't run the testsuite on commit, as it doesn't work
     80e45a1 Move the fpstring.h to an include directory.
     a769b71 spell nhc98-options correctly
     3c38c39 Remove reference in docs to non-existant function tokens
     130906e Remove one indirection in the representation of lazy ByteString Instead of: newtype ByteString = LPS [S.ByteString] we have: data ByteString = Empty | Chunk {-# UNPACK #-} !S.ByteString ByteString That is, the strict ByteString element is unpacked into the Chunk constructor so it's now just one pointer to get to the data rather than having to look up the S.ByteString cons element and then follow the pointer to the data. Combined with SpecConstr we should be able to get some good speed improvements.
     964d87d fix for Hugs: import internal newForeignPtr_
     7a0ab06 Export Fusion module, just for the sake of the testsuite
     9484264 TAG ghc-6.8 branched 2007-09-03
     e8e0d20 Add a boring file
     1a2c3a8 Make it build with ghc-6.4.2
     c128e41 Use new style syntax in .cabal file and use configurations for ghc-6.4.2 We previously had a comment saying what to change to get it to build with older ghc versions. Now we can do it automatically with configurations.
     ab51141 Haddock section header fixes, spelling, and trivial whitespace bits Section names and content should be more consistent between the modules now.
     dcadcc6 Export isInfixOf from Data.ByteString.Char8 It got added to Data.ByteString as an alias for isSubstringOf because isInfixOf got added to Data.List
     b8a9bbe Note that the ByteString searching api is about to be replaced So add a deprecated note to that effect to encourage people not to use them. Besides, the current implementation is slower than a naive search.
     5acb5d8 extra , at end of line not accepted by the head
     6158acb Comment out Cabal version check This was causing the build to fail as Cabal didn't know its own version number.
     d5e1bc6 bytestring head depends on array
     c08c2d5 Make it build with ghc-6.4 and 6.6 The patch cannot be pushed to ghc-6.8's bytestring branch until ghc bootstraps Cabal correctly, otherwise it trips up over the "cabal-version: >=1.2" field.
     08a3d3b typo in doc
     fdb9234 Documentation only: haddock the arguments and return values of fromForeignPtr and toForeignPtr.
     e2e9881 bump version number. import flags from ndp project
     5150cfc update QC properties for 6.8
     5f1ecc0 fix building of testsuite
     8ee6c71 move countOccurences out of .Internal
     6623251 clean up some internals (docs, inlining)
     2f9c786 don't test unpack stuff
     843ca60 Disable old array fusion mechanisms, was messing with the simplifier. Big perf improvements to lazy map/filter/fold
     c1d0766 no api changes, just perf improvments
     35ad399 keep haddock happy
     bc8c204 update small test programs
     decda6f add category
     593dc8c add isSpaceChar8, a good bit faster in tight inner loops
     5f59e92 For lazy IO operations, be sure to hClose the resource on EOF
     2d2432c new email address
     be6a669 add test for lazy hclose working
     ce7ac3c Remember to always hClose when doing a strict hGetContents. Avoids resource leaks.
     fe0175e Don't hClose on getN functions -- they're not expected to read the whole file anyway
     6af5098 complete test for resource leaks in getContents/readFile on both types
     83a7917 bump version
     f8d1f9e note that Lazy.lines is too strict, and sketch lazy imlementation
     62bfccd instance IsString for strict and lazy bytestrings. Use -XOverloadedStrings
     0daf1ef fix laziness issue with Lazy.lines
     7cfe53f bump version
     eaf7ba1 todo, find the memcmp length threshodl
     26af6ea typo in doc. spotted by Johan Tibell
     296754b Remove pessimistic INLINE on compareBytes. 5x speedup for some Ord-heavy tests
     d9f07e5 some tests on Ord speed
     419ed24 bump version
     bde5b1b Documentations typos (filterByte instead of filterChar).
     e3c9505 Use unsafeDupablePerformIO as a cheaper unsafePerformIO, fixes stack overflow issues in stack squeezing cases
     136021e clean up some things
     4a5e842 respect warnings
     2fe2097 portably use unsafeDupablePerformIO
     075673a erroneos inline [1] on Char8.dropWhile
     17a1e67 Add rewrite rule for Char8, matching the Word8 one, specialising break (==x)
     5c1f5a3 more tests
     b1e981f remove deprecated 'join' -- people should have transitioned to intercalate in the past 12 months
     c00c83d Document IsString ByteString, and how to enable it
     96dec13 dead code
     ed211e5 standardise rules firing with prefix "ByteString"
     bfef7b5 standardise rule names with   "ByteString" prefix
     f266cc4 tweaks
     7ae1eca normalise rewrite rule names
     5f1827a document second argument of hGet
     4a3478c note how to run testsuite with hugs
     fa42f18 bump version number
     95dfe74 use appropriate -X flags
     e4ba7c1 ghc uses -XUnliftedFFITypes -XMagicHash -XUnboxedTuples -XDeriveDataTypeable
     54ceef1 reuse internal invariant test
     03b25ab coverage for Monoid instance
     a02a52d Use -fno-ignore-asserts when testing
     07949b7 improve performance of findSubstrings on small strings
     6410a7f more test coverage
     40de93b actually fail if tests don't pass
     b7bc41b return failures
     c056923 use "ByteString" prefix for rules
     d4ab449 comments
     530170a add cheaper hpc test target
     df0d550 require Instances
     04e5992 no longer depend on array
     b385a04 tweaks
     0f032f4 more tests
     fe9ca2c faster findSubstrings
     a65029c Add breakSubstring, split a bytestring on another bytestring. More idiomatic approach than findSubstring
     4992455 properties for breakSubstring
     eedb41a tweak makefile
     4a3a75c better clean target
     c7be0e8 More coverage
     1ad58ab tweaks
     dc23b18 More testing. 80% of bytestring is now tested with QuickCheck
     8084d08 normalise rule names
     3484b9c more testing
     7a64776 typos in comment
     513458a add a cunning test for packMallocCString
     38fb6ad Remove obscure filter (==) rewrite rule
     ef59f64 Use -fglasgow-exts to re-enable rewrite rules
     1a2bf6d more QuickCheck properties, 88% covered now
     319d9fd pointless filter rule
     c189ff3 some more tests
     7700999 tune deprecation string
     eb346ed more tests
     530b8dc Remove old fusion mechanism. Data.ByteString.Fusion is a place holder for streams now.
     7c2790e fix warnings
     97baa03 Add properties for rewrite rules, compiled sans -fhpc
     345f3ef extra-source-files
     c84adbf Point to HPC coverage data
     d5548fe make hackage happy
     9d2cccf more aggressive inlining on lazy bytestring readInt. Performance wins for sum-file
     3ef2a98 clean up flags. building on 6.9
     1048c66 notes, and undo -fcpr-off
     46e21e3 typo in comment
     d16cdb7 clarify comments on hGet and EOF
     09229fa Only a minor version bump
     cbc3a57 stupid ghc-prim
     56e297e Drop unrecognised and unnecessary pragma
     fdcd243 Build with both base-3 and 4
     640608a Drop -fglasgow-exts, use LANGUAGE pragmas
     fc9b7c6 Whitespace changes to the package description
     631090a Bump version to 0.9.1.3
     6fc64f5 fix import of Control.Exception for nhc98
     a76f436 Drop dependency on syb with base 4
     4b60cb1 Bump version to 0.9.1.4
     f476915 Import fix for nhc98
     f75b4c3 avoid import renaming errors in nhc98
     c1e10f7 Make everything build with ghc-6.6 and 6.4 No code changes, just cpp for new LANGUAGE pragmas and not using a RULE with a funky LHS for ghc-6.4 which didn't allow it.
     d35456d Add TODO item to eliminate -fno-warn-orphans Orphan instances in libraries are not a good thing.
     b63d692 Fix strictness bugs in readInt and readInteger.
     83b1d54 Add a test for the laziness of readInt and readInteger over lazy ByteStrings
     265c4c6 bump versoin
     434be9b Use comma separated lists in the LANGUAGE pragmas Haddock complains.
     9ad8269 Improve the top-level documentation for the Unsafe and Internal modules Clarify the purpose and properties of the functions in the two modules. In particular try to disuade people from using the Internal functions unnecessarily.
     ac67540 Make docs for fromForeignPtr point to suitable public alternatives
     4b1b473 Fix docs for unsafePackAddressLen, it doesn't need null-termination
     28ecbeb Hide the .Internal modules in the haddock docs This should stop users accidentally using the semi-public modules while still leaving them available for extension packages. Also means that references to 'ByteString' go to a sensible place rather than the .Internal modules.
     579e862 Fix some "warn-unused-do-bind" warnings where we want to ignore the value
     8732db3 Remove INLINE pragmas on recursive functions Merge of patch from ghc's fork:   Fri Dec  5 17:04:52 GMT 2008  simonpj at microsoft.com     * Remove INLINE pragmas on recursive functions
     4d97daa Fix "cabal check" warnings Merge of patch from ghc's fork:   Tue Aug 11 22:58:58 BST 2009  Ian Lynagh <igloo at earth.li>     * Fix "Cabal check" warnings
     586ea72 Update for new IO library Merge of patch from ghc's fork:   Thu Jun 11 15:09:37 BST 2009  Simon Marlow <marlowsd at gmail.com>     * Update for new IO library
     719c21d Fix import warnings Patches merged from ghc's fork:   Tue Jul  7 12:58:17 BST 2009  Ian Lynagh <igloo at earth.li>     * Remove unused imports
     40c5f36 Clean up the language extension pragmas We cannot actually specify them correctly, see ghc ticket #3457. We can at least simplify things and make it clear it does not work, rather than having misleading code that looks like it might work.
     e9fc821 Update "tested-with" list It builds with ghc-6.4 through to 6.11 (23/08/09) It builds with no warnings with ghc 6.8, 6.10 and 6.11.
     8bd0a05 Fix elemIndices and split They were using inlinePerformIO to lazily delay IO actions within the scope of a withForeignPtr. Thus the ptr was still in use after the ForeignPtr went out of scope. This lead to dangling pointers, incorrect results and segfaults. Nasty. See ghc tickets #3486 and #3487. Audited the rest of the code base for the same anit-pattern. Thanks to nwn and people on the haskell-jp mailing list for reporting the bug with nice test cases and also to Ian, Bertram and Don for diagnosing the source of the problem.
     1bcfb05 Check for negative lengths in hGet and hGetNonBlocking See ghc ticket #3514
     8b49490 Check for negative lengths in packCStringLen
     8de83ec Update copyright dates
     a97d5e6 Use Setup.hs like everyone else does
     baf0c73 Drop the stability field from the .cabal file It is pretty meaningless. It also said "provisional" which isn't true.
     0d5abdf Fix warnings with ghc-6.12 And check and update tested-with list. It really does build with Cabal-1.2.3.0 and with ghc-6.4 through 6.12.
     7526f75 Remove redundant specialise pragmas GHC HEAD will now warn about these.
     cbb71b4 Make it compile with non-ghc.
     73b0bef hGetContents: use hGet instead of hGetNonBlocking + hWaitForInput + hIsEOF
     ae78a19 update docs for hGet, hGetNonBlocking
     6e67a2b Fix up import warnings
     d12e43d Bump version to 0.9.1.6
     31673d5 bump version to 0.9.1.7
     72b654e ROLLBACK: hGetContents: use hGet instead of hGetNonBlocking + hWaitForInput + hIsEOF
     74492ea ROLLBACK partly: update docs for hGet, hGetNonBlocking
     05ebb50 Fix for SPJs new typechecking system A local value was being generalised to Ptr a, and used at type Ptr Word8 and also at type Ptr CChar. SPJs new type checker prefers not to generalise local bindings such as this. This instance is also a bit wierd from an engineering point of view. The code is now more explicit that we are using a pointer at two different types, by using a castPtr, which is the same as the way we handle other CString cases.
     2b4485b Add a note to the docs for hGetContents(N) about using hSetBinaryMode See GHC bug #3808
     d55dfd6 Bump version number to 0.9.1.8
     e2e94a9 add Data.ByteString.hGetSome; use it in Data.ByteString.Lazy.hGetContents See GHC ticket #3808
     e9bba92 Fix syntax errors in one branch of an #ifdef
     1d0b973 Make it build again for nhc98.
     469dd6d Add an explicit Data.String import list to fix build with GHC 7.2
     38eca6f Fix imports for older GHC versions
     c65a5d7 Bump version number to 0.9.1.9
     2f0e605 Make is build with nhc98.
     fb2a76e Bump version number to 0.9.1.10
     15c5ae7 Use explicit import list for GHC.IO to avoid build failure
     6cef919 Add hPutNonBlocking Based originally on a patch by David Fox <david.fox at linspire.com> Fixes ghc ticket #1070. Also update the documentation for hGetNonBlocking
     dff7b69 Export putStrLn and hPutStrLn from D.B.Lazy.Char8 and deprecate both functions in the non-Char8 modules. Functions that rely on ASCII encodings belong in the Char8 modules.
     02aee0e Bump minor version due to API additions
     a95da63 Drop support for ghc-6.4 and 6.6
     151c1af Update maintainers' email addresses
     efdca75 Update the test suite to QC2 and add a tests-suite stanza to the cabal file QC2 uses a rather different instance for Arbitrary Int which uses much bigger numbers than QC1 used. Some properties have had to be updated to use a smaller int range or they would take nearly forever to run.
     9c7df37 Remove some old done TODO items
     d15a7ed Remove old GHC flag from Cabal file
     4af4f62 Use Safe Haskell if GHC >= 7.2
     385c93c Follow change to FFI decls: Import constructors of newtypes
     a73a711 Specify sensible fixities for cons and snoc As suggested by Yitzchak Gale.
     ff5b7ca Throw exception in IO for functions in IO Tracked down by Gershom Bazerman
     96eda1d Add NFData instances for strict and lazy ByteStrings
     7af3c56 Update cabal package metadata Remove old homepage, add source repo and bug report addresses.
     59648db Fix test-suite and get rid of some warnings Based on a patch by Bas van Dijk <v.dijk.bas at gmail.com>
     88f65a7 Remove unused fusion module
     a625b69 Add new internal list pack and unpack functions Use them for the Show and Read instances. They should also be a tad better in terms of speed and memory use.
     8ea65cb Add a proper Show and Read instance for lazy bytestrings Previous one was derived which was silly.
     18cec43 Add proper Data class instances that actually contain the data. Same style as instances for Data.Text.
     01374ce Move the IsString instance so it is not an orphan
     c914a5f Drop unnecessary -funbox-strict-fields and set -fspec-constr-count We use the UNPACK pragma explicitly in the couple places where we use strict fields.
     c25779d Use the new {un,}pack{Bytes,Chars} functions and simplify We had a whole variety of odd pack/unpack functions. The nice thing is that with modern ghc we can use simpler implementations and get as good or better code than the old ones.
     d8b0a5d Move Eq, Ord, Monoid instances to eliminate orphans
     ae5086b Add BangPatterns extension
     3c74db3 Add tests for groupBy Note that it fails for Lazy.groupBy due to a chunk boundary bug.
     8ae0cea Include non-0 offset in instance Arbitrary Strict.ByteString And fix a test that breaks.
     bdfe39c Add more extensive tests for the various new pack and unpack functions
     02aecf0 Clean up a few minor things in the test properties
     f51cb87 Fix implementation of Lazy.groupBy
     442fe00 CPP-conditional LANGUAGE pragmas now work since ghc-7.0.x
     6d6e732 Fix warning about C FFI types
     35db5c4 Fix for ghc-6.8 / base-3
     77af820 Update package description and tested-with list Liberally borrowed the style of description from the text package.
     464cdfa A few minor doc improvements
     5b17318 Update module metadata and copyright info
     52ae9e1 Bump version to 0.10.0.0 Some minor API changes and a number of extensions
     7c20c22 Fix documentation of complexity of toChunks
     77e1df6 Add conversion functions between lazy and (single) strict ByteStrings API proposal and initial patch by Herbert Valerio Riedel <hvr at gnu.org> http://article.gmane.org/gmane.comp.lang.haskell.libraries/16444 More or less unanimous support.
     2accd98 Also export foldrChunks and foldlChunks Along with fromStrict and toStrict we now match the Text API in this area.
     e0f62b4 Added tests for toStrict and fromStrict
     6e52436 Add new Builder monoid by Simon Meier The design of strict and lazy ByteStrings makes concatenation expensive. A builder monoid lets us efficiently build bytestrings by sticking bits together in an ad-hoc way. For example by pretty-printing or serialising. This is as opposed to a uniform approach using unfoldr.
     b33c352 Update docs for chunk size constants
     8112f6c Add the test suite for the builder monoid Again, this is Simon Meier's code
     3185c3b Make the builder test suite into a cabal test-suite The advantage is it makes it easier to run automatically. The disadvantage is we cannot use the nice test-framework package since cabal then thinks we've got a circular dependency since test-framework indirectly depends on bytestring. This will be solvable in future with encapsulated package dependencies, but util then we use a minimal implementation of the bit of the test-framework that we're using.
     c8e7960 Convert existing main test suite over to the minimal TestFramework code This will make it easier to switch to the test-framework package later.
     e9cb88f Add missing extension
     fe87271 Add Simon's builder benchmark suite and add to .cabal file Makes use of cabal's new support for benchmarks
     159ae22 Fix a few test failures due to incorrect Int64 -> Int conversion Switch it around so we only promote Int -> Int64.
     7efb416 port additional work on bytestring builder
     c59520d Do not expose the BasicEncoding and other internals for this release We are being conservative here. There is useful functionality that we will want to expose somehow eventually, including the fixed and bounded size encodings for maximum speed of short encodings, plus the ability to do things like size-prefixed runs of data. However we will give ourselves some time to let this stuff settle down and a bit longer to think about the best way to support the more advanced & low-level bits.
     0847231 Fix building with ghc-7.3 and hopefully 7.4.x also Based on a patch contributed by Herbert Valerio Riedel. Also fixes warnings for ghc-7.2.
     523c926 Add implementation of builder internal hPut for old or non-ghc Handle The current hPut is specific to newer GHC with the new Unicode Handle stuff. Provide an implementation for older ghc and non-ghc compilers.
     933e86f Make the testHandlePutBuilder conditional and add char8 version The testHandlePutBuilder does not apply to older ghc with the pre-Unicode Handles. Extra char8 test covers old ghc and should work with new too.
     febf5d2 Fixes for ghc-6.10
     b30ac17 Fix an issue with char/binary Handle write ordering with ghc-6.12 For 6.12 it needs an extra flushWriteBuffer.
     e0cfcd6 Fix some more import warnings
     6eb0d62 Allow using older versions of the random package
     f54a935 Move __hscore_memcpy_src_off from base into include/fpstring.h
     1b7baf1 Add .gitignore file for GHC build.
     aa31ed1 Add unsafePackMallocCStringLen
     f13d7b2 Add a NOINLINE [1] for zipWith as it is matched in a RULE GHC correctly warns that RULES cannot reliably match on functions that get inlined too early. Spotted by Paolo Capriotti.
     5d6b262 Implemented unsnoc, unsafeInit and unsafeLast
     89d58ea Fix property in the documentation for unfoldrN Spotted by Dan Burton
     97c2717 Fix implementation of hPutNonBlocking for non-GHC Spotted by Dan Burton
     0a324d0 Remove the old memcpy_ptr_baoff / memcpy alias
     0480fa9 Export hGetSome from Data.ByteString.Char8
     6ceb567 Use binary mode for Char8 file functions It doesn't actually make any difference these days, but it's better to be explicit and consistent about it here.
     515cc0d Add internal functions createUptoN and createUptoN' Just tidies things up, not exported for now.
     b0ac129 Rename Builder modules Just Data.ByteString.Builder rather than Data.ByteString.Lazy.Builder And instead of BasicEncoding, just Prim, so Data.ByteString.Builder.Prim And use Extra instead of Extras
     f185f61 Simplify the implementation of unsnoc We have to do two traversals either way, no saving.
     149e84a Rename Encoding types to Prim BoundedEncoding -> BoundedPrim FixedEncoding -> FixedPrim Also rename various operations to match
     6a23bf6 Re-export all of the D.B.Builder.ASCII via top level D.B.Builder Decided it's better to have a few biger builder modules than to confuse users with loads of Builder.* modules.
     5afd623 Expose the Data.ByteString.Builder.Prim module
     9bb2713 Don't export builder prim testing support functions Now that it's an exposed API
     a76a0d7 Document for the Char8 I/O that it does not respect the newline mode though that this is considered a flaw and may be changed in future.
     715a007 Go back to using short names for eitherB, condB combinators
     6e45e78 Rename byteStringHexFixed to just byteStringHex The Fixed added nothing in this case, as the alternative would be silly.
     ff2fc80 Adjust documentation to talk about builder primitives rather than encodings
     85ffe22 Minor doc addition, spelling fixes
     7a8cf9c Add and export a lower level runBuilder function
     ad3436d Mention the Builder in the package description
     9a9c417 Reluctantly expose the builder internal modules with a stiff warning
     40bf048 Fix up the builder testsuite following recent renamings
     5341838 Add a test for the new runBuilder stuff
     07c8bfc Fix the Prim.Extra module for the sake of the tests It's not currentl built as part of the lib.
     01d63d7 Export createUptoN and unsafeCreateUptoN afterall
     7c4ee8f Fixes for ghc-7.6+
     b4907e9 Drop support for ghc-6.10 and older in the .cabal file
     be3a97e Add all other-modules for the testsuites
     ac7cd50 Fix up the builder benchmarks for the recent builder renamings
     070f840 Bump the version to 0.10.1.0 We've added some builder stuff. While 0.10.0.0 was never properly released, it could be a little confusing. So might as well bump.
     3b87534 TAG 0.10.0.0
     2409162 Retrospective 0.10.0.1 release
     ebb5579 TAG 0.10.0.1
     c8a9cd6 Fix docs that use old showF/showB testing functions
     2b24d79 Add a show instance for Builder just for convenience
     d243ad5 Add compat modules for builder under previous names We were not able to get our name changes included in time, so we have to be compatible with the 0.10.0.0 release.
     b3426cc Fix module names of builder test
     49866c2 Bump version to 0.10.2.0 We're skipping the 0.10.1.0, that one can't be released as it is not compatible with what got released as 0.10.0.0
     86df1f1 Fix a few incorrect uses of inlinePerformIO The incorrect use of inlinePerformIO resulted in multiple calls to mallocByteString being shared, and hence two different strings sharing the same memory. See http://hackage.haskell.org/trac/ghc/ticket/7270
     d4d1983 Import unsafeDupablePerformIO
     42b2de6 Re-implement the foldr and foldl functions and fix unpack fusion They were just wrong. The old foldr and foldl were doing strict accumulation when they should be lazy.
     4a46cd1 Remove references to array fusion from the haddock docs We are not doing fusion and have not done so for ages and ages.
     90ba5e2 Retrospective 0.10.0.2 release
     8f35e60 Bump to current 0.10.3.x version
     8d80968 Relax directory version constraint for builder testsuite
     5adc3b9 TAG 0.10.0.2
     859729a Fix a couple warnings
     9c593a5 Ignore some more bits
     b20547a Point various URLs at github
     89bda08 Add an IsString instance for Builder
     4d24356 Add some ignore files for hg and git
     bf3ab9e Make tests build standalone
     794c345 Fix the rewrite rule that optimizes packing of string literals
     3a42bb1 Move D.B.Unsafe.unsafePackAddr to D.B.Internal
     efe48cd conditionally export D.B.Internal.unsafePackAddress
     176a2e6 Fix build on GHC 7.0
     bca8a9f Fix typos in docs of 'unsafePackAddress'
     36e7e21 Fix typos in docs of 'unsafePackAddressLen'
     8dd2efa Merge pull request #3 from meiersi/fix-typos-in-bytestring-internals
     6cdd5dd Declare "digits" static
     b53e34a Fix export of module Data.ByteString.Builder.ASCII
     2cafebf Implement (lazy) byteStringHexFixed
     c521a78 Add trustworthy pragmas to various safe builder modules and also make internal modules that expose ByteString constructors unsafe.
     b3bd784 Merge pull request #4 from scslab/trust
     9e2814f Add a new ShortByteString type
     3bb3b57 Add a builder primitive for ShortByteString
     341a4c1 Unbreak the testsuite
     5a86aa7 Add tests for the ShortByteString
     25708d3 Port performance patches from private bytestring branch
     4ac4be0 Use 'unsafeDupablePerformIO' instead of 'unsafePerformIO'.
     49ffb60 Remove unnecessary code for chunked and variable-length encoding.
     1a0ede3 Remove unneeded and/or commented-out code.
     0a4b8dd Update builder tests and setup 'hpc'.
     a8b7b02 Finish renaming 'Bounded/FixedEncoding ~> Bounded/FixedPrim'.
     53f91ca Make benchmarks compile and install again.
     5890510 Compare integer encoding and bytestring insertion performance to blaze-builder.
     92f19a5 Implement fast decimal integer encoding.
     4720784 Use 'integer-simple' flag analogous to the 'text' library.
     eaa31e0 Make Data.ByteString.Short work on several ghc versions
     bf73032 Fix warnings for different GHC versions, including 7.8
     4cc37e8 Remove dubious and unnecessary use of unsafeCoerce
     2fdf6fc A few minor documentation tweaks and improvements
     388303c Fix formatting typo in package description
     8279aca Fix documentation of memory overheads
     9c3ee74 Mention ShortByteString in the package description
     0e147dd Move the other benchmarks into the separate cabal file
     f2b3258 Declare all extensions in .hs files
     930a45b Bump version to 0.10.4.0
     16772aa Tidy up a few more uses of extensions
     033a686 Update tested-with list
     6ad8c0d Don't declare the Trustworthy & Unsafe extensions in the .cabal file
     f0bac1d Apparently the Unsafe extension is only in ghc 7.4+
     9ea13b7 Add Travis-CI script
     a14c7ce Merge pull request #7 from hvr/master
     80ff4a3 Rename and document inlinePerformIO to better reflect its behaviour
     35b38d1 Fixed logic on CONLIKE hack.
     8312989 Added Data.ByteString.Lazy.elemIndexEnd implementation
     6093aef QuickCheck update from yesterday breaks the build
     e2d2352 Make travis builds work again
     86ab496 Updated README
     737332b Whoops, the .cabal file referred to the README
     4c5855c Delete prologue.txt
     e97df17 Use S.foldl' on each chunk when strictly folding a lazy bytestring.
     38540d3 Update .travis.yml description
     6cf683d Add `FlexibleContexts` to fix compilation with GHC HEAD
     b916e3b Add GHC 7.8.3 to the Travis build-matrix
     f04e6f5 Constrain version of QuickCheck for compatibility
     37b3017 Allow tests to use multiple cores
     ca80162 Ignore cabal sandbox fun
     7f9acc4 Ignore Emacs files
     1d3b3fd Protect against Int overflow in concat
     f097086 Drop trailing whitespace
     2530b1c Rename sumP to checkedSum, and export it
     fbcc0af Fix Int overflow in Lazy.toStrict
     d61dffb Add regressions to test suite
     09edcd8 Remove trailing comma from build-depends
     a832f99 Add new test-framework deps to TravisCI job
     ec1d7c7 Enable ScopedTypeVariables for tests/Regressions
     3115296 Enable --show-details=always
     1cc7cfb Disable regression test and turn on test-framework
     a562ab2 Use --show-details=streaming when available
     da4c7e9 Don't mention ISO-8859-1 in doc string for hGetContents
     d4798e9 Fix typos: rename funtion to function
     f37493f Merge pull request #31 from spl/patch-1
     39de720 Merge pull request #21 from Lemmih/master
     8faa3ab Merge pull request #25 from thomie/T5861
     b060048 Fix haddock references to the ASCII module
     9f0ee6b Fix documented complexity of unsafePackMallocCStringLen
     5475757 Add a changelog
     87aa6ee Improve the author credits
     27d597b Bump to development version 0.10.5.0
     30e135c Add support for `deepseq-1.4.0.0`
     7a7602a Merge pull request #34 from hvr/pr-deepseq-14
     a399cdd Update Safe Haskell tags on some modules
     cf3af8f Merge pull request #36 from dterei/more-safe-haskell
     eb4514e Merge pull request #12 from DaveCTurner/master
     cf29654 Replace explicit uses of seq with bang patterns
     ee2b178 We should not have exported breakByte, add a deprecation message
     0bfef87 Add required CPP language pragmas
     c3457d7 Re-export isSuffixOf from D.B.L.Char8
     fd022fe Replace STRICT macros with bang patterns
     7670357 Add -fwarn-tabs
     1a8ed9f Remove various old commented-out implementations
     ba75c25 Remove old fusion related stuff
     8c3c7f3 Fix unfoldrN to call the predicate at most n times.
     77cf05c Fix readFile for files with incorrectly reported file sizes
     cb85a53 Update changelog
     fa7e1cc Bump version to 0.10.6.0
     8d512e1 hGet returns 'empty' not 'null' at EOF
     9b63d5f Eta expand continuation of empty
     c1960a9 Merge pull request #40 from bgamari/builder-opt
     08d5c3a Merge pull request #38 from DaveCTurner/patch-1


More information about the ghc-commits mailing list