Skip to content

Conversation

danidiaz
Copy link
Contributor

Hi,

There doesn't seem to be an analogue of mapAccumL in "streaming", at least I didn't find it. This pull request is a possible implementation (adapted from the implementation of Streaming.Prelude.scan).

My motivation for having this function is to decode ByteString streams into Text streams with the help of Data.Text.Encoding.streamDecodeUtf8:

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Streaming
import qualified Streaming.Prelude as S
import Data.Text (Text)
import Data.Text.Encoding (streamDecodeUtf8,Decoding(Some))
import qualified Data.Text as T
import qualified Data.ByteString as B

main :: IO ()
main = 
    do let step f bytes = case f bytes of
               Some text _ nextf -> nextf :> text 
       f :> () <- S.print $ S.mapAccum step streamDecodeUtf8 $ S.yield "foo \xe2"
       let Some _ leftovers _ = f mempty
       print $ if B.null leftovers
                then "no leftovers!"
                else "oops, leftovers"

Instead of using the proposed mapAccum, we can decode using the already existing Streaming.Prelude.scan:

utf8scan :: Monad m => Stream (Of B.ByteString) m r -> Stream (Of T.Text) m r
utf8scan = S.scan step (streamDecodeUtf8 mempty) (\(Some txt _ _) -> txt) 
    where
    step (Some _ _ f) bytes = f bytes

However, the problem with using scan is that it doesn't let us check the ByteString leftovers once the stream is exhausted, in order to see if there's some undecoded input remaining.

Another (minor) annoyance is that scan always yields its initial state, which in the example will be an empty Text. Yielding something before processing any input is weird for a decoding function.

@danidiaz danidiaz changed the title Added "mapAccum". Add "mapAccum". Jun 11, 2020
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Labels

None yet

Projects

None yet

Development

Successfully merging this pull request may close these issues.

1 participant