transient-0.7.0.0: composing programs with multithreading, events and distributed computing

Safe HaskellNone
LanguageHaskell2010

Transient.Parse

Contents

Synopsis

Setting the stream

setParseStream :: TransMonad m => TransIO (StreamData ByteString) -> m () Source #

set a stream of strings to be parsed

setParseString :: TransMonad m => ByteString -> m () Source #

set a string to be parsed

parsing

string :: ByteString -> TransIO ByteString 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. data ParseContext str = IsString str => ParseContext (IO (StreamData str)) str deriving Typeable

succeed if read the string given as parameter

tDropUntilToken :: ByteString -> TransIO () Source #

fast search for a token. If the token is not found, the parse is left in the original state.

integer :: TransIO Integer Source #

read an Integer

hex :: TransIO Int Source #

parse an hexadecimal number

int :: TransIO Int Source #

read an Int

double :: TransIO Double Source #

read a double in floating point/scientific notation

tChar :: Char -> TransIO Char Source #

verify that the next character is the one expected

anyChar :: TransIO Char Source #

read a char. If there is no input left it fails with empty

manyTill :: TransIO a -> TransIO b -> TransIO [a] Source #

read many results with a parser (at least one) until a end parser succeed.

chainManyTill :: Monoid t1 => (t2 -> t1 -> t1) -> TransIO t2 -> TransIO a -> TransIO t1 Source #

between :: Monad m => m a1 -> m a2 -> m b -> m b Source #

sepBy :: TransIO a -> TransIO x -> TransIO [a] 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 #

chainMany :: (Alternative f, Monad f, Monoid a1) => (a2 -> a1 -> a1) -> f a2 -> f a1 Source #

tTakeWhile :: (Char -> Bool) -> TransIO ByteString Source #

take characters while they meet the condition. if no char matches, it returns empty

tTakeUntil :: (ByteString -> Bool) -> TransIO ByteString Source #

take from the stream until a condition is met

tTakeWhile' :: (Char -> Bool) -> TransIO ByteString Source #

take characters while they meet the condition and drop the next character

tTake :: Int64 -> TransIO ByteString Source #

take n characters

tDrop :: Int64 -> TransIO () Source #

drop n characters

tDropUntil :: (ByteString -> Bool) -> TransIO () Source #

drop from the stream until a condition is met

tPutStr :: ByteString -> TransIO () Source #

add the String at the beginning of the stream to be parsed

isDone :: TransIO Bool Source #

True if the stream has finished

giving the parse string

withGetParseString :: (ByteString -> TransIO (a, ByteString)) -> TransIO a Source #

bring the lazy byteString state to a parser which return the rest of the stream together with the result and actualize the byteString state with it The tuple that the parser returns should be : (what it returns, what should remain to be parsed)

giveParseString :: TransIO ByteString Source #

bring the data of the parse context as a lazy byteString

debug

notParsed :: TransIO ByteString Source #

return the portion of the string not parsed it is useful for testing purposes:

 result <- myParser  <|>  (do rest <- notParsed ; liftIO (print "not parsed this:"++ rest))

would print where myParser stopped working. This does not work with (infinite) streams. Use getParseBuffer instead

getParseBuffer :: TransIO ByteString Source #

get the current buffer already read but not yet parsed

clearParseBuffer :: TransIO () Source #

empty the buffer

showNext :: Show a => a -> Int64 -> TransIO () Source #

Used for debugging. It shows the next N characters in the parse buffer

(|-) :: 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 (|--) :: TransIO (StreamData BS.ByteString) -> TransIO b -> TransIO b p |-- q = do --addThreads 1 v liftIO $ newIORef undefined -- :: TransIO (MVar (StreamData BS.ByteString - IO ())) initq v | initp v -- catcht (_ :: BlockedIndefinitelyOnMVar) -> empty -- TODO #2 use react instrad of MVar's? need buffering-contention where initq v= do --abduce r <-withParseStream (takev v ) q liftIO $ print "AFGRT WITH" return r