Safe Haskell | None |
---|---|
Language | Haskell2010 |
Fast not-backtracking incremental scanner for bytestrings
Unlike attoparsec or most of other parser combinator libraries, scanner doesn't support backtracking. But you probably don't need it anyway, at least if you need fast parser.
Scanner processes input incrementally. When more input is needed, scanner
returns More
continuation. All the already processed input is discarded.
Synopsis
- data Scanner a
- data Result r
- = Done ByteString r
- | Fail ByteString String
- | More (ByteString -> Result r)
- scan :: Scanner r -> ByteString -> Result r
- scanOnly :: Scanner a -> ByteString -> Either String a
- scanLazy :: Scanner a -> ByteString -> Either String a
- scanWith :: Monad m => m ByteString -> Scanner a -> ByteString -> m (Result a)
- anyWord8 :: Scanner Word8
- anyChar8 :: Scanner Char
- word8 :: Word8 -> Scanner ()
- char8 :: Char -> Scanner ()
- take :: Int -> Scanner ByteString
- takeWhile :: (Word8 -> Bool) -> Scanner ByteString
- takeWhileChar8 :: (Char -> Bool) -> Scanner ByteString
- string :: ByteString -> Scanner ()
- skipWhile :: (Word8 -> Bool) -> Scanner ()
- skipSpace :: Scanner ()
- lookAhead :: Scanner (Maybe Word8)
- lookAheadChar8 :: Scanner (Maybe Char)
- foldlWhile :: (Word8 -> Bool) -> (a -> Word8 -> a) -> a -> Scanner a
- foldlWhile1 :: (Word8 -> Bool) -> (a -> Word8 -> a) -> a -> Scanner a
- satisfy :: (Word8 -> Bool) -> Scanner Word8
- satisfyMaybe :: (Word8 -> Bool) -> Scanner (Maybe Word8)
- decimal :: Integral n => Scanner n
Documentation
CPS scanner without backtracking
Scanner result
Done ByteString r | Successful result with the rest of input |
Fail ByteString String | Scanner failed with rest of input and error message |
More (ByteString -> Result r) | Need more input |
scanOnly :: Scanner a -> ByteString -> Either String a Source #
Scan the complete input, without resupplying
scanLazy :: Scanner a -> ByteString -> Either String a Source #
Scan lazy bytestring by resupplying scanner with chunks
scanWith :: Monad m => m ByteString -> Scanner a -> ByteString -> m (Result a) Source #
Scan with the provided resupply action
takeWhileChar8 :: (Char -> Bool) -> Scanner ByteString Source #
Take input while the predicate is True
string :: ByteString -> Scanner () Source #
Consume the specified string
Warning: it is not optimized yet, so for for small string it is better
to consume it byte-by-byte using word8
foldlWhile :: (Word8 -> Bool) -> (a -> Word8 -> a) -> a -> Scanner a Source #
Fold over the octets, which satisfy the predicate
foldlWhile1 :: (Word8 -> Bool) -> (a -> Word8 -> a) -> a -> Scanner a Source #
Fold over the octets, which satisfy the predicate, ensuring that there's at least one
satisfy :: (Word8 -> Bool) -> Scanner Word8 Source #
Consume a single octet which satisfies the predicate and fail if it does not