Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides support for parsing values from ByteString
InputStream
s using attoparsec
. Since: 1.4.0.0.
Synopsis
- parseFromStream :: Parser r -> InputStream ByteString -> IO r
- parserToInputStream :: Parser (Maybe r) -> InputStream ByteString -> IO (InputStream r)
- data ParseException = ParseException String
Parsing
parseFromStream :: Parser r -> InputStream ByteString -> IO r Source #
Supplies an attoparsec
Parser
with an InputStream
, returning the
final parsed value or throwing a ParseException
if parsing fails.
parseFromStream
consumes only as much input as necessary to satisfy the
Parser
: any unconsumed input is pushed back onto the InputStream
.
If the Parser
exhausts the InputStream
, the end-of-stream signal is sent
to attoparsec.
Example:
ghci> import Data.Attoparsec.ByteString.Char8 ghci> is <-fromList
["12345xxx" ::ByteString
] ghci>parseFromStream
(takeWhile
isDigit
) is "12345" ghci>read
is Just "xxx"
parserToInputStream :: Parser (Maybe r) -> InputStream ByteString -> IO (InputStream r) Source #
Given a Parser
yielding values of type
, transforms an
Maybe
rInputStream
over byte strings to an InputStream
yielding values of type
r
.
If the parser yields Just x
, then x
will be passed along downstream, and
if the parser yields Nothing
, that will be interpreted as end-of-stream.
Upon a parse error, parserToInputStream
will throw a ParseException
.
Example:
ghci> import Control.Applicative ghci> import Data.Attoparsec.ByteString.Char8 ghci> is <-fromList
["1 2 3 4 5" ::ByteString
] ghci> let parser = (endOfInput
>>pure
Nothing
) <|> (Just <$> (skipWhile
isSpace
*>decimal
)) ghci>parserToInputStream
parser is >>=toList
[1,2,3,4,5] ghci> is' <-fromList
["1 2xx3 4 5" ::ByteString
] >>=parserToInputStream
parser ghci>read
is' Just 1 ghci>read
is' Just 2 ghci>read
is' *** Exception: Parse exception: Failed reading: takeWhile1
data ParseException Source #
An exception raised when parsing fails.
Instances
Show ParseException Source # | |
Defined in System.IO.Streams.Internal.Attoparsec showsPrec :: Int -> ParseException -> ShowS # show :: ParseException -> String # showList :: [ParseException] -> ShowS # | |
Exception ParseException Source # | |
Defined in System.IO.Streams.Internal.Attoparsec |