| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Attoparsec.ByteString.Streaming
Description
Here is a simple use of parsed and standard Streaming segmentation devices
to parse a file in which groups of numbers are separated by blank lines. Such a
problem of 'nesting streams' is described in the conduit context in
this StackOverflow question.
-- $ cat nums.txt -- 1 -- 2 -- 3 -- -- 4 -- 5 -- 6 -- -- 7 -- 8
We will sum the groups and stream the results to standard output:
import Streaming
import qualified Streaming.Prelude as S
import qualified Data.ByteString.Streaming.Char8 as Q
import qualified Data.Attoparsec.ByteString.Char8 as A
import qualified Data.Attoparsec.ByteString.Streaming as AS
import Data.Function ((&))
main :: IO ()
main = Q.getContents -- raw bytes
& AS.parsed lineParser -- stream of parsed `Maybe Int`s; blank lines are `Nothing`
& void -- drop any unparsed nonsense at the end
& S.split Nothing -- split on blank lines
& S.maps S.concat -- keep `Just x` values in the sub-streams (cp. catMaybes)
& S.mapped S.sum -- sum each substream
& S.print -- stream results to stdout
lineParser = Just <$> A.scientific <* A.endOfLine <|> Nothing <$ A.endOfLine-- $ cat nums.txt | ./atto -- 6.0 -- 15.0 -- 15.0
Synopsis
- type Errors = ([String], String)
- parse :: Monad m => Parser a -> ByteString m x -> m (Either Errors a, ByteString m x)
- parsed :: Monad m => Parser a -> ByteString m r -> Stream (Of a) m (Either (Errors, ByteString m r) r)
Documentation
parse :: Monad m => Parser a -> ByteString m x -> m (Either Errors a, ByteString m x) Source #
The result of a parse (Either ([String], String) a), with the unconsumed byte stream.
>>>:set -XOverloadedStrings -- the string literal below is a streaming bytestring>>>(r,rest1) <- AS.parse (A.scientific <* A.many' A.space) "12.3 4.56 78.3">>>print rRight 12.3>>>(s,rest2) <- AS.parse (A.scientific <* A.many' A.space) rest1>>>print sRight 4.56>>>(t,rest3) <- AS.parse (A.scientific <* A.many' A.space) rest2>>>print tRight 78.3>>>Q.putStrLn rest3-- Nothing left, this prints an empty string.
Arguments
| :: Monad m | |
| => Parser a | Attoparsec parser |
| -> ByteString m r | Raw input |
| -> Stream (Of a) m (Either (Errors, ByteString m r) r) |
Apply a parser repeatedly to a stream of bytes, streaming the parsed values, but ending when the parser fails or the bytes run out.
>>>S.print . void $ AS.parsed (A.scientific <* A.many' A.space) "12.3 4.56 78.9"12.3 4.56 78.9