Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- setParseStream :: IO (StreamData ByteString) -> TransIO ()
- setParseString :: ByteString -> TransIO ()
- withParseString :: ByteString -> TransIO a -> TransIO a
- data ParseContext str = IsString str => ParseContext (IO (StreamData str)) str
- string :: ByteString -> TransIO ByteString
- tDropUntilToken :: ByteString -> TransIO ()
- tTakeUntilToken :: ByteString -> TransIO ByteString
- integer :: TransIO Integer
- int :: TransIO Int
- manyTill :: TransIO a -> TransIO b -> TransIO [a]
- chainManyTill :: (Alternative f, Monad f, Monoid a1) => (t -> a1 -> a1) -> f t -> f a2 -> f a1
- between :: Monad m => m a1 -> m a2 -> m b -> m b
- symbol :: ByteString -> TransIO ByteString
- parens :: TransIO b -> TransIO b
- braces :: TransIO b -> TransIO b
- angles :: TransIO b -> TransIO b
- brackets :: TransIO b -> TransIO b
- semi :: TransIO ByteString
- comma :: TransIO ByteString
- dot :: TransIO ByteString
- colon :: TransIO ByteString
- sepBy :: TransIO a -> TransIO x -> TransIO [a]
- sepBy1 :: TransIO a -> TransIO x -> TransIO [a]
- chainSepBy :: (Alternative f, Monad f, Monoid a1) => (a2 -> a1 -> a1) -> f a2 -> f x -> f a1
- chainSepBy1 :: (Monad m, Monoid b, Alternative m) => (a -> b -> b) -> m a -> m x -> m b
- chainMany :: (Alternative f, Monad f, Monoid a1) => (a2 -> a1 -> a1) -> f a2 -> f a1
- commaSep :: TransIO a -> TransIO [a]
- semiSep :: TransIO a -> TransIO [a]
- commaSep1 :: TransIO a -> TransIO [a]
- semiSep1 :: TransIO a -> TransIO [a]
- dropSpaces :: TransIO ()
- dropTillEndOfLine :: TransIO ()
- parseString :: TransIO ByteString
- tTakeWhile :: (Char -> Bool) -> TransIO ByteString
- tTakeWhile' :: (Char -> Bool) -> TransIO ByteString
- just1 :: (p -> (a, b)) -> p -> (Maybe a, b)
- tTake :: Int64 -> TransIO ByteString
- tDrop :: Int64 -> TransIO ()
- anyChar :: TransIO Char
- tChar :: Char -> TransIO Char
- withData :: (ByteString -> TransIO (a, ByteString)) -> TransIO a
- giveData :: TransIO ByteString
- isDone :: TransIO Bool
- (|-) :: TransIO (StreamData ByteString) -> TransIO b -> TransIO b
Documentation
setParseStream :: IO (StreamData ByteString) -> TransIO () Source #
set a stream of strings to be parsed
setParseString :: ByteString -> TransIO () Source #
set a string to be parsed
withParseString :: ByteString -> TransIO a -> TransIO a Source #
data ParseContext str Source #
The parse context contains either the string to be parsed or a computation that gives an stream of strings or both. First, the string is parsed. If it is empty, the stream is pulled for more.
IsString str => ParseContext (IO (StreamData str)) str |
string :: ByteString -> TransIO ByteString Source #
succeed if read the string given as parameter
tDropUntilToken :: ByteString -> TransIO () Source #
fast search for a token
manyTill :: TransIO a -> TransIO b -> TransIO [a] Source #
read many results with a parser (at least one) until a end
parser succeed.
chainManyTill :: (Alternative f, Monad f, Monoid a1) => (t -> a1 -> a1) -> f t -> f a2 -> f a1 Source #
symbol :: ByteString -> TransIO ByteString Source #
semi :: TransIO ByteString Source #
dot :: TransIO ByteString Source #
chainSepBy :: (Alternative f, Monad f, Monoid a1) => (a2 -> a1 -> a1) -> f a2 -> f x -> f a1 Source #
chainSepBy1 :: (Monad m, Monoid b, Alternative m) => (a -> b -> b) -> m a -> m x -> m b Source #
dropSpaces :: TransIO () Source #
dropTillEndOfLine :: TransIO () Source #
tTakeWhile :: (Char -> Bool) -> TransIO ByteString Source #
take characters while they meet the condition
tTakeWhile' :: (Char -> Bool) -> TransIO ByteString Source #
take characters while they meet the condition and drop the next character
withData :: (ByteString -> TransIO (a, ByteString)) -> TransIO a Source #
bring the lazy byteString state to a parser and actualize the byteString state with the result The tuple that the parser should return should be : (what it returns, what should remain to be parsed)
giveData :: TransIO ByteString Source #
bring the data of the parse context as a lazy byteString
(|-) :: TransIO (StreamData ByteString) -> TransIO b -> TransIO b Source #
Chain two parsers. The motivation is to parse a chunked HTTP response which contains JSON messages.
If the REST response is infinite and contains JSON messages, I have to chain the
dechunk parser with the JSON decoder of aeson, to produce a stream of aeson messages.
Since the boundaries of chunks and JSON messages do not match, it is not possible to add a
decode
to the monadic pipeline. Since the stream is potentially infinite and/or the
messages may arrive at any time, I can not wait until all the input finish before decoding
the messages.
I need to generate a ByteString stream with the first parser, which is the input for the second parser.
The first parser wait until the second consume the previous chunk, so it is pull-based.
many parsing stages can be chained with this operator.
The output is nondeterministic: it can return 0, 1 or more results
example: https://t.co/fmx1uE2SUd