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

Symantic.Parser.Machine.Optimize

Description

Initial encoding with bottom-up optimizations of Instructions, re-optimizing downward as needed after each optimization. There is only one optimization (for push) so far, but the introspection enabled by the Instr data-type is also useful to optimize with more context in the Machine.

Synopsis

Data family Instr

data family Instr (instr :: ReprInstr -> Constraint) (repr :: ReprInstr) :: ReprInstr Source #

Instructions of the Machine. This is an extensible data-type.

Instances

Instances details
(Readable tok repr, tok ~ InputToken inp) => Trans (Instr (Readable tok) repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr (Readable tok) repr inp vs es a -> repr inp vs es a Source #

Joinable repr => Trans (Instr Joinable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Joinable repr inp vs es a -> repr inp vs es a Source #

Inputable repr => Trans (Instr Inputable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Inputable repr inp vs es a -> repr inp vs es a Source #

Failable repr => Trans (Instr Failable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Failable repr inp vs es a -> repr inp vs es a Source #

Branchable repr => Trans (Instr Branchable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Branchable repr inp vs es a -> repr inp vs es a Source #

Routinable repr => Trans (Instr Routinable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Routinable repr inp vs es a -> repr inp vs es a Source #

Stackable repr => Trans (Instr Stackable repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: Instr Stackable repr inp vs es a -> repr inp vs es a Source #

data Instr Joinable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Joinable repr where
data Instr Inputable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Inputable repr where
data Instr Failable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Failable repr where
data Instr Branchable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Branchable repr where
data Instr Routinable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Routinable repr where
data Instr Stackable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Stackable repr where
data Instr (Readable tok) repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr (Readable tok) repr where

pattern Instr :: Typeable comb => Instr comb repr inp vs es a -> SomeInstr repr inp vs es a Source #

Convenient utility to pattern-match a SomeInstr.

Type SomeInstr

data SomeInstr repr inp vs es a Source #

Some Instruction existantialized over the actual instruction symantic class. Useful to handle a list of Instructions without requiring impredicative quantification. Must be used by pattern-matching on the SomeInstr data-constructor, to bring the constraints in scope.

As in SomeComb, a first pass of optimizations is directly applied in it to avoid introducing an extra newtype, this also give a more comprehensible code.

Constructors

(Trans (Instr instr repr inp vs es) (repr inp vs es), Typeable instr) => SomeInstr (Instr instr repr inp vs es a) 

Instances

Instances details
(Readable tok repr, Typeable tok) => Readable tok (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

read :: forall inp (vs :: [Type]) (es :: Peano) a. tok ~ InputToken inp => [ErrorItem tok] -> TermInstr (tok -> Bool) -> SomeInstr repr inp (tok ': vs) ('Succ es) a -> SomeInstr repr inp vs ('Succ es) a Source #

Joinable repr => Joinable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

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

Inputable repr => Inputable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

loadInput :: forall inp (vs :: [Type]) (es :: Peano) a. SomeInstr repr inp vs es a -> SomeInstr repr inp (Cursor inp ': vs) es a Source #

pushInput :: forall inp (vs :: [Type]) (es :: Peano) a. SomeInstr repr inp (Cursor inp ': vs) es a -> SomeInstr repr inp vs es a Source #

Failable repr => Failable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

popFail :: forall inp (vs :: [Type]) (es :: Peano) a. SomeInstr repr inp vs es a -> SomeInstr repr inp vs ('Succ es) a Source #

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

Branchable repr => Branchable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

caseI :: forall inp x (vs :: [Type]) (es :: Peano) r y. SomeInstr repr inp (x ': vs) es r -> SomeInstr repr inp (y ': vs) es r -> SomeInstr repr inp (Either x y ': vs) es r Source #

choices :: forall v inp (vs :: [Type]) (es :: Peano) a. [TermInstr (v -> Bool)] -> [SomeInstr repr inp vs es a] -> SomeInstr repr inp vs es a -> SomeInstr repr inp (v ': vs) es a Source #

ifI :: forall inp (vs :: [Type]) (es :: Peano) a. SomeInstr repr inp vs es a -> SomeInstr repr inp vs es a -> SomeInstr repr inp (Bool ': vs) es a Source #

Routinable repr => Routinable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

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

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

ret :: forall inp a (es :: Peano). SomeInstr repr inp '[a] es a Source #

jump :: forall a inp (es :: Peano). LetName a -> SomeInstr repr inp '[] ('Succ es) a Source #

Stackable repr => Stackable (SomeInstr repr) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

push :: forall v inp (vs :: [Type]) (es :: Peano) a. TermInstr v -> SomeInstr repr inp (v ': vs) es a -> SomeInstr repr inp vs es a Source #

pop :: forall inp (vs :: [Type]) (es :: Peano) a v. SomeInstr repr inp vs es a -> SomeInstr repr inp (v ': vs) es a Source #

liftI2 :: forall x y z inp (vs :: [Type]) (es :: Peano) a. TermInstr (x -> y -> z) -> SomeInstr repr inp (z ': vs) es a -> SomeInstr repr inp (y ': (x ': vs)) es a Source #

swap :: forall inp x y (vs :: [Type]) (es :: Peano) a. SomeInstr repr inp (x ': (y ': vs)) es a -> SomeInstr repr inp (y ': (x ': vs)) es a Source #

mapI :: forall x y inp (vs :: [Type]) (es :: Peano) a. TermInstr (x -> y) -> SomeInstr repr inp (y ': vs) es a -> SomeInstr repr inp (x ': vs) es a Source #

appI :: forall inp y (vs :: [Type]) (es :: Peano) a x. SomeInstr repr inp (y ': vs) es a -> SomeInstr repr inp (x ': ((x -> y) ': vs)) es a Source #

Trans (SomeInstr repr inp vs es) (repr inp vs es) Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

Methods

trans :: SomeInstr repr inp vs es a -> repr inp vs es a Source #

unSomeInstr :: forall instr repr inp vs es a. Typeable instr => SomeInstr repr inp vs es a -> Maybe (Instr instr repr inp vs es a) Source #

(unSomeInstr i :: Maybe (Instr comb repr inp vs es a)) extract the data-constructor from the given SomeInstr iif. it belongs to the (Instr comb repr a) data-instance.