Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- data Grammar p a b where
- Iso :: (a -> b) -> (b -> a) -> Grammar p a b
- PartialIso :: (a -> b) -> (b -> Either Mismatch a) -> Grammar p a b
- Flip :: Grammar p a b -> Grammar p b a
- (:.:) :: Grammar p b c -> Grammar p a b -> Grammar p a c
- (:<>:) :: Grammar p a b -> Grammar p a b -> Grammar p a b
- Traverse :: Traversable f => Grammar p a b -> Grammar p (f a) (f b)
- OnHead :: Grammar p a b -> Grammar p (a :- t) (b :- t)
- OnTail :: Grammar p a b -> Grammar p (h :- a) (h :- b)
- Annotate :: Text -> Grammar p a b -> Grammar p a b
- Dive :: Grammar p a b -> Grammar p a b
- Step :: Grammar p a a
- Locate :: Grammar p p p
- data h :- t = h :- t
- forward :: Grammar p a b -> a -> ContextError (Propagation p) (GrammarError p) b
- backward :: Grammar p a b -> b -> ContextError (Propagation p) (GrammarError p) a
- data GrammarError p = GrammarError (Propagation p) Mismatch
- data Mismatch
- expected :: Text -> Mismatch
- unexpected :: Text -> Mismatch
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.
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 :: 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 |
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. |
"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.
h :- t infixr 5 |
Instances
Bitraversable (:-) Source # | |
Defined in Data.InvertibleGrammar.Base bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a :- b) -> f (c :- d) # | |
Bifoldable (:-) Source # | |
Bifunctor (:-) Source # | |
Functor ((:-) h) Source # | |
Foldable ((:-) h) Source # | |
Defined in Data.InvertibleGrammar.Base 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 # elem :: Eq a => a -> (h :- a) -> Bool # maximum :: Ord a => (h :- a) -> a # minimum :: Ord a => (h :- a) -> a # | |
Traversable ((:-) h) Source # | |
(Eq h, Eq t) => Eq (h :- t) Source # | |
(Show h, Show t) => Show (h :- t) Source # | |
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 GrammarError p Source #
Instances
Show p => Show (GrammarError p) Source # | |
Defined in Data.InvertibleGrammar.Monad showsPrec :: Int -> GrammarError p -> ShowS # show :: GrammarError p -> String # showList :: [GrammarError p] -> ShowS # | |
Semigroup (GrammarError p) Source # | |
Defined in Data.InvertibleGrammar.Monad (<>) :: GrammarError p -> GrammarError p -> GrammarError p # sconcat :: NonEmpty (GrammarError p) -> GrammarError p # stimes :: Integral b => b -> GrammarError p -> GrammarError p # |
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.