scanner-0.3: Fast non-backtracking incremental combinator parsing for bytestrings

Safe HaskellNone
LanguageHaskell2010

Scanner

Description

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

Documentation

data Scanner a Source #

CPS scanner without backtracking

Instances
Monad Scanner Source # 
Instance details

Defined in Scanner.Internal

Methods

(>>=) :: Scanner a -> (a -> Scanner b) -> Scanner b #

(>>) :: Scanner a -> Scanner b -> Scanner b #

return :: a -> Scanner a #

fail :: String -> Scanner a #

Functor Scanner Source # 
Instance details

Defined in Scanner.Internal

Methods

fmap :: (a -> b) -> Scanner a -> Scanner b #

(<$) :: a -> Scanner b -> Scanner a #

Applicative Scanner Source # 
Instance details

Defined in Scanner.Internal

Methods

pure :: a -> Scanner a #

(<*>) :: Scanner (a -> b) -> Scanner a -> Scanner b #

liftA2 :: (a -> b -> c) -> Scanner a -> Scanner b -> Scanner c #

(*>) :: Scanner a -> Scanner b -> Scanner b #

(<*) :: Scanner a -> Scanner b -> Scanner a #

data Result r Source #

Scanner result

Constructors

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

scan :: Scanner r -> ByteString -> Result r Source #

Run scanner with the 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

anyWord8 :: Scanner Word8 Source #

Consume the next word

It fails if end of input

anyChar8 :: Scanner Char Source #

Consume the next 8-bit char

It fails if end of input

word8 :: Word8 -> Scanner () Source #

Consume the specified word or fail

char8 :: Char -> Scanner () Source #

Consume the specified 8-bit char or fail

take :: Int -> Scanner ByteString Source #

Take the specified number of bytes

takeWhile :: (Word8 -> Bool) -> Scanner ByteString Source #

Take input while the predicate is True

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

skipWhile :: (Word8 -> Bool) -> Scanner () Source #

Skip any input while the preducate is True

skipSpace :: Scanner () Source #

Skip space

lookAhead :: Scanner (Maybe Word8) Source #

Return the next byte, if any, without consuming it

lookAheadChar8 :: Scanner (Maybe Char) Source #

Return the next byte, if any, without consuming it

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

satisfyMaybe :: (Word8 -> Bool) -> Scanner (Maybe Word8) Source #

Consume a single octet in case it satisfies the predicate

decimal :: Integral n => Scanner n Source #

Parse a non-negative decimal number in ASCII