Safe Haskell | None |
---|
Documentation
type PreGramTrafo = Trafo Unit (Productions TL)Source
type ExtGram env start nts = PreGramTrafo env () (Export start nts env)Source
type GramExt env start nts start' nts' = PreGramTrafo env (Export start nts env) (Export start' nts' env)Source
addNT :: PreGramTrafo env (PreProductions TL env a) (Symbol a TNonT env)Source
addProds :: PreGramTrafo env (Symbol a TNonT env, PreProductions TL env a) ()Source
updProds :: PreGramTrafo env (Symbol a TNonT env, PreProductions TL env a -> PreProductions TL env a) ()Source
replaceProds :: PreGramTrafo env (Symbol a TNonT env, PreProductions TL env a) ()Source
mapNTProds :: Symbol b TNonT env -> Symbol b TNonT env -> PreProductions TL env a -> PreProductions TL env aSource
extendGram :: (NTRecord (nts env), NTRecord (nts' env)) => ExtGram env start nts -> GramExt env start nts start' nts' -> ExtGram env start' nts'Source
(+>>) :: (NTRecord (nts env), NTRecord (nts' env)) => ExtGram env start nts -> GramExt env start nts start' nts' -> ExtGram env start' nts'Source
exportNTs :: NTRecord (nts env) => PreGramTrafo env (Export start nts env) (Export start nts env)Source
labelLSPair :: LSPair nt a t env -> ntSource
GetNTLabel nt1 (l env) r (tenv env) => GetNTBool HFalse nt1 (NTCons nt2 v l env) r (tenv env) | |
GetNTBool HTrue nt1 (NTCons nt1 v l env) (Symbol v TNonT env) (tenv env) | |
NotDuplicated nt1 (l env) => NotDuplicated nt1 (NTCons nt2 v l env) | |
Fail (Duplicated nt) => NotDuplicated nt (NTCons nt v l env) | |
(TypeEq nt1 nt2 b, GetNTBool b nt1 (NTCons nt2 v l env) r (tenv env)) => GetNTLabel nt1 (NTCons nt2 v l env) r (tenv env) | |
(NTRecord (l env), NotDuplicated nt (l env)) => NTRecord (NTCons nt v l env) |
NotDuplicated nt (NTNil env) | |
Fail (NotFound nt (tenv env)) => GetNTLabel nt (NTNil env) r (tenv env) | |
NTRecord (NTNil env) |
data Duplicated nt Source
class NotDuplicated nt r Source
NotDuplicated nt (NTNil env) | |
NotDuplicated nt1 (l env) => NotDuplicated nt1 (NTCons nt2 v l env) | |
Fail (Duplicated nt) => NotDuplicated nt (NTCons nt v l env) |
GetNTLabel nt1 (l env) r (tenv env) => GetNTBool HFalse nt1 (NTCons nt2 v l env) r (tenv env) |
class GetNTLabel nt r v tenv | nt r -> v whereSource
getNTLabel :: tenv -> nt -> r -> vSource
Fail (NotFound nt (tenv env)) => GetNTLabel nt (NTNil env) r (tenv env) | |
(TypeEq nt1 nt2 b, GetNTBool b nt1 (NTCons nt2 v l env) r (tenv env)) => GetNTLabel nt1 (NTCons nt2 v l env) r (tenv env) |
export :: (NTRecord (l env), NotDuplicated nt (l env)) => nt -> Symbol a TNonT env -> l env -> NTCons nt a l envSource
extendExport :: Export start t env -> (t env -> nts env) -> Export start nts envSource