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

Symantic.Parser.Grammar.Combinators

Synopsis

Class Applicable

class Applicable repr where Source #

This is like the usual Functor and Applicative type classes from the base package, but using (Haskell a) instead of just (a) to be able to use and pattern match on some usual terms of type (a) (like id) and thus apply some optimizations. (repr) , for "representation", is the usual tagless-final abstraction over the many semantics that this syntax (formed by the methods of type class like this one) will be interpreted.

Minimal complete definition

Nothing

Methods

(<$>) :: Haskell (a -> b) -> repr a -> repr b infixl 4 Source #

(a2b <$> ra) parses like (ra) but maps its returned value with (a2b).

(<&>) :: repr a -> Haskell (a -> b) -> repr b infixl 4 Source #

Like <$> but with its arguments flip-ped.

(<$) :: Haskell a -> repr b -> repr a infixl 4 Source #

(a <$ rb) parses like (rb) but discards its returned value by replacing it with (a).

($>) :: repr a -> Haskell b -> repr b infixl 4 Source #

(ra $> b) parses like (ra) but discards its returned value by replacing it with (b).

pure :: Haskell a -> repr a Source #

(pure a) parses the empty string, always succeeding in returning (a).

pure :: Liftable repr => Applicable (Output repr) => Haskell a -> repr a Source #

(pure a) parses the empty string, always succeeding in returning (a).

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

(ra2b <*> ra) parses sequentially (ra2b) and then (ra), and returns the application of the function returned by (ra2b) to the value returned by (ra).

(<*>) :: Liftable2 repr => Applicable (Output repr) => repr (a -> b) -> repr a -> repr b infixl 4 Source #

(ra2b <*> ra) parses sequentially (ra2b) and then (ra), and returns the application of the function returned by (ra2b) to the value returned by (ra).

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

(liftA2 a2b2c ra rb) parses sequentially (ra) and then (rb), and returns the application of (a2b2c) to the values returned by those parsers.

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

(ra <* rb) parses sequentially (ra) and then (rb), and returns like (ra), discarding the return value of (rb).

(*>) :: repr a -> repr b -> repr b infixl 4 Source #

(ra *> rb) parses sequentially (ra) and then (rb), and returns like (rb), discarding the return value of (ra).

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

Like <*> but with its arguments flip-ped.

Instances

Instances details
Applicable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Applicable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Methods

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

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

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

($>) :: DumpComb a -> Haskell b -> DumpComb b Source #

pure :: Haskell a -> DumpComb a Source #

(<*>) :: DumpComb (a -> b) -> DumpComb a -> DumpComb b Source #

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

(<*) :: DumpComb a -> DumpComb b -> DumpComb a Source #

(*>) :: DumpComb a -> DumpComb b -> DumpComb b Source #

(<**>) :: DumpComb a -> DumpComb (a -> b) -> DumpComb b Source #

Applicable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

(<$>) :: Haskell (a -> b) -> Comb repr a -> Comb repr b Source #

(<&>) :: Comb repr a -> Haskell (a -> b) -> Comb repr b Source #

(<$) :: Haskell a -> Comb repr b -> Comb repr a Source #

($>) :: Comb repr a -> Haskell b -> Comb repr b Source #

pure :: Haskell a -> Comb repr a Source #

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

liftA2 :: Haskell (a -> b -> c) -> Comb repr a -> Comb repr b -> Comb repr c Source #

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

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

(<**>) :: Comb repr a -> Comb repr (a -> b) -> Comb repr 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 #

Applicable repr => Applicable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

(<$>) :: Haskell (a -> b) -> CleanDefs letName repr a -> CleanDefs letName repr b Source #

(<&>) :: CleanDefs letName repr a -> Haskell (a -> b) -> CleanDefs letName repr b Source #

(<$) :: Haskell a -> CleanDefs letName repr b -> CleanDefs letName repr a Source #

($>) :: CleanDefs letName repr a -> Haskell b -> CleanDefs letName repr b Source #

pure :: Haskell a -> CleanDefs letName repr a Source #

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

