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

Symantic.Parser.Machine.Instructions

Synopsis

Type Instr

data Instr input valueStack (failStack :: Peano) returnValue where Source #

Instructions for the Machine.

Constructors

Push :: InstrPure v -> Instr inp (v ': vs) es ret -> Instr inp vs es ret

(Push x k) pushes (x) on the valueStack and continues with the next Instruction (k).

Pop :: Instr inp vs es ret -> Instr inp (v ': vs) es ret

(Pop k) pushes (x) on the valueStack.

LiftI2 :: InstrPure (x -> y -> z) -> Instr inp (z ': vs) es ret -> Instr inp (y ': (x ': vs)) es ret

(LiftI2 f k) pops two values from the valueStack, and pushes the result of (f) applied to them.

Fail :: [ErrorItem (InputToken inp)] -> Instr inp vs ('Succ es) ret

(Fail) raises an error from the failStack.

PopFail :: Instr inp vs es ret -> Instr inp vs ('Succ es) ret

(PopFail k) removes a FailHandler from the failStack and continues with the next Instruction (k).

CatchFail :: Instr inp vs ('Succ es) ret -> Instr inp (Cursor inp ': vs) es ret -> Instr inp vs es ret

(CatchFail l r) tries the (l) Instruction in a new failure scope such that if (l) raises a failure, it is caught, then the input is pushed as it was before trying (l) on the valueStack, and the control flow goes on with the (r) Instruction.

LoadInput :: Instr inp vs es r -> Instr inp (Cursor inp ': vs) es r

(LoadInput k) removes the input from the valueStack and continues with the next Instruction (k) using that input.

PushInput :: Instr inp (Cursor inp ': vs) es ret -> Instr inp vs es ret

(PushInput k) pushes the input (inp) on the valueStack and continues with the next Instruction (k).

Case :: Instr inp (x ': vs) es r -> Instr inp (y ': vs) es r -> Instr inp (Either x y ': vs) es r

(Case l r).

Swap :: Instr inp (x ': (y ': vs)) es r -> Instr inp (y ': (x ': vs)) es r

(Swap k) pops two values on the valueStack, pushes the first popped-out, then the second, and continues with the next Instruction (k).

Choices :: [InstrPure (v -> Bool)] -> [Instr inp vs es ret] -> Instr inp vs es ret -> Instr inp (v ': vs) es ret

(Choices ps bs d).

Subroutine :: LetName v -> Instr inp '[] ('Succ 'Zero) v -> Instr inp vs ('Succ es) ret -> Instr inp vs ('Succ es) ret

(Subroutine n v k) binds the LetName (n) to the Instr'uctions (v), Calls (n) and continues with the next Instruction (k).

Jump :: LetName ret -> Instr inp '[] ('Succ es) ret

(Jump n k) pass the control-flow to the Subroutine named (n).

Call :: LetName v -> Instr inp (v ': vs) ('Succ es) ret -> Instr inp vs ('Succ es) ret

(Call n k) pass the control-flow to the Subroutine named (n), and when it Returns, continues with the next Instruction (k).

Ret :: Instr inp '[ret] es ret

(Ret) returns the value stored in a singleton valueStack.

Read :: [ErrorItem (InputToken inp)] -> InstrPure (InputToken inp -> Bool) -> Instr inp (InputToken inp ': vs) ('Succ es) ret -> Instr inp vs ('Succ es) ret

(Read expected p k) reads a Char (c) from the input, if (p c) is True then continues with the next Instruction (k) on, otherwise Fail.

DefJoin :: LetName v -> Instr inp (v ': vs) es ret -> Instr inp vs es ret -> Instr inp vs es ret 
RefJoin :: LetName v -> Instr inp (v ': vs) es ret 

Instances

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

Defined in Symantic.Parser.Machine.Instructions

Methods

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

Type InstrPure

data InstrPure a where Source #

Constructors

InstrPureHaskell :: Haskell a -> InstrPure a 
InstrPureSameOffset :: Cursorable cur => InstrPure (cur -> cur -> Bool) 

Instances

Instances details
Trans InstrPure (CodeQ :: Type -> Type) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

trans :: InstrPure a -> CodeQ a Source #

Show (InstrPure a) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Type LetName

newtype LetName a Source #

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 Executable

type Executable repr = (Stackable repr, Branchable repr, Failable repr, Inputable repr, Routinable repr, Joinable repr) Source #

Class Stackable

class Stackable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

push :: InstrPure v -> repr inp (v ': vs) n ret -> repr inp vs n ret Source #

pop :: repr inp vs n ret -> repr inp (v ': vs) n ret Source #

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

swap :: repr inp (x ': (y ': vs)) n r -> repr inp (y ': (x ': vs)) n r Source #

Instances

Instances details
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 #

Stackable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

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

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

Class Branchable

class Branchable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

case_ :: repr inp (x ': vs) n r -> repr inp (y ': vs) n r -> repr inp (Either x y ': vs) n r Source #

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

Instances

Instances details
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 #

Branchable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

Class Failable

class Failable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

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

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

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

Instances

Instances details
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 #

Failable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

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

Class Inputable

class Inputable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

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

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

Instances

Instances details
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 #

Inputable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

Class Routinable

class Routinable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

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

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

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

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

Instances

Instances details
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 #

Routinable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

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

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

Class Joinable

class Joinable (repr :: Type -> [Type] -> Peano -> Type -> Type) where Source #

Methods

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

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

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 #

Joinable DumpInstr Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

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

Class Readable

class Readable (repr :: Type -> [Type] -> Peano -> Type -> Type) (tok :: Type) where Source #

Methods

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

Instances

Instances details
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 #

Readable DumpInstr inp Source # 
Instance details

Defined in Symantic.Parser.Machine.Dump

Methods

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

Type Peano

data Peano Source #

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

Constructors

Zero 
Succ Peano 

pattern Fmap :: InstrPure (x -> y) -> Instr inp (y ': xs) es ret -> Instr inp (x ': xs) es ret Source #

(Fmap f k).

pattern App :: Instr inp (y ': vs) es ret -> Instr inp (x ': ((x -> y) ': vs)) es ret Source #

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

pattern If :: Instr inp vs es ret -> Instr inp vs es ret -> Instr inp (Bool ': vs) es ret Source #

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

Type Machine

data Machine inp v Source #

Making the control-flow explicit.

Constructors

Machine 

Fields

Instances

Instances details
Letable Name (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

def :: Name -> Machine inp a -> Machine inp a Source #

ref :: Bool -> Name -> Machine inp a Source #

(Ord (InputToken inp), Cursorable (Cursor inp)) => Lookable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

look :: Machine inp a -> Machine inp a Source #

negLook :: Machine inp a -> Machine inp () Source #

eof :: Machine inp () Source #

Cursorable (Cursor inp) => Foldable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

chainPre :: Machine inp (a -> a) -> Machine inp a -> Machine inp a Source #

chainPost :: Machine inp a -> Machine inp (a -> a) -> Machine inp a Source #

Matchable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

conditional :: Eq a => [Haskell (a -> Bool)] -> [Machine inp b] -> Machine inp a -> Machine inp b -> Machine inp b Source #

match :: Eq a => [Haskell a] -> Machine inp a -> (Haskell a -> Machine inp b) -> Machine inp b -> Machine inp b Source #

Selectable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

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

Cursorable (Cursor inp) => Alternable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

(<|>) :: Machine inp a -> Machine inp a -> Machine inp a Source #

empty :: Machine inp a Source #

try :: Machine inp a -> Machine inp a Source #

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

Applicable (Machine inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

(<$>) :: Haskell (a -> b) -> Machine inp a -> Machine inp b Source #

(<&>) :: Machine inp a -> Haskell (a -> b) -> Machine inp b Source #

(<$) :: Haskell a -> Machine inp b -> Machine inp a Source #

($>) :: Machine inp a -> Haskell b -> Machine inp b Source #

pure :: Haskell a -> Machine inp a Source #

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

liftA2 :: Haskell (a -> b -> c) -> Machine inp a -> Machine inp b -> Machine inp c Source #

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

(*>) :: Machine inp a -> Machine inp b -> Machine inp b Source #

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

tok ~ InputToken inp => Satisfiable (Machine inp) tok Source # 
Instance details

Defined in Symantic.Parser.Machine.Instructions

Methods

satisfy :: [ErrorItem tok] -> Haskell (tok -> Bool) -> Machine inp tok Source #

runMachine :: forall inp v es repr. Executable repr => Readable repr (InputToken inp) => Machine inp v -> repr inp '[] ('Succ es) v Source #

failIfConsumed :: Cursorable (Cursor inp) => Instr inp vs ('Succ es) ret -> Instr 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.

makeJoin :: Instr inp (v ': vs) es ret -> (Instr inp (v ': vs) es ret -> Instr inp vs es ret) -> Instr inp vs es ret Source #

(makeJoin k f) factorizes (k) in (f), by introducing a DefJoin if necessary, and passing the corresponding RefJoin to (f), or (k) as is when factorizing is useless.