invertible-grammar-0.1.2: Invertible parsing combinators framework

Safe HaskellNone
LanguageHaskell2010

Data.InvertibleGrammar.Base

Synopsis

Documentation

data Grammar p a b where Source #

Representation of an invertible grammar -- a grammar that can be run either "forwards" and "backwards".

For a grammar Grammar p a b, running it forwards will take a value of type a and possibly produce a value of type b. Running it backwards will take a value of type b and possibly produce an a. If a value cannot be produced, an error message is generated.

As a common example, running a Grammar forwards corresponds to parsing and running backwards corresponds to prettyprinting.

That is, the grammar defines a partial isomorphism between two values.

Constructors

Iso :: (a -> b) -> (b -> a) -> Grammar p a b

Total isomorphism grammar.

PartialIso :: (a -> b) -> (b -> Either Mismatch a) -> Grammar p a b

Partial isomorphism. Use Flip to change the direction of partiality.

Flip :: Grammar p a b -> Grammar p b a

Flip forward and backward passes of an underlying grammar.

(:.:) :: Grammar p b c -> Grammar p a b -> Grammar p a c

Grammar composition.

(:<>:) :: Grammar p a b -> Grammar p a b -> Grammar p a b

Grammar alternation. Left operand is tried first.

Traverse :: Traversable f => Grammar p a b -> Grammar p (f a) (f b)

Application of a grammar on Traversable functor.

OnHead :: Grammar p a b -> Grammar p (a :- t) (b :- t)

Applicaiton of a grammar on stack head (first component of :-).

OnTail :: Grammar p a b -> Grammar p (h :- a) (h :- b)

Applicaiton of a grammar on stack tail (second component of :-).

Annotate :: Text -> Grammar p a b -> Grammar p a b

Application of a grammar inside a context of annotation, used for error messages.

Dive :: Grammar p a b -> Grammar p a b

Application of a grammar inside a context of a nested structure, used for error messages. E.g. JSON arrays.

Step :: Grammar p a a

Propagate logical position inside a nested structure. E.g. after each successfully matched element of a JSON array.

Locate :: Grammar p p p

Update the position of grammar monad from value on grammar's input or output on forward or backward pass, respectively. Used for error messages.

Instances
Category (Grammar p :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

id :: Grammar p a a #

(.) :: Grammar p b c -> Grammar p a b -> Grammar p a c #

Semigroup (Grammar p a b) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

(<>) :: Grammar p a b -> Grammar p a b -> Grammar p a b #

sconcat :: NonEmpty (Grammar p a b) -> Grammar p a b #

stimes :: Integral b0 => b0 -> Grammar p a b -> Grammar p a b #

data h :- t infixr 5 Source #

"Cons" pair of a heterogenous list or a stack with potentially polymophic tail. E.g. "first" :- 2 :- (3,4) :- t

Isomorphic to a tuple with two elments, but is much more convenient for nested pairs.

Constructors

h :- t infixr 5 
Instances
Bitraversable (:-) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a :- b) -> f (c :- d) #

Bifoldable (:-) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

bifold :: Monoid m => (m :- m) -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (a :- b) -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (a :- b) -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (a :- b) -> c #

Bifunctor (:-) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

bimap :: (a -> b) -> (c -> d) -> (a :- c) -> b :- d #

first :: (a -> b) -> (a :- c) -> b :- c #

second :: (b -> c) -> (a :- b) -> a :- c #

Functor ((:-) h) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

fmap :: (a -> b) -> (h :- a) -> h :- b #

(<$) :: a -> (h :- b) -> h :- a #

Foldable ((:-) h) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

fold :: Monoid m => (h :- m) -> m #

foldMap :: Monoid m => (a -> m) -> (h :- a) -> m #

foldr :: (a -> b -> b) -> b -> (h :- a) -> b #

foldr' :: (a -> b -> b) -> b -> (h :- a) -> b #

foldl :: (b -> a -> b) -> b -> (h :- a) -> b #

foldl' :: (b -> a -> b) -> b -> (h :- a) -> b #

foldr1 :: (a -> a -> a) -> (h :- a) -> a #

foldl1 :: (a -> a -> a) -> (h :- a) -> a #

toList :: (h :- a) -> [a] #

null :: (h :- a) -> Bool #

length :: (h :- a) -> Int #

elem :: Eq a => a -> (h :- a) -> Bool #

maximum :: Ord a => (h :- a) -> a #

minimum :: Ord a => (h :- a) -> a #

sum :: Num a => (h :- a) -> a #

product :: Num a => (h :- a) -> a #

Traversable ((:-) h) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

traverse :: Applicative f => (a -> f b) -> (h :- a) -> f (h :- b) #

sequenceA :: Applicative f => (h :- f a) -> f (h :- a) #

mapM :: Monad m => (a -> m b) -> (h :- a) -> m (h :- b) #

sequence :: Monad m => (h :- m a) -> m (h :- a) #

(Eq h, Eq t) => Eq (h :- t) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

(==) :: (h :- t) -> (h :- t) -> Bool #

(/=) :: (h :- t) -> (h :- t) -> Bool #

(Show h, Show t) => Show (h :- t) Source # 
Instance details

Defined in Data.InvertibleGrammar.Base

Methods

showsPrec :: Int -> (h :- t) -> ShowS #

show :: (h :- t) -> String #

showList :: [h :- t] -> ShowS #

forward :: Grammar p a b -> a -> ContextError (Propagation p) (GrammarError p) b Source #

Run Grammar forwards.

For Grammar p a b, given a value of type a tries to produce a value of type b, otherwise reports an error with position of type p.

backward :: Grammar p a b -> b -> ContextError (Propagation p) (GrammarError p) a Source #

Run Grammar backwards.

For Grammar p a b, given a value of type b tries to produce a value of type a, otherwise reports an error with position of type p.

data Mismatch Source #

Data type to encode mismatches during parsing or generation, kept abstract. Use expected and unexpected constructors to build a mismatch report.

expected :: Text -> Mismatch Source #

Construct a mismatch report with specified expectation. Can be appended to other expectations and unexpected reports to clarify a mismatch.

unexpected :: Text -> Mismatch Source #

Construct a mismatch report with information what occurred during the processing but was not expected.