Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module can be used to scrap the boilerplate attribute declarations. In particular:
- If an
attribution
rule always merely copies the inherited attributes to the children's inherited attributes of the same name, the rule can be left out by wrapping the transformation into anAuto
constructor and making the inherited attributes aGeneric
instance. - A synthesized attribute whose value is a fold of all same-named attributes of the children can be wrapped in the
Folded
constructor and calculated automatically. - A synthesized attribute that is a copy of the current node but with every child taken from the same-named
synthesized child attribute can be wrapped in the
Mapped
constructor and calculated automatically. - If the attribute additionally carries an applicative effect, the
Mapped
wrapper can be replaced byTraversed
.
Synopsis
- newtype Auto t = Auto t
- newtype Folded a = Folded {
- getFolded :: a
- newtype Mapped f a = Mapped {
- getMapped :: f a
- newtype Traversed m f a = Traversed {
- getTraversed :: m (f a)
- class Bequether t g deep shallow where
- class Synthesizer t g deep shallow where
- synthesis :: forall sem. sem ~ Semantics t => t -> shallow (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Atts (Synthesized t) (g sem sem)
- class SynthesizedField (name :: Symbol) result t g deep shallow where
- synthesizedField :: forall sem. sem ~ Semantics t => Proxy name -> t -> shallow (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> result
- class (Transformation t, dom ~ Domain t) => Revelation t dom where
- reveal :: t -> dom x -> x
- foldedField :: forall name t g a sem. (Monoid a, Foldable (Accumulator t name a) (g sem)) => Proxy name -> t -> g sem (Synthesized t) -> Folded a
- mappedField :: forall name t g f sem. (Functor (Replicator t f name) (g f), Atts (Synthesized t) (g sem sem) ~ Atts (Synthesized t) (g f f)) => Proxy name -> t -> g sem (Synthesized t) -> g f f
- passDown :: forall t g shallow deep atts. Functor (PassDown t shallow atts) (g deep) => atts -> g deep shallow -> g deep (Inherited t)
- bequestDefault :: forall t g shallow deep sem. (sem ~ Semantics t, Domain t ~ shallow, Revelation t shallow, Functor (PassDown t sem (Atts (Inherited t) (g sem sem))) (g sem)) => t -> shallow (g sem sem) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> g sem (Inherited t)
Type wrappers for automatic attribute inference
Transformation wrapper that allows automatic inference of attribute rules.
Auto t |
Instances
(Bequether (Auto t) g d s, Synthesizer (Auto t) g d s) => Attribution (Auto t) g d s Source # | |
Defined in Transformation.AG.Generics |
Wrapper for a field that should be automatically synthesized by folding together all child nodes' synthesized attributes of the same name.
Instances
(Monoid a, Foldable (Accumulator t name a) (g (Semantics t))) => SynthesizedField name (Folded a) t g deep shallow Source # | |
Defined in Transformation.AG.Generics | |
Eq a => Eq (Folded a) Source # | |
Ord a => Ord (Folded a) Source # | |
Defined in Transformation.AG.Generics | |
Show a => Show (Folded a) Source # | |
Semigroup a => Semigroup (Folded a) Source # | |
Monoid a => Monoid (Folded a) Source # | |
Wrapper for a field that should be automatically synthesized by replacing every child node by its synthesized attribute of the same name.
Instances
(Functor f, Functor (Replicator t f name) (g f), Atts (Synthesized t) (g (Semantics t) (Semantics t)) ~ Atts (Synthesized t) (g f f)) => SynthesizedField name (Mapped f (g f f)) t g deep f Source # | |
Defined in Transformation.AG.Generics | |
Monad f => Monad (Mapped f) Source # | |
Functor f => Functor (Mapped f) Source # | |
Applicative f => Applicative (Mapped f) Source # | |
Foldable f => Foldable (Mapped f) Source # | |
Defined in Transformation.AG.Generics fold :: Monoid m => Mapped f m -> m # foldMap :: Monoid m => (a -> m) -> Mapped f a -> m # foldMap' :: Monoid m => (a -> m) -> Mapped f a -> m # foldr :: (a -> b -> b) -> b -> Mapped f a -> b # foldr' :: (a -> b -> b) -> b -> Mapped f a -> b # foldl :: (b -> a -> b) -> b -> Mapped f a -> b # foldl' :: (b -> a -> b) -> b -> Mapped f a -> b # foldr1 :: (a -> a -> a) -> Mapped f a -> a # foldl1 :: (a -> a -> a) -> Mapped f a -> a # elem :: Eq a => a -> Mapped f a -> Bool # maximum :: Ord a => Mapped f a -> a # minimum :: Ord a => Mapped f a -> a # | |
Eq (f a) => Eq (Mapped f a) Source # | |
Ord (f a) => Ord (Mapped f a) Source # | |
Defined in Transformation.AG.Generics | |
Show (f a) => Show (Mapped f a) Source # | |
Semigroup (f a) => Semigroup (Mapped f a) Source # | |
Monoid (f a) => Monoid (Mapped f a) Source # | |
newtype Traversed m f a Source #
Wrapper for a field that should be automatically synthesized by traversing over all child nodes and applying each node's synthesized attribute of the same name.
Traversed | |
|
Instances
Type classes replacing Attribution
class Bequether t g deep shallow where Source #
A half of the Attribution
class used to specify all inherited attributes.
:: forall sem. sem ~ Semantics t | |
=> t | transformation |
-> shallow (g deep deep) | tree node |
-> Atts (Inherited t) (g sem sem) | inherited attributes |
-> g sem (Synthesized t) | synthesized attributes |
-> g sem (Inherited t) |
class Synthesizer t g deep shallow where Source #
A half of the Attribution
class used to specify all synthesized attributes.
:: forall sem. sem ~ Semantics t | |
=> t | transformation |
-> shallow (g deep deep) | tre node |
-> Atts (Inherited t) (g sem sem) | inherited attributes |
-> g sem (Synthesized t) | synthesized attributes |
-> Atts (Synthesized t) (g sem sem) |
Instances
(Atts (Synthesized t) (g sem sem) ~ result, Generic result, sem ~ Semantics t, GenericSynthesizer t g d s (Rep result)) => Synthesizer t g d s Source # | |
Defined in Transformation.AG.Generics |
class SynthesizedField (name :: Symbol) result t g deep shallow where Source #
Class for specifying a single named attribute
:: forall sem. sem ~ Semantics t | |
=> Proxy name | attribute name |
-> t | transformation |
-> shallow (g deep deep) | tree node |
-> Atts (Inherited t) (g sem sem) | inherited attributes |
-> g sem (Synthesized t) | synthesized attributes |
-> result |
Instances
(Monoid a, Foldable (Accumulator t name a) (g (Semantics t))) => SynthesizedField name (Folded a) t g deep shallow Source # | |
Defined in Transformation.AG.Generics | |
(Functor f, Functor (Replicator t f name) (g f), Atts (Synthesized t) (g (Semantics t) (Semantics t)) ~ Atts (Synthesized t) (g f f)) => SynthesizedField name (Mapped f (g f f)) t g deep f Source # | |
Defined in Transformation.AG.Generics | |
(Traversable f, Applicative m, Traversable (Traverser t m f name) (g f), Atts (Synthesized t) (g (Semantics t) (Semantics t)) ~ Atts (Synthesized t) (g f f)) => SynthesizedField name (Traversed m f (g f f)) t g deep f Source # | |
Defined in Transformation.AG.Generics |
class (Transformation t, dom ~ Domain t) => Revelation t dom where Source #
Instances
(Transformation t, Domain t ~ Identity) => Revelation t Identity Source # | |
Defined in Transformation.AG.Generics | |
(Transformation t, Domain t ~ (,) a) => Revelation t ((,) a) Source # | |
Defined in Transformation.AG.Generics |
The default behaviour on generic datatypes
foldedField :: forall name t g a sem. (Monoid a, Foldable (Accumulator t name a) (g sem)) => Proxy name -> t -> g sem (Synthesized t) -> Folded a Source #
The default synthesizedField
method definition for Folded
fields.
mappedField :: forall name t g f sem. (Functor (Replicator t f name) (g f), Atts (Synthesized t) (g sem sem) ~ Atts (Synthesized t) (g f f)) => Proxy name -> t -> g sem (Synthesized t) -> g f f Source #
The default synthesizedField
method definition for Mapped
fields.
passDown :: forall t g shallow deep atts. Functor (PassDown t shallow atts) (g deep) => atts -> g deep shallow -> g deep (Inherited t) Source #
Pass down the given record of inherited fields to child nodes.
bequestDefault :: forall t g shallow deep sem. (sem ~ Semantics t, Domain t ~ shallow, Revelation t shallow, Functor (PassDown t sem (Atts (Inherited t) (g sem sem))) (g sem)) => t -> shallow (g sem sem) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> g sem (Inherited t) Source #
The default bequest
method definition relies on generics to automatically pass down all same-named inherited
attributes.