deep-transformations-0.1: Deep natural and unnatural tree transformations, including attribute grammars
Safe HaskellNone
LanguageHaskell2010

Transformation.AG.Generics

Description

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 an Auto constructor and deriving the Generic instance of the inherited attributes.
  • 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 by Traversed.
Synopsis

Type wrappers for automatic attribute inference

newtype Auto t Source #

Transformation wrapper that allows automatic inference of attribute rules.

Constructors

Auto t 

Instances

Instances details
(Bequether (Auto t) g d s, Synthesizer (Auto t) g d s) => Attribution (Auto t) g d s Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

attribution :: Auto t -> s (g d d) -> Rule (Auto t) g Source #

newtype Folded a Source #

Wrapper for a field that should be automatically synthesized by folding together all child nodes' synthesized attributes of the same name.

Constructors

Folded 

Fields

Instances

Instances details
(Monoid a, Foldable (Accumulator t name a) (g (Semantics t))) => SynthesizedField name (Folded a) t g deep shallow Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> shallow (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Folded a Source #

Eq a => Eq (Folded a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(==) :: Folded a -> Folded a -> Bool #

(/=) :: Folded a -> Folded a -> Bool #

Ord a => Ord (Folded a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

compare :: Folded a -> Folded a -> Ordering #

(<) :: Folded a -> Folded a -> Bool #

(<=) :: Folded a -> Folded a -> Bool #

(>) :: Folded a -> Folded a -> Bool #

(>=) :: Folded a -> Folded a -> Bool #

max :: Folded a -> Folded a -> Folded a #

min :: Folded a -> Folded a -> Folded a #

Show a => Show (Folded a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

showsPrec :: Int -> Folded a -> ShowS #

show :: Folded a -> String #

showList :: [Folded a] -> ShowS #

Semigroup a => Semigroup (Folded a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(<>) :: Folded a -> Folded a -> Folded a #

sconcat :: NonEmpty (Folded a) -> Folded a #

stimes :: Integral b => b -> Folded a -> Folded a #

Monoid a => Monoid (Folded a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

mempty :: Folded a #

mappend :: Folded a -> Folded a -> Folded a #

mconcat :: [Folded a] -> Folded a #

newtype Mapped f a Source #

Wrapper for a field that should be automatically synthesized by replacing every child node by its synthesized attribute of the same name.

Constructors

Mapped 

Fields

Instances

Instances details
(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 # 
Instance details

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> f (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Mapped f (g f f) Source #

Monad f => Monad (Mapped f) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(>>=) :: Mapped f a -> (a -> Mapped f b) -> Mapped f b #

(>>) :: Mapped f a -> Mapped f b -> Mapped f b #

return :: a -> Mapped f a #

Functor f => Functor (Mapped f) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

fmap :: (a -> b) -> Mapped f a -> Mapped f b #

(<$) :: a -> Mapped f b -> Mapped f a #

Applicative f => Applicative (Mapped f) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

pure :: a -> Mapped f a #

(<*>) :: Mapped f (a -> b) -> Mapped f a -> Mapped f b #

liftA2 :: (a -> b -> c) -> Mapped f a -> Mapped f b -> Mapped f c #

(*>) :: Mapped f a -> Mapped f b -> Mapped f b #

(<*) :: Mapped f a -> Mapped f b -> Mapped f a #

Foldable f => Foldable (Mapped f) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

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 #

toList :: Mapped f a -> [a] #

null :: Mapped f a -> Bool #

length :: Mapped f a -> Int #

elem :: Eq a => a -> Mapped f a -> Bool #

maximum :: Ord a => Mapped f a -> a #

minimum :: Ord a => Mapped f a -> a #

sum :: Num a => Mapped f a -> a #

product :: Num a => Mapped f a -> a #

Eq (f a) => Eq (Mapped f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(==) :: Mapped f a -> Mapped f a -> Bool #

(/=) :: Mapped f a -> Mapped f a -> Bool #

Ord (f a) => Ord (Mapped f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

compare :: Mapped f a -> Mapped f a -> Ordering #

(<) :: Mapped f a -> Mapped f a -> Bool #

(<=) :: Mapped f a -> Mapped f a -> Bool #

(>) :: Mapped f a -> Mapped f a -> Bool #

(>=) :: Mapped f a -> Mapped f a -> Bool #

max :: Mapped f a -> Mapped f a -> Mapped f a #

min :: Mapped f a -> Mapped f a -> Mapped f a #

Show (f a) => Show (Mapped f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

showsPrec :: Int -> Mapped f a -> ShowS #

show :: Mapped f a -> String #

showList :: [Mapped f a] -> ShowS #

Semigroup (f a) => Semigroup (Mapped f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(<>) :: Mapped f a -> Mapped f a -> Mapped f a #

sconcat :: NonEmpty (Mapped f a) -> Mapped f a #

stimes :: Integral b => b -> Mapped f a -> Mapped f a #

Monoid (f a) => Monoid (Mapped f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

mempty :: Mapped f a #

mappend :: Mapped f a -> Mapped f a -> Mapped f a #

mconcat :: [Mapped f a] -> Mapped f a #

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.

Constructors

Traversed 

Fields

Instances

Instances details
(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 # 
Instance details

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> f (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Traversed m f (g f f) Source #

(Functor m, Functor f) => Functor (Traversed m f) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

fmap :: (a -> b) -> Traversed m f a -> Traversed m f b #

(<$) :: a -> Traversed m f b -> Traversed m f a #

Eq (m (f a)) => Eq (Traversed m f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(==) :: Traversed m f a -> Traversed m f a -> Bool #

(/=) :: Traversed m f a -> Traversed m f a -> Bool #

Ord (m (f a)) => Ord (Traversed m f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

compare :: Traversed m f a -> Traversed m f a -> Ordering #

(<) :: Traversed m f a -> Traversed m f a -> Bool #

(<=) :: Traversed m f a -> Traversed m f a -> Bool #

(>) :: Traversed m f a -> Traversed m f a -> Bool #

(>=) :: Traversed m f a -> Traversed m f a -> Bool #

max :: Traversed m f a -> Traversed m f a -> Traversed m f a #

min :: Traversed m f a -> Traversed m f a -> Traversed m f a #

Show (m (f a)) => Show (Traversed m f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

showsPrec :: Int -> Traversed m f a -> ShowS #

show :: Traversed m f a -> String #

showList :: [Traversed m f a] -> ShowS #

Semigroup (m (f a)) => Semigroup (Traversed m f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

(<>) :: Traversed m f a -> Traversed m f a -> Traversed m f a #

sconcat :: NonEmpty (Traversed m f a) -> Traversed m f a #

stimes :: Integral b => b -> Traversed m f a -> Traversed m f a #

Monoid (m (f a)) => Monoid (Traversed m f a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

mempty :: Traversed m f a #

mappend :: Traversed m f a -> Traversed m f a -> Traversed m f a #

mconcat :: [Traversed m f a] -> Traversed m f a #

Type classes replacing Attribution

class Bequether t g deep shallow where Source #

A half of the Attribution class used to specify all inherited attributes.

Methods

bequest Source #

Arguments

:: 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) 

Instances

Instances details
(sem ~ Semantics t, Domain t ~ shallow, Revelation t shallow, Functor (PassDown t sem (Atts (Inherited t) (g sem sem))) (g sem)) => Bequether t g (Semantics t) shallow Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

bequest :: forall (sem :: Type -> Type). sem ~ Semantics t => t -> shallow (g (Semantics t) (Semantics t)) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> g sem (Inherited t) Source #

class Synthesizer t g deep shallow where Source #

A half of the Attribution class used to specify all synthesized attributes.

Methods

synthesis Source #

Arguments

:: 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

Instances details
(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 # 
Instance details

Defined in Transformation.AG.Generics

Methods

synthesis :: forall (sem :: Type -> Type). sem ~ Semantics t => t -> s (g d d) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Atts (Synthesized t) (g sem sem) Source #

class SynthesizedField (name :: Symbol) result t g deep shallow where Source #

Class for specifying a single named attribute

Methods

synthesizedField Source #

Arguments

:: 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

Instances details
(Monoid a, Foldable (Accumulator t name a) (g (Semantics t))) => SynthesizedField name (Folded a) t g deep shallow Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> shallow (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Folded a Source #

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

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> f (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Mapped f (g f f) Source #

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

Defined in Transformation.AG.Generics

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics t => Proxy name -> t -> f (g deep deep) -> Atts (Inherited t) (g sem sem) -> g sem (Synthesized t) -> Traversed m f (g f f) Source #

class (Transformation t, dom ~ Domain t) => Revelation t dom where Source #

Methods

reveal :: t -> dom x -> x Source #

Extract the value from the transformation domain

Instances

Instances details
(Transformation t, Domain t ~ Identity) => Revelation t Identity Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

reveal :: t -> Identity x -> x Source #

(Transformation t, Domain t ~ (,) a) => Revelation t ((,) a) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

reveal :: t -> (a, x) -> x Source #

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 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.