| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Symantic.Parser.Machine.Generate
Synopsis
- genCode :: TermInstr a -> CodeQ a
- data Gen inp vs es a = Gen {
- minHorizon :: Map Name Horizon -> Horizon
- unGen :: GenCtx inp vs es a -> CodeQ (Either (ParsingError inp) a)
- data ParsingError inp = ParsingErrorStandard {
- parsingErrorOffset :: Offset
- parsingErrorUnexpected :: Maybe (InputToken inp)
- parsingErrorExpecting :: Set (ErrorItem (InputToken inp))
- type Offset = Int
- type Horizon = Offset
- type Cont inp v a = Cursor inp -> [ErrorItem (InputToken inp)] -> v -> Cursor inp -> Either (ParsingError inp) a
- type FailHandler inp a = Cursor inp -> Cursor inp -> [ErrorItem (InputToken inp)] -> Either (ParsingError inp) a
- generateCode :: 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)
- data GenCtx inp vs (es :: Peano) a = (Lift (InputToken inp), Cursorable (Cursor inp), Show (InputToken inp)) => GenCtx {
- valueStack :: ValueStack vs
- failStack :: FailStack inp a es
- retCode :: CodeQ (Cont inp a a)
- input :: CodeQ (Cursor inp)
- moreInput :: CodeQ (Cursor inp -> Bool)
- nextInput :: CodeQ (Cursor inp -> (# InputToken inp, Cursor inp #))
- farthestInput :: CodeQ (Cursor inp)
- farthestExpecting :: CodeQ [ErrorItem (InputToken inp)]
- checkedHorizon :: Offset
- minHorizonByName :: Map Name Offset
- data ValueStack vs where
- ValueStackEmpty :: ValueStack '[]
- ValueStackCons :: {..} -> ValueStack (v ': vs)
- data FailStack inp a es where
- FailStackEmpty :: FailStack inp a 'Zero
- FailStackCons :: {..} -> FailStack inp a ('Succ es)
- generateSuspend :: Gen inp (v ': vs) es a -> GenCtx inp vs es a -> CodeQ (Cont inp v a)
- generateResume :: CodeQ (Cont inp v a) -> Gen inp (v ': vs) es a
- checkHorizon :: Lift (InputToken inp) => Gen inp vs ('Succ es) a -> Gen inp vs ('Succ es) a
- checkToken :: forall inp vs es a. Ord (InputToken inp) => Lift (InputToken inp) => [ErrorItem (InputToken inp)] -> TermInstr (InputToken inp -> Bool) -> Gen inp (InputToken inp ': vs) ('Succ es) a -> Gen inp vs ('Succ es) a
Documentation
Type Gen
Generate the CodeQ parsing the input.
Constructors
| Gen | |
Fields
| |
Instances
| Joinable Gen Source # | |
| Inputable Gen Source # | |
| Failable Gen Source # | |
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 # | |
| Branchable Gen Source # | |
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 # | |
| Routinable Gen Source # | |
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 # | |
| Stackable Gen Source # | |
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 # | |
| Readable Char Gen Source # | |
Type ParsingError
data ParsingError inp Source #
Constructors
| ParsingErrorStandard | |
Fields
| |
Instances
| Show (InputToken inp) => Show (ParsingError inp) Source # | |
Defined in Symantic.Parser.Machine.Generate Methods showsPrec :: Int -> ParsingError inp -> ShowS # show :: ParsingError inp -> String # showList :: [ParsingError inp] -> ShowS # | |
Type Offset
Type Horizon
type Horizon = Offset Source #
Synthetized minimal input length
required for a successful parsing.
Used with checkedHorizon to factorize input length checks,
instead of checking the input length
one InputToken at a time at each read.
Type Cont
type Cont inp v a = Cursor inp -> [ErrorItem (InputToken inp)] -> v -> Cursor inp -> Either (ParsingError inp) a Source #
Type FailHandler
type FailHandler inp a = Cursor inp -> Cursor inp -> [ErrorItem (InputToken inp)] -> Either (ParsingError inp) a Source #
generateCode :: 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 #
( generates generateCode input mach)TemplateHaskell code
parsing the given input according to the given Machine.
Type GenCtx
data GenCtx inp vs (es :: Peano) a Source #
This is an inherited (top-down) context only present at compile-time, to build TemplateHaskell splices.
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 a es where Source #
Constructors
| FailStackEmpty :: FailStack inp a 'Zero | |
| FailStackCons | |
Fields
| |
generateSuspend :: Gen inp (v ': vs) es a -> GenCtx inp vs es a -> CodeQ (Cont inp v a) Source #
Generate a continuation to be called with generateResume,
used when call returns.
The return value is pushed on the valueStack.
generateResume :: CodeQ (Cont inp v a) -> Gen inp (v ': vs) es a Source #
Generate a call to the generateSuspend continuation.
Used when call returns.
checkHorizon :: Lift (InputToken inp) => Gen inp vs ('Succ es) a -> Gen inp vs ('Succ es) a Source #
checkToken :: forall inp vs es a. Ord (InputToken inp) => Lift (InputToken inp) => [ErrorItem (InputToken inp)] -> TermInstr (InputToken inp -> Bool) -> Gen inp (InputToken inp ': vs) ('Succ es) a -> Gen inp vs ('Succ es) a Source #