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

Transformation.AG

Description

An attribute grammar is a particular kind of Transformation that assigns attributes to nodes in a tree. Different node types may have different types of attributes, so the transformation is not natural. All attributes are divided into Inherited and Synthesized attributes.

Synopsis

Documentation

type family Atts (f :: * -> *) a Source #

Type family that assigns maps a node type to the type of its attributes, indexed per type constructor.

newtype Inherited t a Source #

Type constructor wrapping the inherited attributes for the given transformation.

Constructors

Inherited 

Fields

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 #

Show (Atts (Inherited t) a) => Show (Inherited t a) Source # 
Instance details

Defined in Transformation.AG

Methods

showsPrec :: Int -> Inherited t a -> ShowS #

show :: Inherited t a -> String #

showList :: [Inherited t a] -> ShowS #

newtype Synthesized t a Source #

Type constructor wrapping the synthesized attributes for the given transformation.

Constructors

Synthesized 

Fields

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 #

Show (Atts (Synthesized t) a) => Show (Synthesized t a) Source # 
Instance details

Defined in Transformation.AG

Methods

showsPrec :: Int -> Synthesized t a -> ShowS #

show :: Synthesized t a -> String #

showList :: [Synthesized t a] -> ShowS #

type Semantics t = Inherited t ~> Synthesized t Source #

A node's Semantics is a natural tranformation from the node's inherited attributes to its synthesized attributes.

type Rule t g = forall sem. sem ~ Semantics t => (Inherited t (g sem sem), g sem (Synthesized t)) -> (Synthesized t (g sem sem), g sem (Inherited t)) Source #

An attribution rule maps a node's inherited attributes and its child nodes' synthesized attributes to the node's synthesized attributes and the children nodes' inherited attributes.

knit :: (Apply (g sem), sem ~ Semantics t) => Rule t g -> g sem sem -> sem (g sem sem) Source #

class Attribution t g deep shallow where Source #

Methods

attribution :: t -> shallow (g deep deep) -> Rule t g Source #

The attribution rule for a given transormation and node.

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 #

applyDefault :: (q ~ Semantics t, x ~ g q q, Apply (g q), Attribution t g q p) => (forall a. p a -> a) -> t -> p x -> q x Source #

Drop-in implementation of $

fullMapDefault :: (p ~ Domain t, q ~ Semantics t, q ~ Codomain t, x ~ g q q, Apply (g q), Functor t g, Attribution t g p p) => (forall a. p a -> a) -> t -> p (g p p) -> q (g q q) Source #

Drop-in implementation of <$>