Iteratee (take, takeR): identical types, different signatures
Valery V. Vorotyntsev
vvv at mts.com.ua
Thu Jan 14 08:59:14 EST 2010
On Thu, Jan 14, 2010 at 12:39 PM, Valery V. Vorotyntsev <valery.vv at gmail.com> wrote:
> 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-----
-------------- next part --------------
A non-text attachment was scrubbed...
Name: iteratee-0.3.1_take-refactoring.patch
Type: text/x-diff
Size: 2732 bytes
Desc: iteratee-0.3.1_take-refactoring.patch
Url : http://www.haskell.org/pipermail/libraries/attachments/20100114/2628b0f1/iteratee-0.3.1_take-refactoring.bin
-------------- next part --------------
-----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
More information about the Libraries
mailing list