Re: Iteratee (take, takeR): identical types, different signatures

On Thu, Jan 14, 2010 at 12:39 PM, Valery V. Vorotyntsev
I've noticed inconsistency in type signatures of take* functions (Data.Iteratee.Base).
Compare take :: (SC.StreamChunk s el, Monad m) => Int -> EnumeratorN s el s el m a with takeR :: (SC.StreamChunk s el, Monad m) => Int -> IterateeG s el m a -> IterateeG s el m (IterateeG s el m a)
The latter type is equivalent to takeR :: (SC.StreamChunk s el, Monad m) => Int -> EnumeratorN s el s el m a since type EnumeratorN s_outer el_outer s_inner el_inner m a = IterateeG s_inner el_inner m a -> IterateeG s_outer el_outer m (IterateeG s_inner el_inner m a)
`take' and `takeR' functions are almost similar: the only difference is that `take' always consume all the stream while `takeR' can finish early.
Iteratee library should not obscure the fact that type signatures of these functions are identical. Please consider replacing IterateeG s el m (IterateeG s el m a) with EnumeratorN s el s el m a
Dear John, I've refactored `take' and `takeR'. The changes are: - Int argument removed from `step' sub-function - null, length and splitAt belong ListLike (LL), not StreamChunk (SC) - consistent naming used in both functions (s/chk/s/, s/stream/str/) -----BEGIN PATCH----- -----END PATCH----- Code compiles. Proposed change does not affect semantics, AFAICT. I tested behavior with the following code snippet: -----BEGIN TEST----- module XXX where import Data.Iteratee import qualified Data.Iteratee as It test :: IO () test = sequence_ [ putStr (desc ++ " " ++ show n ++ " " ++ show c ++ "\t") >> runIter (joinI $ f n $ It.break (== c)) stream >>= print | n <- [7, 100], c <- "3cX", (f, desc) <- [(It.take, "take "), (takeR, "takeR")] ] where stream = Chunk "0123456789abcdef" -----END TEST----- PS: BTW, what does `R' suffix stand for (in takeR function name)? -- Best regards, vvv

-----BEGIN PATCH-----
-----END PATCH-----
Gmail's web UI does strange things to inlined text attachments... Don't worry, the patch is still there. Just scroll to the bottom of the previous email. Thanks. -- vvv
participants (2)
-
Valery V. Vorotyntsev
-
vvv@mts.com.ua