Safe Haskell | None |
---|
- data Grammar a = forall env . Grammar (Ref a env) (FinalEnv (Productions NF) env)
- type GramEnv = Env (Productions NF)
- type PreGramEnv = Env (Productions TL)
- data TL
- data FL a
- data NF
- data Prod l a env where
- newtype Productions l a env = PS {}
- newtype PreProductions l env a = PP {}
- data TTerm
- data TNonT
- data TAttT
- data Symbol a t env where
- Term :: String -> Symbol (DTerm String) TTerm env
- Nont :: Ref a env -> Symbol a TNonT env
- TermInt :: Symbol (DTerm Int) TAttT env
- TermChar :: Symbol (DTerm Char) TAttT env
- TermVarid :: Symbol (DTerm String) TAttT env
- TermConid :: Symbol (DTerm String) TAttT env
- TermOp :: Symbol (DTerm String) TAttT env
- TermAnyOf :: [Char] -> Symbol (DTerm Char) TAttT env
- TermAnyExcept :: [Char] -> Symbol (DTerm Char) TAttT env
- getRefNT :: Symbol a TNonT env -> Ref a env
- matchSym :: Symbol a t1 env -> Symbol b t2 env -> Maybe (Equal (a, t1) (b, t2))
- pairEq :: Maybe (Equal a b) -> Maybe (Equal (a, t) (b, t))
- int :: Symbol (DTerm Int) TAttT env
- char :: Symbol (DTerm Char) TAttT env
- var :: Symbol (DTerm String) TAttT env
- op :: Symbol (DTerm String) TAttT env
- con :: Symbol (DTerm String) TAttT env
- anyOf :: [Char] -> Symbol (DTerm Char) TAttT env
- anyExcept :: [Char] -> Symbol (DTerm Char) TAttT env
- type Line = Int
- type Column = Int
- type Filename = String
- data Pos
- data DTerm a = DTerm {}
- mkDTerm :: a -> DTerm a
- sym :: Symbol a t env -> PreProductions l env a
- nt :: Symbol a TNonT env -> PreProductions l env a
- ntPrd :: Symbol a TNonT env -> PreProductions l env a
- tr :: String -> PreProductions l env (DTerm String)
- prod :: PreProductions l env a -> Productions l a env
- varPrd :: PreProductions (FL a) env a
- fixPrd :: PreProductions (FL a) env a -> PreProductions TL env a
- pSome :: PreProductions (FL [a]) env a -> PreProductions TL env [a]
- pMany :: PreProductions (FL [a]) env a -> PreProductions TL env [a]
- opt :: PreProductions l env a -> a -> PreProductions l env a
- pMaybe :: (b, a -> b) -> PreProductions TL env a -> PreProductions TL env b
- pFoldr :: (a -> b -> b, b) -> PreProductions (FL b) env a -> PreProductions TL env b
- data Ii = Ii
- iI :: Idiomatic l env (a -> a) g => g
- class Idiomatic l env f g | g -> f l env where
- idiomatic :: PreProductions l env f -> g
- data Kw = Kw String
- kw :: String -> Kw
Documentation
type GramEnv = Env (Productions NF)Source
type PreGramEnv = Env (Productions TL)Source
newtype Productions l a env Source
newtype PreProductions l env a Source
Idiomatic l env x (Ii -> PreProductions l env x) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (PreProductions l env a -> g) | |
Functor (PreProductions l env) | |
Applicative (PreProductions l env) | |
Alternative (PreProductions l env) |
data Symbol a t env whereSource
Represents a symbol in a production, either a terminal or non terminal. Additional attributed terminal symbols exist for common lexical structures.
Term :: String -> Symbol (DTerm String) TTerm env | |
Nont :: Ref a env -> Symbol a TNonT env | |
TermInt :: Symbol (DTerm Int) TAttT env | |
TermChar :: Symbol (DTerm Char) TAttT env | |
TermVarid :: Symbol (DTerm String) TAttT env | |
TermConid :: Symbol (DTerm String) TAttT env | |
TermOp :: Symbol (DTerm String) TAttT env | |
TermAnyOf :: [Char] -> Symbol (DTerm Char) TAttT env | |
TermAnyExcept :: [Char] -> Symbol (DTerm Char) TAttT env |
Idiomatic l env f g => Idiomatic l env (a -> f) (Symbol a TNonT env -> g) | |
Idiomatic l env f g => Idiomatic l env ((Record HNil -> a) -> f) (Symbol a TAttT env -> g) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (Symbol a TAttT env -> g) | |
GetNTBool HTrue nt1 (NTCons nt1 v l env) (Symbol v TNonT env) (tenv env) | |
GetNTLabel nt (nts env) (Symbol a TNonT env) (nts env) => GetNT nt (Export start nts env) (Symbol a TNonT env) |
getRefNT :: Symbol a TNonT env -> Ref a envSource
Gets the reference into the environment from the non terminal.
matchSym :: Symbol a t1 env -> Symbol b t2 env -> Maybe (Equal (a, t1) (b, t2))Source
Matches two symbols
sym :: Symbol a t env -> PreProductions l env aSource
Lifts a single symbol into a singleton PreProductions
nt :: Symbol a TNonT env -> PreProductions l env aSource
Lifts a non terminal into a singleton PreProductions
ntPrd :: Symbol a TNonT env -> PreProductions l env aSource
tr :: String -> PreProductions l env (DTerm String)Source
Lifts a string, as terminal into a singleton PreProductions
prod :: PreProductions l env a -> Productions l a envSource
Conversion between Productions and PreProductions
varPrd :: PreProductions (FL a) env aSource
A PreProductions for a variable used on fixpoint level
fixPrd :: PreProductions (FL a) env a -> PreProductions TL env aSource
The fixpoint of a production
pSome :: PreProductions (FL [a]) env a -> PreProductions TL env [a]Source
pMany :: PreProductions (FL [a]) env a -> PreProductions TL env [a]Source
opt :: PreProductions l env a -> a -> PreProductions l env aSource
pMaybe :: (b, a -> b) -> PreProductions TL env a -> PreProductions TL env bSource
pFoldr :: (a -> b -> b, b) -> PreProductions (FL b) env a -> PreProductions TL env bSource
The Ii
is to be pronounced as stop
Idiomatic l env x (Ii -> PreProductions l env x) |
class Idiomatic l env f g | g -> f l env whereSource
idiomatic :: PreProductions l env f -> gSource
Idiomatic l env f g => Idiomatic l env f (String -> g) | |
Idiomatic l env x (Ii -> PreProductions l env x) | |
Idiomatic l env f g => Idiomatic l env ((a -> b) -> f) ((a -> b) -> g) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (Symbol a TNonT env -> g) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (PreProductions l env a -> g) | |
Idiomatic l env f g => Idiomatic l env ((Record HNil -> DTerm String) -> f) (Kw -> g) | |
Idiomatic l env f g => Idiomatic l env ((Record HNil -> a) -> f) (Symbol a TAttT env -> g) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (SF a -> g) | |
Idiomatic l env f g => Idiomatic l env (DTerm String -> f) (Kw -> g) | |
Idiomatic l env f g => Idiomatic l env (a -> f) (Symbol a TAttT env -> g) |