Earley-0.12.1.0: Parsing all context-free grammars using Earley's algorithm.

Safe HaskellNone
LanguageHaskell2010

Text.Earley.Generator.Internal

Contents

Description

This module exposes the internals of the package: its API may change independently of the PVP-compliant version number.

Synopsis

Concrete rules and productions

data Rule s r e t a Source #

The concrete rule type that the generator uses

Constructors

Rule 

Fields

mkRule :: ProdR s r e t a -> ST s (Rule s r e t a) Source #

prodNulls :: ProdR s r e t a -> Results s t a Source #

removeNulls :: ProdR s r e t a -> ProdR s r e t a Source #

Remove (some) nulls from a production

type ProdR s r e t a = Prod (Rule s r) e t a Source #

resetConts :: Rule s r e t a -> ST s () Source #

Delayed results

newtype Results s t a Source #

Constructors

Results 

Fields

Instances

Monad (Results t s) Source # 

Methods

(>>=) :: Results t s a -> (a -> Results t s b) -> Results t s b #

(>>) :: Results t s a -> Results t s b -> Results t s b #

return :: a -> Results t s a #

fail :: String -> Results t s a #

Functor (Results s t) Source # 

Methods

fmap :: (a -> b) -> Results s t a -> Results s t b #

(<$) :: a -> Results s t b -> Results s t a #

Applicative (Results s t) Source # 

Methods

pure :: a -> Results s t a #

(<*>) :: Results s t (a -> b) -> Results s t a -> Results s t b #

liftA2 :: (a -> b -> c) -> Results s t a -> Results s t b -> Results s t c #

(*>) :: Results s t a -> Results s t b -> Results s t b #

(<*) :: Results s t a -> Results s t b -> Results s t a #

Alternative (Results t s) Source # 

Methods

empty :: Results t s a #

(<|>) :: Results t s a -> Results t s a -> Results t s a #

some :: Results t s a -> Results t s [a] #

many :: Results t s a -> Results t s [a] #

Semigroup (Results s t a) Source # 

Methods

(<>) :: Results s t a -> Results s t a -> Results s t a #

sconcat :: NonEmpty (Results s t a) -> Results s t a #

stimes :: Integral b => b -> Results s t a -> Results s t a #

Monoid (Results s t a) Source # 

Methods

mempty :: Results s t a #

mappend :: Results s t a -> Results s t a -> Results s t a #

mconcat :: [Results s t a] -> Results s t a #

lazyResults :: ST s [(a, [t])] -> ST s (Results s t a) Source #

States and continuations

data BirthPos Source #

Constructors

Previous 
Current 

Instances

data State s r e t a where Source #

An Earley state with result type a.

Constructors

State :: !(ProdR s r e t a) -> !(a -> Results s t b) -> !BirthPos -> !(Conts s r e t b c) -> State s r e t c 
Final :: !(Results s t a) -> State s r e t a 

data Cont s r e t a b where Source #

A continuation accepting an a and producing a b.

Constructors

Cont :: !(a -> Results s t b) -> !(ProdR s r e t (b -> c)) -> !(c -> Results s t d) -> !(Conts s r e t d e') -> Cont s r e t a e' 
FinalCont :: (a -> Results s t c) -> Cont s r e t a c 

data Conts s r e t a c Source #

Constructors

Conts 

Fields

newConts :: STRef s [Cont s r e t a c] -> ST s (Conts s r e t a c) Source #

contraMapCont :: (b -> Results s t a) -> Cont s r e t a c -> Cont s r e t b c Source #

contToState :: BirthPos -> Results s t a -> Cont s r e t a c -> State s r e t c Source #

simplifyCont :: Conts s r e t b a -> ST s [Cont s r e t b a] Source #

Strings of non-ambiguous continuations can be optimised by removing indirections.

Grammars

initialState :: ProdR s a e t a -> ST s (State s a e t a) Source #

Given a grammar, construct an initial state.

Generation

data Result s t a Source #

The result of a generator.

Constructors

Ended (ST s [(a, [t])])

The generator ended.

Generated (ST s [(a, [t])]) (ST s (Result s t a))

The generator produced a number of as. These are given as a computation, ST s [a] that constructs the as when run. The Int is the position in the input where these results were obtained, and the last component is the continuation.

Instances

Functor (Result s t) Source # 

Methods

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

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

safeHead :: ListLike i t => i -> Maybe t Source #

data GenerationEnv s e t a Source #

Constructors

GenerationEnv 

Fields

  • results :: ![ST s [(a, [t])]]

    Results ready to be reported (when this position has been processed)

  • next :: ![State s a e t a]

    States to process at the next position

  • reset :: !(ST s ())

    Computation that resets the continuation refs of productions

  • tokens :: ![t]

    The possible tokens

generate Source #

Arguments

:: [State s a e t a]

States to process at this position

-> GenerationEnv s e t a 
-> ST s (Result s t a) 

The internal generation routine

type Generator t a = forall s. ST s (Result s t a) Source #

generator :: (forall r. Grammar r (Prod r e t a)) -> [t] -> Generator t a Source #

Create a language generator for given grammar and list of allowed tokens.

language :: Generator t a -> [(a, [t])] Source #

Run a generator, returning all members of the language.

The members are returned as parse results paired with the list of tokens used to produce the result. The elements of the returned list of results are sorted by their length in ascending order. If there are multiple results of the same length they are returned in an unspecified order.

upTo :: Int -> Generator t a -> [(a, [t])] Source #

upTo n gen runs the generator gen, returning all members of the language that are of length less than or equal to n.

The members are returned as parse results paired with the list of tokens used to produce the result. The elements of the returned list of results are sorted by their length in ascending order. If there are multiple results of the same length they are returned in an unspecified order.

exactly :: Int -> Generator t a -> [(a, [t])] Source #

exactly n gen runs the generator gen, returning all members of the language that are of length equal to n.

The members are returned as parse results paired with the list of tokens used to produce the result. If there are multiple results they are returned in an unspecified order.