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

Symantic.Parser.Machine.Instructions

Description

Semantic of the parsing instructions used to make the parsing control-flow explicit, in the convenient tagless-final encoding.

Synopsis

Type TermInstr

Type Peano

data Peano Source #

Type-level natural numbers, using the Peano recursive encoding.

Constructors

Zero 
Succ Peano 

Class Machine

type Machine tok repr = (Branchable repr, Failable repr, Inputable repr, Joinable repr, Routinable repr, Stackable repr, Readable tok repr) Source #

All the Instructions.

Type ReprInstr

type ReprInstr = Type -> [Type] -> Peano -> Type -> Type Source #

Type LetName

newtype LetName a Source #

Name of a subroutine or defJoin indexed by the return type of the factorized Instructions. This helps type-inferencing.

Constructors

LetName 

Fields

Instances

Instances details
Eq (LetName a) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

(==) :: LetName a -> LetName a -> Bool #

(/=) :: LetName a -> LetName a -> Bool #

Show (LetName a) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

showsPrec :: Int -> LetName a -> ShowS #

show :: LetName a -> String #

showList :: [LetName a] -> ShowS #

Class Stackable

class Stackable (repr :: ReprInstr) where Source #

Minimal complete definition

push, pop, liftI2, swap

Methods

push :: TermInstr v -> repr inp (v ': vs) es a -> repr inp vs es a Source #

pop :: repr inp vs es a -> repr inp (v ': vs) es a Source #

liftI2 :: TermInstr (x -> y -> z) -> repr inp (z ': vs) es a -> repr inp (y ': (x ': vs)) es a Source #

swap :: repr inp (x ': (y ': vs)) es a -> repr inp (y ': (x ': vs)) es a Source #

mapI :: TermInstr (x -> y) -> repr inp (y ': vs) es a -> repr inp (x ': vs) es a Source #

(mapI f k).

appI :: repr inp (y ': vs) es a -> repr inp (x ': ((x -> y) ': vs)) es a Source #

(appI k) pops (x) and (x2y) from the valueStack, pushes (x2y x) and continues with the next Instruction (k).

Instances

Instances details
Stackable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

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

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

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

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

Stackable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

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

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

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

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

appI :: forall inp y (vs :: [Type]) (es :: Peano) a x. ViewMachine sN inp (y ': vs) es a -> ViewMachine sN inp (x ': ((x -> y) ': vs)) 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 #

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 Stackable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Stackable repr where

Class Routinable

class Routinable (repr :: ReprInstr) where Source #

Methods

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

call :: LetName v -> repr inp (v ': vs) ('Succ es) a -> repr inp vs ('Succ es) a Source #

ret :: repr inp '[a] es a Source #

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

Instances

Instances details
Routinable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

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

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

ShowLetName sN Name => Routinable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

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

ret :: forall inp a (es :: Peano). ViewMachine sN inp '[a] es a Source #

jump :: forall a inp (es :: Peano). LetName a -> ViewMachine sN inp '[] ('Succ 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 #

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 #

data Instr Routinable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Routinable repr where

Class Branchable

class Branchable (repr :: ReprInstr) where Source #

Minimal complete definition

caseI, choices

Methods

caseI :: repr inp (x ': vs) es r -> repr inp (y ': vs) es r -> repr inp (Either x y ': vs) es r Source #

choices :: [TermInstr (v -> Bool)] -> [repr inp vs es a] -> repr inp vs es a -> repr inp (v ': vs) es a Source #

ifI :: repr inp vs es a -> repr inp vs es a -> repr inp (Bool ': vs) es a Source #

(ifI ok ko) pops a Bool from the valueStack and continues either with the Instruction (ok) if it is True or (ko) otherwise.

Instances

Instances details
Branchable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

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

Branchable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

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

ifI :: forall inp (vs :: [Type]) (es :: Peano) a. ViewMachine sN inp vs es a -> ViewMachine sN inp vs es a -> ViewMachine sN inp (Bool ': 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 #

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 #

data Instr Branchable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Branchable repr where

Class Failable

class Failable (repr :: ReprInstr) where Source #

Methods

fail :: [ErrorItem (InputToken inp)] -> repr inp vs ('Succ es) a Source #

popFail :: repr inp vs es a -> repr inp vs ('Succ es) a Source #

catchFail :: repr inp vs ('Succ es) a -> repr inp (Cursor inp ': vs) es a -> repr inp vs es a Source #

Instances

Instances details
Failable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

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

Failable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

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

catchFail :: forall inp (vs :: [Type]) (es :: Peano) a. ViewMachine sN inp vs ('Succ es) a -> ViewMachine sN inp (Cursor inp ': vs) es a -> ViewMachine sN 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 #

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 #

data Instr Failable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Failable repr where

Class Inputable

class Inputable (repr :: ReprInstr) where Source #

Methods

loadInput :: repr inp vs es a -> repr inp (Cursor inp ': vs) es a Source #

pushInput :: repr inp (Cursor inp ': vs) es a -> repr inp vs es a Source #

Instances

Instances details
Inputable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

Inputable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

pushInput :: forall inp (vs :: [Type]) (es :: Peano) a. ViewMachine sN inp (Cursor inp ': vs) es a -> ViewMachine sN inp 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 #

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 #

data Instr Inputable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Inputable repr where

Class Joinable

class Joinable (repr :: ReprInstr) where Source #

Methods

defJoin :: LetName v -> repr inp (v ': vs) es a -> repr inp vs es a -> repr inp vs es a Source #

refJoin :: LetName v -> repr inp (v ': vs) es a Source #

Instances

Instances details
Joinable Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

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

ShowLetName sN Name => Joinable (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

refJoin :: forall v inp (vs :: [Type]) (es :: Peano) a. LetName v -> ViewMachine sN inp (v ': vs) 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 #

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 #

data Instr Joinable repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr Joinable repr where

Class Readable

class Readable (tok :: Type) (repr :: ReprInstr) where Source #

Methods

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

Instances

Instances details
Readable Char Gen Source # 
Instance details

Defined in Symantic.Parser.Machine.Generate

Methods

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

Readable tok (ViewMachine sN) Source # 
Instance details

Defined in Symantic.Parser.Machine.View

Methods

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

(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 #

(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 #

data Instr (Readable tok) repr Source # 
Instance details

Defined in Symantic.Parser.Machine.Optimize

data Instr (Readable tok) repr where