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

Symantic.Parser.Grammar.Optimize

Description

Bottom-up optimization of Combinators, reexamining downward as needed after each optimization.

Synopsis

Type OptimizeGrammar

optimizeGrammar :: Trans (SomeComb repr) repr => SomeComb repr a -> repr a Source #

Data family Comb

data family Comb (comb :: ReprComb -> Constraint) (repr :: ReprComb) :: ReprComb infixl 4 :*>:, :<*:, :<*>:infixl 3 :<|>: Source #

Combinators of the Grammar. This is an extensible data-type.

Instances

Instances details
Letable letName repr => Trans (Comb (Letable letName) repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb (Letable letName) repr a -> repr a Source #

Lookable repr => Trans (Comb Lookable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Lookable repr a -> repr a Source #

Satisfiable tok repr => Trans (Comb (Satisfiable tok) repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb (Satisfiable tok) repr a -> repr a Source #

Foldable repr => Trans (Comb Foldable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Foldable repr a -> repr a Source #

Matchable repr => Trans (Comb Matchable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Matchable repr a -> repr a Source #

Selectable repr => Trans (Comb Selectable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Selectable repr a -> repr a Source #

Alternable repr => Trans (Comb Alternable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Alternable repr a -> repr a Source #

Applicable repr => Trans (Comb Applicable repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: Comb Applicable repr a -> repr a Source #

data Comb Lookable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Lookable repr where
data Comb Foldable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Foldable repr where
data Comb Matchable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Matchable repr where
data Comb Selectable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Selectable repr where
data Comb Alternable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Alternable repr where
data Comb Applicable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Applicable repr where
data Comb (Letable letName) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb (Letable letName) repr where
data Comb (Satisfiable tok) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb (Satisfiable tok) repr where

pattern Comb :: Typeable comb => Comb comb repr a -> SomeComb repr a Source #

Convenient utility to pattern-match a SomeComb.

Type ReprComb

Type SomeComb

data SomeComb repr a Source #

Some Combinator existentialized over the actual combinator symantic class. Useful to handle a list of Combinators without requiring impredicative quantification. Must be used by pattern-matching on the SomeComb data-constructor, to bring the constraints in scope.

The optimizations are directly applied within it, to avoid introducing an extra newtype, this also give a more comprehensible code.

Constructors

(Trans (Comb comb repr) repr, Typeable comb) => SomeComb (Comb comb repr a) 

Instances

Instances details
(Letable letName repr, Typeable letName) => Letable letName (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

def :: letName -> SomeComb repr a -> SomeComb repr a Source #

ref :: Bool -> letName -> SomeComb repr a Source #

(Satisfiable tok repr, Typeable tok) => Satisfiable tok (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

item :: SomeComb repr tok Source #

(Alternable repr, Applicable repr, Lookable repr, Selectable repr, Matchable repr) => Lookable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

look :: SomeComb repr a -> SomeComb repr a Source #

negLook :: SomeComb repr a -> SomeComb repr () Source #

eof :: SomeComb repr () Source #

Foldable repr => Foldable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

chainPre :: SomeComb repr (a -> a) -> SomeComb repr a -> SomeComb repr a Source #

chainPost :: SomeComb repr a -> SomeComb repr (a -> a) -> SomeComb repr a Source #

(Applicable repr, Alternable repr, Lookable repr, Selectable repr, Matchable repr) => Matchable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

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

(Applicable repr, Alternable repr, Lookable repr, Selectable repr, Matchable repr) => Selectable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

(Alternable repr, Applicable repr, Lookable repr, Matchable repr, Selectable repr) => Alternable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

(<|>) :: SomeComb repr a -> SomeComb repr a -> SomeComb repr a Source #

empty :: SomeComb repr a Source #

try :: SomeComb repr a -> SomeComb repr a Source #

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

(Applicable repr, Alternable repr, Lookable repr, Matchable repr, Selectable repr) => Applicable (SomeComb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

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

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

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

pure :: TermGrammar a -> SomeComb repr a Source #

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

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

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

(*>) :: SomeComb repr a -> SomeComb repr b -> SomeComb repr b Source #

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

Trans (SomeComb repr) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

trans :: SomeComb repr a -> repr a Source #

unSomeComb :: forall comb repr a. Typeable comb => SomeComb repr a -> Maybe (Comb comb repr a) Source #

(unSomeComb c :: Maybe (Comb comb repr a)) extract the data-constructor from the given SomeComb iif. it belongs to the (Comb comb repr a) data-instance.

pattern (:<$>:) :: TermGrammar (a -> b) -> SomeComb repr a -> Comb Applicable repr b Source #

pattern (:$>:) :: SomeComb repr a -> TermGrammar b -> Comb Applicable repr b Source #

Orphan instances

MakeLetName Name Source # 
Instance details