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

Symantic.Parser.Grammar.Combinators

Description

Semantic of the grammar combinators used to express parsers, in the convenient tagless-final encoding.

Synopsis

Type TermGrammar

Class Applicable

class Applicable repr where Source #

This is like the usual Functor and Applicative type classes from the base package, but using (TermGrammar 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

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

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

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

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

(<$) :: TermGrammar 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 -> TermGrammar b -> repr b infixl 4 Source #

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

pure :: TermGrammar a -> repr a Source #

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

pure :: Liftable repr => Applicable (Output repr) => TermGrammar 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 :: TermGrammar (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 (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

(<$>) :: TermGrammar (a -> b) -> WriteGrammar sN a -> WriteGrammar sN b Source #

(<&>) :: WriteGrammar sN a -> TermGrammar (a -> b) -> WriteGrammar sN b Source #

(<$) :: TermGrammar a -> WriteGrammar sN b -> WriteGrammar sN a Source #

($>) :: WriteGrammar sN a -> TermGrammar b -> WriteGrammar sN b Source #

pure :: TermGrammar a -> WriteGrammar sN a Source #

(<*>) :: WriteGrammar sN (a -> b) -> WriteGrammar sN a -> WriteGrammar sN b Source #

liftA2 :: TermGrammar (a -> b -> c) -> WriteGrammar sN a -> WriteGrammar sN b -> WriteGrammar sN c Source #

(<*) :: WriteGrammar sN a -> WriteGrammar sN b -> WriteGrammar sN a Source #

(*>) :: WriteGrammar sN a -> WriteGrammar sN b -> WriteGrammar sN b Source #

(<**>) :: WriteGrammar sN a -> WriteGrammar sN (a -> b) -> WriteGrammar sN b Source #

Applicable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

(<$>) :: TermGrammar (a -> b) -> ViewGrammar sN a -> ViewGrammar sN b Source #

(<&>) :: ViewGrammar sN a -> TermGrammar (a -> b) -> ViewGrammar sN b Source #

(<$) :: TermGrammar a -> ViewGrammar sN b -> ViewGrammar sN a Source #

($>) :: ViewGrammar sN a -> TermGrammar b -> ViewGrammar sN b Source #

pure :: TermGrammar a -> ViewGrammar sN a Source #

(<*>) :: ViewGrammar sN (a -> b) -> ViewGrammar sN a -> ViewGrammar sN b Source #

liftA2 :: TermGrammar (a -> b -> c) -> ViewGrammar sN a -> ViewGrammar sN b -> ViewGrammar sN c Source #

(<*) :: ViewGrammar sN a -> ViewGrammar sN b -> ViewGrammar sN a Source #

(*>) :: ViewGrammar sN a -> ViewGrammar sN b -> ViewGrammar sN b Source #

(<**>) :: ViewGrammar sN a -> ViewGrammar sN (a -> b) -> ViewGrammar sN 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 #

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

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

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

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

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

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

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

liftA2 :: TermGrammar (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

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

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

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

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

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

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

liftA2 :: TermGrammar (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 #

Stackable repr => Applicable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

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

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

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

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

pure :: TermGrammar a -> Program repr inp a Source #

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

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

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

(*>) :: Program repr inp a -> Program repr inp b -> Program repr inp b Source #

(<**>) :: Program repr inp a -> Program repr inp (a -> b) -> Program repr inp b 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 Applicable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Applicable repr where

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 (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Alternable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

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

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 #

(Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Stackable repr) => Alternable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

(<|>) :: Program repr inp a -> Program repr inp a -> Program repr inp a Source #

empty :: Program repr inp a Source #

try :: Program repr inp a -> Program repr inp a Source #

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

data Comb Alternable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Alternable repr where

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

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

option :: Applicable repr => Alternable repr => TermGrammar 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 (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

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

Selectable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

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

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 #

(Branchable repr, Joinable repr, Stackable repr) => Selectable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

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

data Comb Selectable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Selectable repr where

Class Matchable

class Matchable repr where Source #

Minimal complete definition

Nothing

Methods

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

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

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

Instances

Instances details
Matchable (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

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

match :: Eq a => WriteGrammar sN a -> [TermGrammar a] -> (TermGrammar a -> WriteGrammar sN b) -> WriteGrammar sN b -> WriteGrammar sN b Source #

Matchable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

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

match :: Eq a => ViewGrammar sN a -> [TermGrammar a] -> (TermGrammar a -> ViewGrammar sN b) -> ViewGrammar sN b -> ViewGrammar sN b 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 #

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

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

match :: Eq a => CleanDefs letName repr a -> [TermGrammar a] -> (TermGrammar 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 => ObserveSharing letName repr a -> [TermGrammar (a -> Bool)] -> [ObserveSharing letName repr b] -> ObserveSharing letName repr b -> ObserveSharing letName repr b Source #

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

(Branchable repr, Joinable repr) => Matchable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

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

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

data Comb Matchable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Matchable repr where

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 (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

chainPre :: WriteGrammar sN (a -> a) -> WriteGrammar sN a -> WriteGrammar sN a Source #

chainPost :: WriteGrammar sN a -> WriteGrammar sN (a -> a) -> WriteGrammar sN a Source #

Foldable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

chainPre :: ViewGrammar sN (a -> a) -> ViewGrammar sN a -> ViewGrammar sN a Source #

chainPost :: ViewGrammar sN a -> ViewGrammar sN (a -> a) -> ViewGrammar sN a 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 #

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 #

(Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Stackable repr) => Foldable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

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

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

data Comb Foldable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Foldable repr where

Class Satisfiable

class Satisfiable tok repr where Source #

Minimal complete definition

Nothing

Methods

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

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

item :: repr tok Source #

Instances

Instances details
Satisfiable tok (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Methods

satisfy :: [ErrorItem tok] -> TermGrammar (tok -> Bool) -> WriteGrammar sN tok Source #

item :: WriteGrammar sN tok Source #

Satisfiable tok (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

satisfy :: [ErrorItem tok] -> TermGrammar (tok -> Bool) -> ViewGrammar sN tok Source #

item :: ViewGrammar sN tok 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 #

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

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

item :: CleanDefs letName repr tok Source #

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

Defined in Symantic.Parser.Grammar.ObserveSharing

Methods

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

item :: ObserveSharing letName repr tok Source #

(tok ~ InputToken inp, Readable tok repr, Typeable tok) => Satisfiable tok (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

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

item :: Program repr inp tok 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 #

data Comb (Satisfiable tok) repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb (Satisfiable tok) repr where

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 (WriteGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.Write

Lookable (ViewGrammar sN) Source # 
Instance details

Defined in Symantic.Parser.Grammar.View

Methods

look :: ViewGrammar sN a -> ViewGrammar sN a Source #

negLook :: ViewGrammar sN a -> ViewGrammar sN () Source #

eof :: ViewGrammar sN () 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 #

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 #

(Ord (InputToken inp), Cursorable (Cursor inp), Branchable repr, Failable repr, Inputable repr, Joinable repr, Readable (InputToken inp) repr, Typeable (InputToken inp), Stackable repr) => Lookable (Program repr inp) Source # 
Instance details

Defined in Symantic.Parser.Machine.Program

Methods

look :: Program repr inp a -> Program repr inp a Source #

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

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

data Comb Lookable repr Source # 
Instance details

Defined in Symantic.Parser.Grammar.Optimize

data Comb Lookable repr where

(<:>) :: 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 => Alternable repr => Satisfiable Char repr => [Char] -> repr [Char] Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

chainl1' :: Applicable repr => Foldable repr => TermGrammar (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) -> TermGrammar 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 #