symantic-parser-0.0.0.20210102: Parser combinators statically optimized and staged via typed meta-programming
Safe HaskellNone
LanguageHaskell2010

Symantic.Parser.Machine.Generate

Synopsis

Type Gen

newtype Gen inp vs es a Source #

Generate the CodeQ parsing the input.

Constructors

Gen 

Fields

Instances

Instances details
Joinable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

defJoin :: forall v inp (vs :: [Type]) (es :: Peano) ret. LetName v -> Gen inp (v ': vs) es ret -> Gen inp vs es ret -> Gen inp vs es ret Source #

refJoin :: forall v inp (vs :: [Type]) (es :: Peano) ret. LetName v -> Gen inp (v ': vs) es ret Source #

Routinable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

subroutine :: forall v inp (vs :: [Type]) (es :: Peano) ret. LetName v -> Gen inp '[] ('Succ 'Zero) v -> Gen inp vs ('Succ es) ret -> Gen inp vs ('Succ es) ret Source #

call :: forall v inp (vs :: [Type]) (es :: Peano) ret. LetName v -> Gen inp (v ': vs) ('Succ es) ret -> Gen inp vs ('Succ es) ret Source #

ret :: forall inp ret (es :: Peano). Gen inp '[ret] es ret Source #

jump :: forall ret inp (es :: Peano). LetName ret -> Gen inp '[] ('Succ es) ret Source #

Inputable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

loadInput :: forall inp (vs :: [Type]) (es :: Peano) r. Gen inp vs es r -> Gen inp (Cursor inp ': vs) es r Source #

pushInput :: forall inp (vs :: [Type]) (es :: Peano) ret. Gen inp (Cursor inp ': vs) es ret -> Gen inp vs es ret Source #

Failable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

fail :: forall inp (vs :: [Type]) (es :: Peano) ret. [ErrorItem (InputToken inp)] -> Gen inp vs ('Succ es) ret Source #

popFail :: forall inp (vs :: [Type]) (es :: Peano) ret. Gen inp vs es ret -> Gen inp vs ('Succ es) ret Source #

catchFail :: forall inp (vs :: [Type]) (es :: Peano) ret. Gen inp vs ('Succ es) ret -> Gen inp (Cursor inp ': vs) es ret -> Gen inp vs es ret Source #

Branchable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

case_ :: forall inp x (vs :: [Type]) (n :: Peano) r y. Gen inp (x ': vs) n r -> Gen inp (y ': vs) n r -> Gen inp (Either x y ': vs) n r Source #

choices :: forall v inp (vs :: [Type]) (es :: Peano) ret. [InstrPure (v -> Bool)] -> [Gen inp vs es ret] -> Gen inp vs es ret -> Gen inp (v ': vs) es ret Source #

Stackable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

push :: forall v inp (vs :: [Type]) (n :: Peano) ret. InstrPure v -> Gen inp (v ': vs) n ret -> Gen inp vs n ret Source #

pop :: forall inp (vs :: [Type]) (n :: Peano) ret v. Gen inp vs n ret -> Gen inp (v ': vs) n ret Source #

liftI2 :: forall x y z inp (vs :: [Type]) (es :: Peano) ret. InstrPure (x -> y -> z) -> Gen inp (z ': vs) es ret -> Gen inp (y ': (x ': vs)) es ret Source #

swap :: forall inp x y (vs :: [Type]) (n :: Peano) r. Gen inp (x ': (y ': vs)) n r -> Gen inp (y ': (x ': vs)) n r Source #

Readable Gen Char Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

read :: forall inp (vs :: [Type]) (es :: Peano) ret. Char ~ InputToken inp => [ErrorItem Char] -> InstrPure (Char -> Bool) -> Gen inp (Char ': vs) ('Succ es) ret -> Gen inp vs ('Succ es) ret Source #

Type ParsingError

data ParsingError inp Source #

Instances

Instances details
Show (InputToken inp) => Show (ParsingError inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Type Offset

Type Cont

type Cont inp v a = Cursor inp -> [ErrorItem (InputToken inp)] -> v -> Cursor inp -> Either (ParsingError inp) a Source #

Type SubRoutine

type SubRoutine inp v a = Cont inp v a -> Cursor inp -> FailHandler inp a -> Either (ParsingError inp) a Source #

Type FailHandler

type FailHandler inp a = Cursor inp -> Cursor inp -> [ErrorItem (InputToken inp)] -> Either (ParsingError inp) a Source #

generate :: forall inp ret. Ord (InputToken inp) => Show (InputToken inp) => Lift (InputToken inp) => Input inp => CodeQ inp -> Show (Cursor inp) => Gen inp '[] ('Succ 'Zero) ret -> CodeQ (Either (ParsingError inp) ret) Source #

(generate input mach) generates TemplateHaskell code parsing given input according to given machine.

Type GenCtx

data GenCtx inp vs (es :: Peano) a Source #

This is a context only present at compile-time.

Constructors

(Lift (InputToken inp), Cursorable (Cursor inp), Show (InputToken inp)) => GenCtx 

Fields

Type ValueStack

data ValueStack vs where Source #

Constructors

ValueStackEmpty :: ValueStack '[] 
ValueStackCons 

Fields

Type FailStack

data FailStack inp es a where Source #

Constructors

FailStackEmpty :: FailStack inp 'Zero a 
FailStackCons 

Fields

suspend :: Gen inp (v ': vs) es a -> GenCtx inp vs es a -> CodeQ (Cont inp v a) Source #

resume :: CodeQ (Cont inp v a) -> Gen inp (v ': vs) es a Source #

sat :: forall inp vs es a. Ord (InputToken inp) => Lift (InputToken inp) => CodeQ (InputToken inp -> Bool) -> Gen inp (InputToken inp ': vs) ('Succ es) a -> Gen inp vs ('Succ es) a -> Gen inp vs ('Succ es) a Source #

emitLengthCheck :: Lift (InputToken inp) => Int -> Gen inp vs es a -> Gen inp vs es a -> Gen inp vs es a Source #

liftCode1 :: InstrPure (a -> b) -> CodeQ a -> CodeQ b Source #

liftCode2 :: InstrPure (a -> b -> c) -> CodeQ a -> CodeQ b -> CodeQ c Source #