murder-1.3.4: MUtually Recursive Definitions Explicitly Represented

Safe HaskellNone

Language.Grammars.Grammar

Synopsis

Documentation

data Grammar a Source

Constructors

forall env . Grammar (Ref a env) (FinalEnv (Productions NF) env) 

data TL Source

data FL a Source

data NF Source

data Prod l a env whereSource

Constructors

Star :: Prod l (a -> b) env -> Prod l a env -> Prod l b env 
FlipStar :: Prod NF a env -> Prod NF (a -> b) env -> Prod NF b env 
Sym :: Symbol a t env -> Prod l a env 
Pure :: a -> Prod l a env 
Fix :: Productions (FL a) a env -> Prod TL a env 
Var :: Prod (FL a) a env 

newtype Productions l a env Source

Constructors

PS 

Fields

unPS :: [Prod l a env]
 

newtype PreProductions l env a Source

Constructors

PP 

Fields

unPP :: [Prod l a env]
 

Instances

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 TNonT Source

Instances

Idiomatic l env f g => Idiomatic l env (a -> f) (Symbol a TNonT 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) 

data TAttT Source

Instances

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) 

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.

Instances

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

pairEq :: Maybe (Equal a b) -> Maybe (Equal (a, t) (b, t))Source

data Pos Source

Instances

data DTerm a Source

Constructors

DTerm 

Fields

pos :: Pos
 
value :: a
 

Instances

Idiomatic l env f g => Idiomatic l env ((Record HNil -> DTerm String) -> f) (Kw -> g) 
Idiomatic l env f g => Idiomatic l env (DTerm String -> f) (Kw -> g) 
Eq a => Eq (DTerm a) 
Show a => Show (DTerm a) 

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

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

data Ii Source

The Ii is to be pronounced as stop

Constructors

Ii 

Instances

Idiomatic l env x (Ii -> PreProductions l env x) 

iI :: Idiomatic l env (a -> a) g => gSource

The function iI is to be pronounced as start

class Idiomatic l env f g | g -> f l env whereSource

Methods

idiomatic :: PreProductions l env f -> gSource

Instances

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) 

data Kw Source

Constructors

Kw String 

Instances

Idiomatic l env f g => Idiomatic l env ((Record HNil -> DTerm String) -> f) (Kw -> g) 
Idiomatic l env f g => Idiomatic l env (DTerm String -> f) (Kw -> g)