Re: Haskell-Cafe Digest, Vol 78, Issue 14

Edward's reply was quite good. I'll just try to fill in a few items he didn't address.
From: Maciej Piechotka
I read a lot about iteratee IO and it seemed very interesting (Unfortunately it lacks tutorial). Especially features like 'no input yet' in network programming (with lazy IO + parsec I run into problems as it tried to evaluate the first response character before sending output).
I decided first write a simple program and then attempt write a Stream implementation for parsec.
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} import Data.Iteratee import Text.Parse
data Buffer a = Buffer instance Monad m => Stream (Buffer a) (IterateeG [] a m) a where uncons Buffer = IterateeG loop where loop (Chunk []) = return $! Cont (IterateeG loop) Nothing loop (Chunk (x:xs)) = return $! Done (Just (x, Buffer)) (Chunk xs) loop (EOF Nothing) = return $! Done Nothing (EOF Nothing) loop (EOF (Just e)) = return $! throwErr e
2. Is there any package which contains this stream definition?
I believe this Stream instance is incorrect. According to the parsec-3.0.1 docs, "A Stream instance is responsible for maintaining the 'position within the stream' in the stream state s. This is trivial unless you are using the monad in a non-trivial way." This is necessary for referential integrity. That is, "uncons s" needs to always evaluate to the same result for the same 's'. Your Stream instance doesn't preserve this. As an example,
testIter = let b = Buffer in uncons b >> uncons b
should be an iteratee that returns a "Maybe (t, buffer)" where t is the first element in the enumeration, but with your instance it will return the second. See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
3. Why Seek FileOffset is error message?
Version 3 of iteratee is somewhat experimental, one of the ideas on trial is that of resumable exceptions. This framework is perfectly suited to handle control messages as well, which is why Seek is included as an error message. I don't want to make a major release just to fix this, but both error handling and control messages will undergo a substantial cleanup in the next major version. Included in this will be a proper separation between control messages and true exceptions, most likely based upon the extensible-exceptions framework. Cheers, John

On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything? I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish. Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s After I broke the running as it was taking too long. Is my implementation correct (when I try to write less trivial benchmark I probably find out but I hope for comment on the idea). Regards

Maciej Piechotka
On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream. Attoparsec provides an *incremental* parser. You feed it bite-sized chunks of an input stream, and it either says "ok, I'm done, here's your value, and the rest of the stream I didn't use" or "I couldn't finish, here's a parser continuation you can feed more chunks to." This, of course, is a perfect conceptual match for iteratees -- with a little bit of plumbing you should be able to parse a stream in O(1) space.
I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish.
Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s
Which column corresponds to which module here, and which module are you
benchmarking against, John's or mine?
G
--
Gregory Collins

On Thu, 2010-02-11 at 11:00 -0500, Gregory Collins wrote:
Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
Well. Not quite. AFAIU (and ByteString implementation indicate so) the uncons have a type uncons :: s -> m (Maybe (t, s)) Where s indicates the position on the stream. Since it is impossible to get back from having s alone the GC should be free to finalize all memory allocated to cache the stream before the first living s. I.e. if input is: text = 'L':'o':'r':'e':'m':' ':'i':'p':'s':'u':'m':[] ^ ^ s1 s2 and s1 and s2 are position in the stream (for stream that is list) GC can free Lor part. It seems that it might be significant in real live as try calls are relatively short comparing with rest of code. By keeping s as 'pointer to' element second uncons have O(1) time instead of O(n).
I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish.
Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s
Which column corresponds to which module here, and which module are you benchmarking against, John's or mine?
G
As I'm implementing for parsec (I don't know attoparsec) [as a kind of exercise to get iteratee better] I benchmarked against John's. My results are on the left. I forgot to compile and optimize. Here's result for ByteString: Mine John's 10: 0.000425s 0.000215s 100: 0.000616s 0.001963s 1000: 0.0041s 0.048359s 10000: 0.041694s 4.492774s 100000: 0.309289s 434.238449s And []: Mine John's 10: 0.000605s 0.000932s 100: 0.001464s 0.008101s 1000: 0.004036s 0.054125s 10000: 0.032341s 1.36938s 100000: 0.317859s 115.846891s Regards and sorry for confusion PS. Sorry - I know that test is somehow simplistic but I thing it emulates real live situation where you are interested in small amount of elements around current position (short try). I also think that /dev/zero have relatively predictable access time (it does not need to be loaded from slow disk first after which it can be accessed from cache, it does not run out of entropy etc.).

