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

Symantic.Parser.Machine.Program

Contents

Description

Build the Instruction Program of a Machine from the Combinators of a Grammar. Instructions are kept introspectable to enable more optimizations now possible because of a broader knowledge of the Instructions around those generated (eg. by using joinNext).

Synopsis

Type Program

data Program repr inp a Source #

A Program is a tree of Instructions, where each Instruction is built by a continuation to be able to introspect, duplicate and/or change the next Instruction.

Constructors

Program 

Fields

Instances

Instances details
Routinable repr => Letable Name (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

def :: Name -> Program repr inp a -> Program repr inp a Source #

ref :: Bool -> Name -> Program repr inp a Source #

(tok ~ InputToken inp, Readable tok repr, Typeable tok) => Satisfiable tok (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

satisfy :: [ErrorItem tok] -> TermGrammar (tok -> Bool) -> Program repr inp tok Source #

item :: Program repr inp tok Source #

(Ord (InputToken inp), Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Readable (InputToken inp) repr, Typeable (InputToken inp), Stackable repr) => Lookable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

look :: Program repr inp a -> Program repr inp a Source #

negLook :: Program repr inp a -> Program repr inp () Source #

eof :: Program repr inp () Source #

(Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Stackable repr) => Foldable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

chainPre :: Program repr inp (a -> a) -> Program repr inp a -> Program repr inp a Source #

chainPost :: Program repr inp a -> Program repr inp (a -> a) -> Program repr inp a Source #

(Branchable repr, Joinable repr) => Matchable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

conditional :: Eq a => Program repr inp a -> [TermGrammar (a -> Bool)] -> [Program repr inp b] -> Program repr inp b -> Program repr inp b Source #

match :: Eq a => Program repr inp a -> [TermGrammar a] -> (TermGrammar a -> Program repr inp b) -> Program repr inp b -> Program repr inp b Source #

(Branchable repr, Joinable repr, Stackable repr) => Selectable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

branch :: Program repr inp (Either a b) -> Program repr inp (a -> c) -> Program repr inp (b -> c) -> Program repr inp c Source #

(Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Stackable repr) => Alternable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

(<|>) :: Program repr inp a -> Program repr inp a -> Program repr inp a Source #

empty :: Program repr inp a Source #

try :: Program repr inp a -> Program repr inp a Source #

(<+>) :: (Applicable (Program repr inp), Alternable (Program repr inp)) => Program repr inp a -> Program repr inp b -> Program repr inp (Either a b) Source #

Stackable repr => Applicable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

(<$>) :: TermGrammar (a -> b) -> Program repr inp a -> Program repr inp b Source #

(<&>) :: Program repr inp a -> TermGrammar (a -> b) -> Program repr inp b Source #

(<$) :: TermGrammar a -> Program repr inp b -> Program repr inp a Source #

($>) :: Program repr inp a -> TermGrammar b -> Program repr inp b Source #

pure :: TermGrammar a -> Program repr inp a Source #

(<*>) :: Program repr inp (a -> b) -> Program repr inp a -> Program repr inp b Source #

liftA2 :: TermGrammar (a -> b -> c) -> Program repr inp a -> Program repr inp b -> Program repr inp c Source #

(<*) :: Program repr inp a -> Program repr inp b -> Program repr inp a Source #

(*>) :: Program repr inp a -> Program repr inp b -> Program repr inp b Source #

(<**>) :: Program repr inp a -> Program repr inp (a -> b) -> Program repr inp b Source #

optimizeMachine :: forall inp es repr a. Machine (InputToken inp) repr => Program repr inp a -> repr inp '[] ('Succ es) a Source #

Build an interpreter of the Program of the given Machine.

failIfConsumed :: Cursorable (Cursor inp) => Branchable repr => Failable repr => Inputable repr => Stackable repr => SomeInstr repr inp vs ('Succ es) ret -> SomeInstr repr inp (Cursor inp ': vs) ('Succ es) ret Source #

If no input has been consumed by the failing alternative then continue with the given continuation. Otherwise, propagate the Failure.

joinNext :: Joinable repr => Program repr inp v -> Program repr inp v Source #

(joinNext m) factorize the next Instruction to be able to reuse it multiple times without duplication. It does so by introducing a defJoin and passing the corresponding refJoin as next Instruction to (m), unless factorizing is useless because the next Instruction is already a refJoin or a ret. It should be used each time the next Instruction is used multiple times.