Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exposes the internals of the package: its API may change independently of the PVP-compliant version number.
- data Rule s r e t a = Rule {}
- mkRule :: ProdR s r e t a -> ST s (Rule s r e t a)
- prodNulls :: ProdR s r e t a -> Results s t a
- removeNulls :: ProdR s r e t a -> ProdR s r e t a
- type ProdR s r e t a = Prod (Rule s r) e t a
- resetConts :: Rule s r e t a -> ST s ()
- newtype Results s t a = Results {}
- lazyResults :: ST s [(a, [t])] -> ST s (Results s t a)
- data BirthPos
- data State s r e t a where
- data Cont s r e t a b where
- data Conts s r e t a c = Conts {}
- newConts :: STRef s [Cont s r e t a c] -> ST s (Conts s r e t a c)
- contraMapCont :: (b -> Results s t a) -> Cont s r e t a c -> Cont s r e t b c
- contToState :: BirthPos -> Results s t a -> Cont s r e t a c -> State s r e t c
- simplifyCont :: Conts s r e t b a -> ST s [Cont s r e t b a]
- initialState :: ProdR s a e t a -> ST s (State s a e t a)
- data Result s t a
- safeHead :: ListLike i t => i -> Maybe t
- data GenerationEnv s e t a = GenerationEnv {}
- emptyGenerationEnv :: [t] -> GenerationEnv s e t a
- generate :: [State s a e t a] -> GenerationEnv s e t a -> ST s (Result s t a)
- type Generator t a = forall s. ST s (Result s t a)
- generator :: (forall r. Grammar r (Prod r e t a)) -> [t] -> Generator t a
- language :: Generator t a -> [(a, [t])]
- upTo :: Int -> Generator t a -> [(a, [t])]
- exactly :: Int -> Generator t a -> [(a, [t])]
Concrete rules and productions
The concrete rule type that the generator uses
removeNulls :: ProdR s r e t a -> ProdR s r e t a Source #
Remove (some) nulls from a production
resetConts :: Rule s r e t a -> ST s () Source #
Delayed results
States and continuations
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
The result of a generator.
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 |
data GenerationEnv s e t a Source #
emptyGenerationEnv :: [t] -> GenerationEnv s e t a Source #
:: [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
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.