On Thu, Feb 11, 2010 at 1:27 PM, Maciej Piechotka
On Thu, 2010-02-11 at 11:00 -0500, Gregory Collins wrote:
Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
Well. Not quite. AFAIU (and ByteString implementation indicate so) the uncons have a type uncons :: s -> m (Maybe (t, s))
Where s indicates the position on the stream. Since it is impossible to get back from having s alone the GC should be free to finalize all memory allocated to cache the stream before the first living s.
I'm not sure that this is correct - parsec believes that it is free to call 'uncons' multiple times on the same value and receive an equivalent answer. Maybe I'm misunderstanding what we're talking about, but a simple test is: backtrackTest = (try (string "aardvark")) <|> (string "aaple") And then attempt to parse the stream equivalent to "aaple" with 'backtrackTest'. This should be a successful parse (untested). Antoine

On Thu, 2010-02-11 at 13:34 -0600, Antoine Latter wrote:
On Thu, 2010-02-11 at 11:00 -0500, Gregory Collins wrote:
Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a
valid
Stream instance using iteratee. Also Gregory Collins recently
an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
Well. Not quite. AFAIU (and ByteString implementation indicate so)
On Thu, Feb 11, 2010 at 1:27 PM, Maciej Piechotka
wrote: posted the uncons have a type uncons :: s -> m (Maybe (t, s))
Where s indicates the position on the stream. Since it is impossible to get back from having s alone the GC should be free to finalize all memory allocated to cache the stream before the first living s.
I'm not sure that this is correct - parsec believes that it is free to call 'uncons' multiple times on the same value and receive an equivalent answer.
That's what I meant. But it have to keep the reference to the first element. Consider example with list: text = 'L':'o':'r':'e':'m':' ':'i':'p':'s':'u':'m':[] ^ ^ ^ s1 s2 s3 uncons s1 == Identity (Just ('e', 'm':' ':'i':'p':'s':'u':'m':[])) uncons s2 == Identity (Just ('p', 's':'u':'m':[])) uncons s3 == Identity Nothing However we will never get (nor we keep reference to): 'L':'o':'r':'e':'m':' ':'i':'p':'s':'u':'m':[], 'o':'r':'e':'m':' ':'i':'p':'s':'u':'m':[] 'r':'e':'m':' ':'i':'p':'s':'u':'m':[] so those values can be freed as they are before first pointer (namely s1). Regards

On Thu, Feb 11, 2010 at 10:00 AM, Gregory Collins
Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
This is true, however I believe this alternative approach is also correct. The Cursor holds the stream state, and parsec holds on to the Cursor for backtracking. Data is only read within the Iteratee monad when it goes beyond the currently available cursors, at which point another cursor is added to the linked list (implemented with IORef or other mutable reference). The downside to this approach is that data is consumed from the iteratee stream for a partial parse, even if the parse fails. I did not want this behavior, so I chose a different approach.
I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish.
Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s
I'm surprised your version has better performance for small numbers of elements. I wonder if it's partially due to more aggressive inlining from GHC or something of that nature. Or maybe your version compiles to a tighter loop as elements can be gc'd. I expected poor performance of my code for larger numbers of elements, as demonstrated here. I envisioned the usage scenario where parsers would be relatively short (<20 chars), and most of the work would be done directly with iteratees. In this case it would be more important to preserve the stream state in the case of a failed parse, and the performance issues of appending chunks wouldn't arise either. Cheers, John