liftA2 :: Haskell (a -> b -> c) -> CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr c Source #

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

(*>) :: CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr b Source #

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

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Applicable repr) => Applicable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

(<$>) :: Haskell (a -> b) -> ObserveSharing letName repr a -> ObserveSharing letName repr b Source #

(<&>) :: ObserveSharing letName repr a -> Haskell (a -> b) -> ObserveSharing letName repr b Source #

(<$) :: Haskell a -> ObserveSharing letName repr b -> ObserveSharing letName repr a Source #

($>) :: ObserveSharing letName repr a -> Haskell b -> ObserveSharing letName repr b Source #

pure :: Haskell a -> ObserveSharing letName repr a Source #

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

liftA2 :: Haskell (a -> b -> c) -> ObserveSharing letName repr a -> ObserveSharing letName repr b -> ObserveSharing letName repr c Source #

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

(*>) :: ObserveSharing letName repr a -> ObserveSharing letName repr b -> ObserveSharing letName repr b Source #

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

Applicable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

(<$>) :: Haskell (a -> b) -> OptimizeComb letName repr a -> OptimizeComb letName repr b Source #

(<&>) :: OptimizeComb letName repr a -> Haskell (a -> b) -> OptimizeComb letName repr b Source #

(<$) :: Haskell a -> OptimizeComb letName repr b -> OptimizeComb letName repr a Source #

($>) :: OptimizeComb letName repr a -> Haskell b -> OptimizeComb letName repr b Source #

pure :: Haskell a -> OptimizeComb letName repr a Source #

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

liftA2 :: Haskell (a -> b -> c) -> OptimizeComb letName repr a -> OptimizeComb letName repr b -> OptimizeComb letName repr c Source #

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

(*>) :: OptimizeComb letName repr a -> OptimizeComb letName repr b -> OptimizeComb letName repr b Source #

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

Class Alternable

class Alternable repr where Source #

Minimal complete definition

Nothing

Methods

(<|>) :: repr a -> repr a -> repr a infixl 3 Source #

(rl <|> rr) parses (rl) and return its return value or, if it fails, parses (rr) from where (rl) has left the input stream, and returns its return value.

empty :: repr a Source #

(empty) parses nothing, always failing to return a value.

try :: repr a -> repr a Source #

(try ra) records the input stream position, then parses like (ra) and either returns its value it it succeeds or fails if it fails but with a reset of the input stream to the recorded position. Generally used on the first alternative: (try rl <|> rr).

(<|>) :: Liftable2 repr => Alternable (Output repr) => repr a -> repr a -> repr a infixl 3 Source #

(rl <|> rr) parses (rl) and return its return value or, if it fails, parses (rr) from where (rl) has left the input stream, and returns its return value.

empty :: Liftable repr => Alternable (Output repr) => repr a Source #

(empty) parses nothing, always failing to return a value.

try :: Liftable1 repr => Alternable (Output repr) => repr a -> repr a Source #

(try ra) records the input stream position, then parses like (ra) and either returns its value it it succeeds or fails if it fails but with a reset of the input stream to the recorded position. Generally used on the first alternative: (try rl <|> rr).

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

Like (<|>) but with different returning types for the alternatives, and a return value wrapped in an Either accordingly.

Instances

Instances details
Alternable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Alternable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Alternable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

empty :: Comb repr a Source #

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

(<+>) :: (Applicable (Comb repr), Alternable (Comb repr)) => Comb repr a -> Comb repr b -> Comb repr (Either a b) 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 #

Alternable repr => Alternable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

(<|>) :: CleanDefs letName repr a -> CleanDefs letName repr a -> CleanDefs letName repr a Source #

empty :: CleanDefs letName repr a Source #

try :: CleanDefs letName repr a -> CleanDefs letName repr a Source #

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

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Alternable repr) => Alternable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

(<|>) :: ObserveSharing letName repr a -> ObserveSharing letName repr a -> ObserveSharing letName repr a Source #

empty :: ObserveSharing letName repr a Source #

try :: ObserveSharing letName repr a -> ObserveSharing letName repr a Source #

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

