smith-0.1.1.0: Parse arrays of tokens

Safe HaskellNone
LanguageHaskell2010

Data.Parser

Contents

Description

Parse token sequences.

Synopsis

Documentation

data Parser :: Type -> Type -> Type -> Type -> Type Source #

A non-resumable toke parser.

Instances
Monad (Parser a e s) Source # 
Instance details

Defined in Data.Parser.Unsafe

Methods

(>>=) :: Parser a e s a0 -> (a0 -> Parser a e s b) -> Parser a e s b #

(>>) :: Parser a e s a0 -> Parser a e s b -> Parser a e s b #

return :: a0 -> Parser a e s a0 #

fail :: String -> Parser a e s a0 #

Functor (Parser a e s) Source # 
Instance details

Defined in Data.Parser.Unsafe

Methods

fmap :: (a0 -> b) -> Parser a e s a0 -> Parser a e s b #

(<$) :: a0 -> Parser a e s b -> Parser a e s a0 #

Applicative (Parser a e s) Source # 
Instance details

Defined in Data.Parser.Unsafe

Methods

pure :: a0 -> Parser a e s a0 #

(<*>) :: Parser a e s (a0 -> b) -> Parser a e s a0 -> Parser a e s b #

liftA2 :: (a0 -> b -> c) -> Parser a e s a0 -> Parser a e s b -> Parser a e s c #

(*>) :: Parser a e s a0 -> Parser a e s b -> Parser a e s b #

(<*) :: Parser a e s a0 -> Parser a e s b -> Parser a e s a0 #

data Result e a #

The result of running a parser.

Constructors

Failure e

An error message indicating what went wrong.

Success !(Slice a)

The parsed value and the number of bytes remaining in parsed slice.

Instances
Functor (Result e) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

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

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

Foldable (Result e) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fold :: Monoid m => Result e m -> m #

foldMap :: Monoid m => (a -> m) -> Result e a -> m #

foldr :: (a -> b -> b) -> b -> Result e a -> b #

foldr' :: (a -> b -> b) -> b -> Result e a -> b #

foldl :: (b -> a -> b) -> b -> Result e a -> b #

foldl' :: (b -> a -> b) -> b -> Result e a -> b #

foldr1 :: (a -> a -> a) -> Result e a -> a #

foldl1 :: (a -> a -> a) -> Result e a -> a #

toList :: Result e a -> [a] #

null :: Result e a -> Bool #

length :: Result e a -> Int #

elem :: Eq a => a -> Result e a -> Bool #

maximum :: Ord a => Result e a -> a #

minimum :: Ord a => Result e a -> a #

sum :: Num a => Result e a -> a #

product :: Num a => Result e a -> a #

(Eq e, Eq a) => Eq (Result e a) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

(==) :: Result e a -> Result e a -> Bool #

(/=) :: Result e a -> Result e a -> Bool #

(Show e, Show a) => Show (Result e a) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

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

show :: Result e a -> String #

showList :: [Result e a] -> ShowS #

data Slice a #

Slicing metadata (an offset and a length) accompanied by a value. This does not represent a slice into the value. This type is intended to be used as the result of an executed parser. In this context the slicing metadata describe a slice into to the array (or byte array) that from which the value was parsed.

It is often useful to check the length when a parser succeeds since a non-zero length indicates that there was additional unconsumed input. The offset is only ever needed to construct a new slice (via Bytes or SmallVector) from the remaining input.

Constructors

Slice !Int !Int a 
Instances
Functor Slice 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

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

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

Foldable Slice 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

fold :: Monoid m => Slice m -> m #

foldMap :: Monoid m => (a -> m) -> Slice a -> m #

foldr :: (a -> b -> b) -> b -> Slice a -> b #

foldr' :: (a -> b -> b) -> b -> Slice a -> b #

foldl :: (b -> a -> b) -> b -> Slice a -> b #

foldl' :: (b -> a -> b) -> b -> Slice a -> b #

foldr1 :: (a -> a -> a) -> Slice a -> a #

foldl1 :: (a -> a -> a) -> Slice a -> a #

toList :: Slice a -> [a] #

null :: Slice a -> Bool #

length :: Slice a -> Int #

elem :: Eq a => a -> Slice a -> Bool #

maximum :: Ord a => Slice a -> a #

minimum :: Ord a => Slice a -> a #

sum :: Num a => Slice a -> a #

product :: Num a => Slice a -> a #

Eq a => Eq (Slice a) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

(==) :: Slice a -> Slice a -> Bool #

(/=) :: Slice a -> Slice a -> Bool #

Show a => Show (Slice a) 
Instance details

Defined in Data.Bytes.Parser.Types

Methods

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

show :: Slice a -> String #

showList :: [Slice a] -> ShowS #

parseSmallArray :: forall a e b. (forall s. Parser a e s b) -> SmallArray a -> Result e b Source #

Primitives

any :: e -> Parser a e s a Source #

Consumes and returns the next token from the input. Fails if no tokens are left.

opt :: Parser a e s (Maybe a) Source #

Consume a token from the input or return Nothing if end of the stream has been reached. This parser never fails.

peek :: e -> Parser a e s a Source #

Returns the next token from the input without consuming it. Fails if no tokens are left.

token Source #

Arguments

:: Eq a 
=> e

Error message

-> a

Expected value of next token

-> Parser a e s () 

Consumes the next token from the input. Fails if it is not equal to the expected value.

effect :: ST s b -> Parser a e s b Source #

Lift an effect into a parser.

fail :: e -> Parser a e s b Source #

Consumes and returns the next token from the input. Fails if no tokens are left.

trySatisfy :: (a -> Bool) -> Parser a e s Bool Source #

Looks at the next token from the input. If the token matches the predicate, consume the token and return True. Otherwise, do not consume the token and return False. If no tokens remain in the input, return False. This parser never fails.

Control Flow

foldSepBy1 Source #

Arguments

:: Parser a e s Bool

Separator

-> (b -> Parser a e s b)

Step

-> b

Initial value

-> Parser a e s b 

Fold over the tokens, repeatedly running step followed by separator until separator returns False. This is strict in the accumulator and always runs step at least once. There is no backtracking; any failure causes the whole combinator to fail.

sepBy1 Source #

Arguments

:: Parser a e s Bool

Separator

-> Parser a e s b

Step

-> Parser a e s () 

Fold over the tokens, repeatedly running step followed by separator until separator returns False. The results of step are discarded, but in conjunction with effect, this can be used to populate an array or a builder. This always runs step at least once.

sepBy1 sep step === step *> (sep >>= bool (pure ()) (step *> (sep >>= bool (pure ()) (...))))

skipWhile Source #

Arguments

:: (a -> Bool)

Predicate

-> Parser a e s () 

Skip tokens for which the predicate is true.