Z-Data-0.1.6.0: Array, vector and text

Copyright(c) Dong Han 2017-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Parser.Base

Contents

Description

This module provide internal data types for a simple resumable Parser, which is suitable for binary protocol and simple textual protocol parsing. Parser extensively works on on Bytes, which is same to Text representation.

Synopsis

Parser types

data Result a Source #

Simple parsing result, that represent respectively:

  • Success: the remaining unparsed data and the parsed value
  • Failure: the remaining unparsed data and the error message
  • Partial: that need for more input data, supply empty bytes to indicate endOfInput
Instances
Functor Result Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

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

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

Show a => Show (Result a) Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

type ParseError = [Text] Source #

Type alias for error message

type ParseStep r = Bytes -> Result r Source #

A parse step consumes Bytes and produce Result.

newtype Parser a Source #

Simple CPSed parser

A parser takes a failure continuation, and a success one, while the success continuation is usually composed by Monad instance, the failure one is more like a reader part, which can be modified via <?>. If you build parsers from ground, a pattern like this can be used:

   xxParser = do
     ensureN errMsg ...            -- make sure we have some bytes
     Parser $  kf k inp ->        -- fail continuation, success continuation and input
       ...
       ... kf errMsg (if input not OK)
       ... k ... (if we get something useful for next parser)
 

Constructors

Parser 

Fields

Instances
Monad Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

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

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

MonadFail Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

fail :: String -> Parser a #

Applicative Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

pure :: a -> Parser a #

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

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

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

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

Alternative Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 
Instance details

Defined in Z.Data.Parser.Base

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

(<?>) :: Text -> Parser a -> Parser a infixr 0 Source #

Running a parser

parse :: Parser a -> Bytes -> (Bytes, Either ParseError a) Source #

Parse the complete input, without resupplying, return the rest bytes

parse_ :: Parser a -> Bytes -> Either ParseError a Source #

Parse the complete input, without resupplying

parseChunk :: Parser a -> Bytes -> Result a Source #

Parse an input chunk

parseChunks :: Monad m => Parser a -> m Bytes -> Bytes -> m (Bytes, Either ParseError a) Source #

Run a parser with an initial input string, and a monadic action that can supply more input if needed.

Note, once the monadic action return empty bytes, parsers will stop drawing more bytes (take it as endOfInput).

finishParsing :: Result a -> (Bytes, Either ParseError a) Source #

Finish parsing and fetch result, feed empty bytes if it's Partial result.

runAndKeepTrack :: Parser a -> Parser (Result a, [Bytes]) Source #

Run a parser and keep track of all the input chunks it consumes. Once it's finished, return the final result (always Success or Failure) and all consumed chunks.

match :: Parser a -> Parser (Bytes, a) Source #

Return both the result of a parse and the portion of the input that was consumed while it was being parsed.

Basic parsers

ensureN :: Int -> ParseError -> Parser () Source #

Ensure that there are at least n bytes available. If not, the computation will escape with Partial.

Since this parser is used in many other parsers, an extra error param is provide to attach custom error info.

endOfInput :: Parser () Source #

Test whether all input has been consumed, i.e. there are no remaining undecoded bytes. Fail if not atEnd.

atEnd :: Parser Bool Source #

Test whether all input has been consumed, i.e. there are no remaining undecoded bytes.

Primitive decoders

decodePrim :: forall a. Unaligned a => Parser a Source #

decodePrimLE :: forall a. Unaligned (LE a) => Parser a Source #

decodePrimBE :: forall a. Unaligned (BE a) => Parser a Source #

More parsers

scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s) Source #

A stateful scanner. The predicate consumes and transforms a state argument, and each transformed state is passed to successive invocations of the predicate on each byte of the input until one returns Nothing or the input ends.

This parser does not fail. It will return an empty string if the predicate returns Nothing on the first byte of input.

scanChunks :: forall s. s -> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s) Source #

Similar to scan, but working on Bytes chunks, The predicate consumes a Bytes chunk and transforms a state argument, and each transformed state is passed to successive invocations of the predicate on each chunk of the input until one chunk got splited to Right (V.Bytes, V.Bytes) or the input ends.

peekMaybe :: Parser (Maybe Word8) Source #

Match any byte, to perform lookahead. Returns Nothing if end of input has been reached. Does not consume any input.

peek :: Parser Word8 Source #

Match any byte, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.

satisfy :: (Word8 -> Bool) -> Parser Word8 Source #

The parser satisfy p succeeds for any byte for which the predicate p returns True. Returns the byte that is actually parsed.

digit = satisfy isDigit
    where isDigit w = w >= 48 && w <= 57

satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a Source #

The parser satisfyWith f p transforms a byte, and succeeds if the predicate p returns True on the transformed value. The parser returns the transformed byte that was parsed.

word8 :: Word8 -> Parser () Source #

Match a specific byte.

char8 :: Char -> Parser () Source #

Match a specific 8bit char.

skipWord8 :: Parser () Source #

Skip a byte.

endOfLine :: Parser () Source #

Match either a single newline byte '\n', or a carriage return followed by a newline byte "\r\n".

skip :: Int -> Parser () Source #

skip N bytes.

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

Skip past input for as long as the predicate returns True.

skipSpaces :: Parser () Source #

Skip over white space using isSpace.

takeTill :: (Word8 -> Bool) -> Parser Bytes Source #

Consume input as long as the predicate returns False or reach the end of input, and return the consumed input.

takeWhile :: (Word8 -> Bool) -> Parser Bytes Source #

Consume input as long as the predicate returns True or reach the end of input, and return the consumed input.

takeWhile1 :: (Word8 -> Bool) -> Parser Bytes Source #

Similar to takeWhile, but requires the predicate to succeed on at least one byte of input: it will fail if the predicate never returns True or reach the end of input

bytes :: Bytes -> Parser () Source #

bytes s parses a sequence of bytes that identically match s.

bytesCI :: Bytes -> Parser () Source #

Same as bytes but ignoring case.

text :: Text -> Parser () Source #

text s parses a sequence of UTF8 bytes that identically match s.

Misc

isSpace :: Word8 -> Bool Source #

isSpace w = w == 32 || w - 9 <= 4 || w == 0xA0

fail' :: Text -> Parser a Source #

Text version of fail.