Alternable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

(<|>) :: OptimizeComb letName repr a -> OptimizeComb letName repr a -> OptimizeComb letName repr a Source #

empty :: OptimizeComb letName repr a Source #

try :: OptimizeComb letName repr a -> OptimizeComb letName repr a Source #

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

optionally :: Applicable repr => Alternable repr => repr a -> Haskell b -> repr b Source #

optional :: Applicable repr => Alternable repr => repr a -> repr () Source #

option :: Applicable repr => Alternable repr => Haskell a -> repr a -> repr a Source #

choice :: Alternable repr => [repr a] -> repr a Source #

maybeP :: Applicable repr => Alternable repr => repr a -> repr (Maybe a) Source #

manyTill :: Applicable repr => Alternable repr => repr a -> repr b -> repr [a] Source #

Class Selectable

class Selectable repr where Source #

Minimal complete definition

Nothing

Methods

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

branch :: Liftable3 repr => Selectable (Output repr) => repr (Either a b) -> repr (a -> c) -> repr (b -> c) -> repr c Source #

Instances

Instances details
Selectable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

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

Selectable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Methods

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

Selectable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

branch :: Comb repr (Either a b) -> Comb repr (a -> c) -> Comb repr (b -> c) -> Comb repr c 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 #

Selectable repr => Selectable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Selectable repr) => Selectable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

Selectable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

Class Matchable

class Matchable repr where Source #

Minimal complete definition

Nothing

Methods

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

conditional :: Unliftable repr => Liftable2 repr => Matchable (Output repr) => Eq a => [Haskell (a -> Bool)] -> [repr b] -> repr a -> repr b -> repr b Source #

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

Instances

Instances details
Matchable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

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

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

Matchable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Methods

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

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

Matchable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

match :: Eq a => [Haskell a] -> Comb repr a -> (Haskell a -> Comb repr b) -> Comb repr b -> Comb repr b 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 #

Matchable repr => Matchable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

conditional :: Eq a => [Haskell (a -> Bool)] -> [CleanDefs letName repr b] -> CleanDefs letName repr a -> CleanDefs letName repr b -> CleanDefs letName repr b Source #

match :: Eq a => [Haskell a] -> CleanDefs letName repr a -> (Haskell a -> CleanDefs letName repr b) -> CleanDefs letName repr b -> CleanDefs letName repr b Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Matchable repr) => Matchable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

conditional :: Eq a => [Haskell (a -> Bool)] -> [ObserveSharing letName repr b] -> ObserveSharing letName repr a -> ObserveSharing letName repr b -> ObserveSharing letName repr b Source #

match :: Eq a => [Haskell a] -> ObserveSharing letName repr a -> (Haskell a -> ObserveSharing letName repr b) -> ObserveSharing letName repr b -> ObserveSharing letName repr b Source #

Matchable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

conditional :: Eq a => [Haskell (a -> Bool)] -> [OptimizeComb letName repr b] -> OptimizeComb letName repr a -> OptimizeComb letName repr b -> OptimizeComb letName repr b Source #

match :: Eq a => [Haskell a] -> OptimizeComb letName repr a -> (Haskell a -> OptimizeComb letName repr b) -> OptimizeComb letName repr b -> OptimizeComb letName repr b Source #

Class Foldable

class Foldable repr where Source #

Minimal complete definition

Nothing

Methods

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

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

chainPre :: Applicable repr => Alternable repr => repr (a -> a) -> repr a -> repr a Source #

chainPost :: Applicable repr => Alternable repr => repr a -> repr (a -> a) -> repr a Source #

Instances

Instances details
Foldable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

chainPre :: WriteComb (a -> a) -> WriteComb a -> WriteComb a Source #

chainPost :: WriteComb a -> WriteComb (a -> a) -> WriteComb a Source #

Foldable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Methods

chainPre :: DumpComb (a -> a) -> DumpComb a -> DumpComb a Source #

chainPost :: DumpComb a -> DumpComb (a -> a) -> DumpComb a Source #

Foldable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