On Thu, 2010-02-11 at 17:49 -0600, John Lato wrote:
On Thu, Feb 11, 2010 at 10:00 AM, Gregory Collins
wrote: Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
This is true, however I believe this alternative approach is also correct. The Cursor holds the stream state, and parsec holds on to the Cursor for backtracking. Data is only read within the Iteratee monad when it goes beyond the currently available cursors, at which point another cursor is added to the linked list (implemented with IORef or other mutable reference).
The downside to this approach is that data is consumed from the iteratee stream for a partial parse, even if the parse fails. I did not want this behavior, so I chose a different approach.
Hmm. AFAIU your code you are doing something like:
concatCursor :: (Monad m, Reference r m, StreamChunk c el) => Cursor r m c el -> m (c el) concatCursor c = liftM mconcat (concatCursor' c)
concatCursor' :: (Monad m, Reference r m, StreamChunk c el) => Cursor r m c el -> m [c el] concatCursor' (Cursor r v) = liftM2 (:) (return v) (readRef r >>= concatNextCursor')
concatNextCursor' :: (Monad m, Reference r m, StreamChunk c el) => NextCursor r m c el -> m [c el] concatNextCursor' (NextCursor c) = concatCursor' $! c concatNextCursor' _ = return $! []
parsecIteratee' :: (Monad m, Reference r m, StreamChunk c el) => ParsecT (Cursor r m c el) u (IterateeG c el m) a -> u -> SourceName -> IterateeG c el m (Either ParseError a) parsecIteratee' p u sn = do c <- lift $ mkCursor :: IterateeG c el m (Cursor r m c el) res <- runParserT (liftM2 (,) p getInput) u sn c case res of Right (a, c) -> do sc <- lift $ concatCursor c liftI $! Done (Right a) $! Chunk $! sc Left err -> return $ Left err
Which seems that it should work (I just checked if it is suppose to compile). Unfortunately I need to work the clash between transformers and mtl). EDIT. Ops. sorry. It will not work. However it will (as it should) return the remaining part back to stream.
I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish.
Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s
I'm surprised your version has better performance for small numbers of elements. I wonder if it's partially due to more aggressive inlining from GHC or something of that nature. Or maybe your version compiles to a tighter loop as elements can be gc'd.
It is possible as my code was in the same module. I'll try to use 2 different modules.
I expected poor performance of my code for larger numbers of elements, as demonstrated here.
I haven't tested for more then 1e5 (which was in comment).
I envisioned the usage scenario where parsers would be relatively short (<20 chars), and most of the work would be done directly with iteratees. In this case it would be more important to preserve the stream state in the case of a failed parse, and the performance issues of appending chunks wouldn't arise either.
Fortunately parsec does not limit the number of streams per monad so it is up to user which one he will choose (depending on problem).
Cheers, John
Regards PS. Why iteratee uses transformers? It seems to be identical (both have functional dependencies etc.) to mtl except that mtl is standard in platform. Using both lead to clashes between names.

On Fri, Feb 12, 2010 at 10:32 AM, Maciej Piechotka
On Thu, 2010-02-11 at 17:49 -0600, John Lato wrote:
On Thu, Feb 11, 2010 at 10:00 AM, Gregory Collins
wrote: Maciej Piechotka
writes: On Tue, 2010-02-09 at 16:41 +0000, John Lato wrote:
See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid Stream instance using iteratee. Also Gregory Collins recently posted an iteratee wrapper for Attoparsec to haskell-cafe. To my knowledge these are not yet in any packages, but hackage is vast.
Hmm. Am I correct that his implementation caches everything?
The one that John posted (iteratees on top of parsec) has to keep a copy of the entire input, because parsec wants to be able to do arbitrary backtracking on the stream.
This is true, however I believe this alternative approach is also correct. The Cursor holds the stream state, and parsec holds on to the Cursor for backtracking. Data is only read within the Iteratee monad when it goes beyond the currently available cursors, at which point another cursor is added to the linked list (implemented with IORef or other mutable reference).
The downside to this approach is that data is consumed from the iteratee stream for a partial parse, even if the parse fails. I did not want this behavior, so I chose a different approach.
Hmm. AFAIU your code you are doing something like:
concatCursor :: (Monad m, Reference r m, StreamChunk c el) => Cursor r m c el -> m (c el) concatCursor c = liftM mconcat (concatCursor' c)
concatCursor' :: (Monad m, Reference r m, StreamChunk c el) => Cursor r m c el -> m [c el] concatCursor' (Cursor r v) = liftM2 (:) (return v) (readRef r >>= concatNextCursor')
concatNextCursor' :: (Monad m, Reference r m, StreamChunk c el) => NextCursor r m c el -> m [c el] concatNextCursor' (NextCursor c) = concatCursor' $! c concatNextCursor' _ = return $! []
parsecIteratee' :: (Monad m, Reference r m, StreamChunk c el) => ParsecT (Cursor r m c el) u (IterateeG c el m) a -> u -> SourceName -> IterateeG c el m (Either ParseError a) parsecIteratee' p u sn = do c <- lift $ mkCursor :: IterateeG c el m (Cursor r m c el) res <- runParserT (liftM2 (,) p getInput) u sn c case res of Right (a, c) -> do sc <- lift $ concatCursor c liftI $! Done (Right a) $! Chunk $! sc Left err -> return $ Left err
Which seems that it should work (I just checked if it is suppose to compile). Unfortunately I need to work the clash between transformers and mtl).
EDIT. Ops. sorry. It will not work. However it will (as it should) return the remaining part back to stream.
Yes, the remaining part will be returned, but the consumed portion is lost. I couldn't figure out how to solve that problem other than cacheing everything.
I tried to rewrite the implementation using... well imperative linked list. For trivial benchmark it have large improvement (althought it may be due to error in test such as using ByteString) and, I believe, that it allows to free memory before finish.
Results of test on Core 2 Duo 2.8 GHz: 10: 0.000455s 0.000181s 100: 0.000669s 0.001104s 1000: 0.005209s 0.023704s 10000: 0.053292s 1.423443s 100000: 0.508093s 132.208597s
I expected poor performance of my code for larger numbers of elements, as demonstrated here.
I haven't tested for more then 1e5 (which was in comment).
Interesting. I expect good performance as long as chunks don't need to be concatenated. The default chunk size is either 4096 or 8192 (I don't remember ATM). This also assumes that no intervening functions (take, drop, etc.) alter the stream too significantly. Testing 1e5 wouldn't do more than two concats, and particularly with bytestrings shouldn't impose too much penalty. List performance would be much worse though. Incidentally, performance of the WrappedByteString newtype is poor relative to true bytestrings. This will be fixed in the next major release (due in maybe a month or so?)
I envisioned the usage scenario where parsers would be relatively short (<20 chars), and most of the work would be done directly with iteratees. In this case it would be more important to preserve the stream state in the case of a failed parse, and the performance issues of appending chunks wouldn't arise either.
Fortunately parsec does not limit the number of streams per monad so it is up to user which one he will choose (depending on problem).
Good point.
Regards PS. Why iteratee uses transformers? It seems to be identical (both have functional dependencies etc.) to mtl except that mtl is standard in platform. Using both lead to clashes between names.
Short answer: I am using iteratee with another package that uses transformers. Longer answer: see discussions on mtl vs. transformers in the haskell-libraries archive. There are a few simple solutions. You can build iteratee against mtl by changing the build-depends: field in iteratee.cabal. You can also use the LANGUAGE PackageImports pragma. I'm unaware of any difficulties with either of these approaches. Cheers, John

On Fri, 2010-02-12 at 12:51 +0000, John Lato wrote:
Yes, the remaining part will be returned, but the consumed portion is lost. I couldn't figure out how to solve that problem other than cacheing everything.
I decided to post the new code on webpage (http://www.doc.ic.ac.uk/~mmp08/iteratee/) to not spam everyone's inbox. I think you want something more like safeParsecIteratee from my code. From the same CPU more random numbers (I wonder how they'll look like in a month when BS problems will be resolved). For ByteString: Maciej's Maciej's Safe John's Short parser 5: 0.000144s 0.000040s 0.000067s 10: 0.000052s 0.000042s 0.000048s 15: 0.000053s 0.000052s 0.000061s 20: 0.000041s 0.000033s 0.000039s 50: 0.000054s 0.000049s 0.000111s 100: 0.000082s 0.000101s 0.000254s 1000: 0.000610s 0.000623s 0.014414s 10000: 0.007069s 0.007947s 1.197706s 100000: 0.058025s 0.057382s 117.231680s Short failing parser 5: 0.000104s 0.000030s 0.000026s 10: 0.000028s 0.000024s 0.000023s 15: 0.000026s 0.000025s 0.000031s 20: 0.000027s 0.000028s 0.000025s 50: 0.000027s 0.000025s 0.000042s 100: 0.000026s 0.000024s 0.000023s 1000: 0.000024s 0.000023s 0.000023s 10000: 0.000259s 0.000025s 0.000022s 100000: 0.000025s 0.000039s 0.000024s Failing parser 5: 0.000025s 0.000024s 0.000022s 10: 0.000027s 0.000024s 0.000026s 15: 0.000028s 0.000028s 0.000031s 20: 0.000032s 0.000045s 0.000038s 50: 0.000045s 0.000045s 0.000096s 100: 0.000069s 0.000144s 0.000228s 1000: 0.000544s 0.000512s 0.013124s 10000: 0.004760s 0.004695s 1.240703s 100000: 0.046858s 0.046897s 119.860964s For []: Maciej's Maciej's Safe John's Short parser 5: 0.000215s 0.000141s 0.000541s 10: 0.000054s 0.000286s 0.000178s 15: 0.000046s 0.000078s 0.000248s 20: 0.000130s 0.000050s 0.000420s 50: 0.000066s 0.000200s 0.000785s 100: 0.000176s 0.000240s 0.001522s 1000: 0.000826s 0.000857s 0.014399s 10000: 0.006674s 0.007185s 0.381615s 100000: 0.062452s 0.065178s 31.454621s Short failing parser 5: 0.000210s 0.000054s 0.000099s 10: 0.000096s 0.000037s 0.000104s 15: 0.000059s 0.000039s 0.000184s 20: 0.000038s 0.000036s 0.000114s 50: 0.000037s 0.000100s 0.000111s 100: 0.000165s 0.000037s 0.000103s 1000: 0.000079s 0.000036s 0.000103s 10000: 0.000037s 0.000037s 0.000179s 100000: 0.000037s 0.000168s 0.000104s Failing parser 5: 0.000037s 0.000090s 0.000089s 10: 0.000157s 0.000055s 0.000169s 15: 0.000062s 0.000039s 0.000303s 20: 0.000043s 0.000194s 0.000311s 50: 0.000183s 0.000056s 0.000780s 100: 0.000080s 0.000172s 0.001624s 1000: 0.000714s 0.000714s 0.014076s 10000: 0.005451s 0.006890s 0.379960s 100000: 0.052609s 0.055770s 31.537776s The timings where about the same in every run. Also it seems that keeping reference to input does not create significant slow-down if it is not an artefact of testing method. Short failing parser probably have somewhere an error.
Interesting. I expect good performance as long as chunks don't need to be concatenated. The default chunk size is either 4096 or 8192 (I don't remember ATM). This also assumes that no intervening functions (take, drop, etc.) alter the stream too significantly. Testing 1e5 wouldn't do more than two concats, and particularly with bytestrings shouldn't impose too much penalty. List performance would be much worse though.
With 1e5 it should have 1e5/(4e3 or 8e3) \approx 10-20 concats.
Regards PS. Why iteratee uses transformers? It seems to be identical (both have functional dependencies etc.) to mtl except that mtl is standard in platform. Using both lead to clashes between names.
Short answer: I am using iteratee with another package that uses transformers. Longer answer: see discussions on mtl vs. transformers in the haskell-libraries archive.
I'll read them. I will ask one more question regarding iteratee. Why StreamChunk have 10 methods which already are in ListLike? Regards
participants (4)
-
Antoine Latter
-
Gregory Collins
-
John Lato
-
Maciej Piechotka