[Haskell-cafe] IterIO: How to write use my inumReverse

Maciej Wos maciej.wos at gmail.com
Mon Jul 11 18:59:09 CEST 2011


Sorry, my previous message got truncated.

I was trying to say that many iteratees like iterReverse can be
defined nicely using combinators from Control.Applicative. You end up
with much cleaner code.

Also, iterLines doesn't work as the name would suggest. It only
consumes one line from the input stream and returns it inside a
singleton list.

Instead, iterLines can be defined like this:

iterLines :: (Monad m) => Iter L.ByteString m [L.ByteString]
iterLines = do
    el <- tryBI lineI
    case el of
        -- no more "full" lines left, return the remaining data
        Left (e :: SomeException) -> (:[]) <$> dataI
        -- read one line; add it to the list and read more
        Right line -> (line:) <$> iterLines

enumPure "line1\nline2\nline3" |$ iterLines
[Chunk "line1" Empty,Chunk "line2" Empty,Chunk "line3" Empty]

However, the above returns the resulting list only after consuming the
whole stream, which is something to avoid.

In case of iterReverse it is better to read and accumulate characters
until \n is found and then return the reversed string. One way to do
this is to read one character at a time:

reverseLineSlow :: Iter L.ByteString IO L.ByteString
reverseLineSlow = iter ""
    where
        iter acc = do
            c <- headI
            case c of
                10 -> return $ L.reverse acc
                _  -> iter (acc `mappend` L.singleton c)

But this will be really slow. Instead, the data should be read one
chunk at a time:

reverseLine :: Iter L.ByteString IO L.ByteString
reverseLine = iter ""
    where
        iter acc = do
            -- read the data from the stream one chunk at a time
            Chunk c eof <- chunkI
            -- check if there is any \n, i.e. if we read a whole line
            let (a,b) = L.break (==10) c
            if b == ""
                -- haven't found any \n yet; append all data to the accumulator
                then iter (acc `mappend` a)
                -- have found \n
                else do
                    -- put the data after \n back (while removing \n itself)
                    ungetI $ L.tail b
                    -- return reversed accumulator plus the data up to \n
                    return $ L.reverse $ acc `mappend` a

Hope this helps!

-- Maciej

On Tue, Jul 12, 2011 at 12:47 AM, Maciej Wos <maciej.wos at gmail.com> wrote:
> Don't forget Applicative instance!
> iterReverse = L.reverse <$> lineI
>
> On Monday, 4 July 2011 at 22:54, dm-list-haskell-cafe at scs.stanford.edu
> wrote:
>
> At Mon, 4 Jul 2011 20:36:33 +1000,
> John Ky wrote:
>
> Hi Haskell Cafe,
>
>       enum |$ inumLines .| inumReverse .| inumUnlines .| iter
> ...
>
> iterLines :: (Monad m) => Iter L.ByteString m [L.ByteString]
> iterLines = do
>   line <- lineI
>   return [[line]
>
> iterUnlines :: (Monad m) => Iter [L.ByteString] m L.ByteString
> iterUnlines = (L.concat . (++ [C.pack "\n"])) `liftM` dataI
>
> iterReverse :: (Monad m) => Iter [L.ByteString] m [L.ByteString]
> iterReverse = do
>   lines <- dataI
>   return (map L.reverse lines)
>
> inumLines = mkInum iterLines
> inumUnlines = mkInum iterUnlines
> inumReverse = mkInum iterReverse
>
> It all works fine.
>
> My question is: Is it possible to rewrite inumReverse to be this:
>
> iterReverse :: (Monad m) => Iter L.ByteString m L.ByteString
> iterReverse = do
>   line <- dataI
>   return (L.reverse line)
>
> inumReverse = mkInum iterReverse
>
> And still be able to use it in the line:
>
> enum |$ inumLines .| {-- inumReverse goes in here somehow --} .|
> inumUnlines .| iter
>
> The reason I ask is that the Haskell function reverse has the type [a] ->
> [a],
> not  [[a]] -> [[a]].
>
> I thought perhaps the alternative inumReverse is cleaner than the original
> as
> it behaves more similarly to Haskell's own reverse function.
>
> I'm not sure what you are trying to achieve. If you want an iter that
> works on L.ByteStrings, then you can say:
>
> iterReverse :: (Monad m) => Iter L.ByteString m L.ByteString
> iterReverse = do
> line <- lineI
> return (L.reverse line)
>
> In that case you don't need inumLines and inumUnlines. If, however,
> you want the type to be [L.ByteString], and you would rather do this
> one line at a time, instead of calling map, then you could do
> something like the following:
>
> iterReverse :: (Monad m) => Iter [L.ByteString] m [L.ByteString]
> iterReverse = do
> line <- headI
> return [L.reverse line]
>
> But the code you have above should also work, so it all depends on
> what you are trying to achieve.
>
> David
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



More information about the Haskell-Cafe mailing list