chainPost :: Comb repr a -> Comb repr (a -> a) -> Comb repr a 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 #

Foldable repr => Foldable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

chainPre :: CleanDefs letName repr (a -> a) -> CleanDefs letName repr a -> CleanDefs letName repr a Source #

chainPost :: CleanDefs letName repr a -> CleanDefs letName repr (a -> a) -> CleanDefs letName repr a Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Foldable repr, Applicable repr, Alternable repr) => Foldable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

chainPre :: ObserveSharing letName repr (a -> a) -> ObserveSharing letName repr a -> ObserveSharing letName repr a Source #

chainPost :: ObserveSharing letName repr a -> ObserveSharing letName repr (a -> a) -> ObserveSharing letName repr a Source #

Foldable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

chainPre :: OptimizeComb letName repr (a -> a) -> OptimizeComb letName repr a -> OptimizeComb letName repr a Source #

chainPost :: OptimizeComb letName repr a -> OptimizeComb letName repr (a -> a) -> OptimizeComb letName repr a Source #

Class Satisfiable

class Satisfiable repr tok where Source #

Minimal complete definition

Nothing

Methods

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

satisfy :: Liftable repr => Satisfiable (Output repr) tok => [ErrorItem tok] -> Haskell (tok -> Bool) -> repr tok Source #

Instances

Instances details
Satisfiable WriteComb tok Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

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

Satisfiable DumpComb tok Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Methods

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

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

Defined in Symantic.Parser.Grammar.Optimize

Methods

satisfy :: [ErrorItem tok] -> Haskell (tok -> Bool) -> Comb repr tok 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 #

Satisfiable repr tok => Satisfiable (CleanDefs letName repr) tok Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

satisfy :: [ErrorItem tok] -> Haskell (tok -> Bool) -> CleanDefs letName repr tok Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Satisfiable repr tok) => Satisfiable (ObserveSharing letName repr) tok Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

satisfy :: [ErrorItem tok] -> Haskell (tok -> Bool) -> ObserveSharing letName repr tok Source #

Satisfiable repr tok => Satisfiable (OptimizeComb letName repr) tok Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

satisfy :: [ErrorItem tok] -> Haskell (tok -> Bool) -> OptimizeComb letName repr tok Source #

Type ErrorItem

data ErrorItem tok Source #

Instances

Instances details
Lift tok => Lift (ErrorItem tok :: Type) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Combinators

Methods

lift :: Quote m => ErrorItem tok -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ErrorItem tok -> Code m (ErrorItem tok) #

Eq tok => Eq (ErrorItem tok) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Combinators

Methods

(==) :: ErrorItem tok -> ErrorItem tok -> Bool #

(/=) :: ErrorItem tok -> ErrorItem tok -> Bool #

Ord tok => Ord (ErrorItem tok) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Combinators

Methods

compare :: ErrorItem tok -> ErrorItem tok -> Ordering #

(<) :: ErrorItem tok -> ErrorItem tok -> Bool #

(<=) :: ErrorItem tok -> ErrorItem tok -> Bool #

(>) :: ErrorItem tok -> ErrorItem tok -> Bool #

(>=) :: ErrorItem tok -> ErrorItem tok -> Bool #

max :: ErrorItem tok -> ErrorItem tok -> ErrorItem tok #

min :: ErrorItem tok -> ErrorItem tok -> ErrorItem tok #

Show tok => Show (ErrorItem tok) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Combinators

Methods

showsPrec :: Int -> ErrorItem tok -> ShowS #

show :: ErrorItem tok -> String #

showList :: [ErrorItem tok] -> ShowS #

Class Lookable

class Lookable repr where Source #

Minimal complete definition

Nothing

Methods

look :: repr a -> repr a Source #

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

look :: Liftable1 repr => Lookable (Output repr) => repr a -> repr a Source #

negLook :: Liftable1 repr => Lookable (Output repr) => repr a -> repr () Source #

eof :: repr () Source #

eof :: Liftable repr => Lookable (Output repr) => repr () Source #

Instances

Instances details
Lookable WriteComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Lookable DumpComb Source # 
Instance details

Defined in Symantic.Parser.Grammar.Dump

Lookable (Comb repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

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

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

eof :: Comb repr () 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 #

Lookable repr => Lookable (CleanDefs letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

look :: CleanDefs letName repr a -> CleanDefs letName repr a Source #

negLook :: CleanDefs letName repr a -> CleanDefs letName repr () Source #

eof :: CleanDefs letName repr () Source #

(Letable letName repr, MakeLetName letName, Eq letName, Hashable letName, Lookable repr) => Lookable (ObserveSharing letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

look :: ObserveSharing letName repr a -> ObserveSharing letName repr a Source #

negLook :: ObserveSharing letName repr a -> ObserveSharing letName repr () Source #

eof :: ObserveSharing letName repr () Source #

Lookable (OptimizeComb letName repr) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

Methods

look :: OptimizeComb letName repr a -> OptimizeComb letName repr a Source #

negLook :: OptimizeComb letName repr a -> OptimizeComb letName repr () Source #

eof :: OptimizeComb letName repr () Source #

(<:>) :: Applicable repr => repr a -> repr [a] -> repr [a] infixl 4 Source #

sequence :: Applicable repr => [repr a] -> repr [a] Source #

traverse :: Applicable repr => (a -> repr b) -> [a] -> repr [b] Source #

repeat :: Applicable repr => Int -> repr a -> repr [a] Source #

between :: Applicable repr => repr o -> repr c -> repr a -> repr a Source #

string :: Applicable repr => Satisfiable repr Char => [Char] -> repr [Char] Source #

noneOf :: Lift tok => Eq tok => Satisfiable repr tok => [tok] -> repr tok Source #

ofChars :: Lift tok => Eq tok => [tok] -> CodeQ tok -> CodeQ Bool Source #

more :: Applicable repr => Satisfiable repr Char => Lookable repr => repr () Source #

char :: Applicable repr => Satisfiable repr Char => Char -> repr Char Source #

token :: Lift tok => Eq tok => Applicable repr => Satisfiable repr tok => tok -> repr tok Source #

tokens :: Lift tok => Eq tok => Applicable repr => Alternable repr => Satisfiable repr tok => [tok] -> repr [tok] Source #

item :: Satisfiable repr tok => repr tok Source #

void :: Applicable repr => repr a -> repr () Source #

unit :: Applicable repr => repr () Source #

pfoldr :: Applicable repr => Foldable repr => Haskell (a -> b -> b) -> Haskell b -> repr a -> repr b Source #

pfoldr1 :: Applicable repr => Foldable repr => Haskell (a -> b -> b) -> Haskell b -> repr a -> repr b Source #

pfoldl :: Applicable repr => Foldable repr => Haskell (b -> a -> b) -> Haskell b -> repr a -> repr b Source #

pfoldl1 :: Applicable repr => Foldable repr => Haskell (b -> a -> b) -> Haskell b -> repr a -> repr b Source #

chainl1' :: Applicable repr => Foldable repr => Haskell (a -> b) -> repr a -> repr (b -> a -> b) -> repr b Source #

chainl1 :: Applicable repr => Foldable repr => repr a -> repr (a -> a -> a) -> repr a Source #

chainl :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr (a -> a -> a) -> Haskell a -> repr a Source #

many :: Applicable repr => Foldable repr => repr a -> repr [a] Source #

manyN :: Applicable repr => Foldable repr => Int -> repr a -> repr [a] Source #

some :: Applicable repr => Foldable repr => repr a -> repr [a] Source #

skipMany :: Applicable repr => Foldable repr => repr a -> repr () Source #

skipManyN :: Applicable repr => Foldable repr => Int -> repr a -> repr () Source #

skipSome :: Applicable repr => Foldable repr => repr a -> repr () Source #

sepBy :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #

sepBy1 :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #

endBy :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #

endBy1 :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #

sepEndBy :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #

sepEndBy1 :: Applicable repr => Alternable repr => Foldable repr => repr a -> repr b -> repr [a] Source #