deep-transformations-0.2.1.1: Deep natural and unnatural tree transformations, including attribute grammars
Safe HaskellSafe-Inferred
LanguageHaskell2010

Transformation.AG.Monomorphic

Description

A special case of an attribute grammar where every node has only a single inherited and a single synthesized attribute of the same monoidal type. The synthesized attributes of child nodes are all mconcatted together.

Synopsis

Documentation

newtype Auto t Source #

Transformation wrapper that allows automatic inference of attribute rules.

Constructors

Auto t 

Instances

Instances details
(Transformation (Auto t), Domain (Auto t) ~ f, Functor f, Codomain (Auto t) ~ Semantics a, Functor (Auto t) g, At (Auto t) (g (Semantics a) (Semantics a))) => Functor (Auto t) g Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

(<$>) :: Auto t -> Domain (Auto t) (g (Domain (Auto t)) (Domain (Auto t))) -> Codomain (Auto t) (g (Codomain (Auto t)) (Codomain (Auto t))) Source #

(Transformation (Auto t), p ~ Domain (Auto t), q ~ Codomain (Auto t), q ~ Semantics a, Foldable (g q), Monoid a, Foldable p, Attribution (Auto t) a g q p) => At (Auto t) (g (Semantics a) (Semantics a)) Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

($) :: Auto t -> Domain (Auto t) (g (Semantics a) (Semantics a)) -> Codomain (Auto t) (g (Semantics a) (Semantics a)) Source #

newtype Keep t Source #

Transformation wrapper that allows automatic inference of attribute rules and preservation of the attribute with the original nodes.

Constructors

Keep t 

Instances

Instances details
(Transformation (Keep t), Domain (Keep t) ~ f, Functor f, Codomain (Keep t) ~ PreservingSemantics f a, Functor f, Functor (Keep t) g, At (Keep t) (g (PreservingSemantics f a) (PreservingSemantics f a))) => Functor (Keep t) g Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

(<$>) :: Keep t -> Domain (Keep t) (g (Domain (Keep t)) (Domain (Keep t))) -> Codomain (Keep t) (g (Codomain (Keep t)) (Codomain (Keep t))) Source #

(Transformation (Keep t), Domain (Keep t) ~ f, Traversable f, Traversable (g f), Codomain (Keep t) ~ PreservingSemantics f a, Traversable (Feeder a f) g, Functor (Keep t) g, At (Keep t) (g (PreservingSemantics f a) (PreservingSemantics f a))) => Traversable (Keep t) g Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

traverse :: Codomain (Keep t) ~ Compose m f => Keep t -> Domain (Keep t) (g (Domain (Keep t)) (Domain (Keep t))) -> m (f (g f f)) Source #

(Transformation (Keep t), p ~ Domain (Keep t), q ~ Codomain (Keep t), q ~ PreservingSemantics p a, Foldable (g q), Monoid a, Foldable p, Functor p, Attribution (Keep t) a g q p) => At (Keep t) (g (PreservingSemantics p a) (PreservingSemantics p a)) Source # 
Instance details

Defined in Transformation.AG.Monomorphic

type Atts a = Atts a a Source #

pattern Atts :: a -> a -> Atts a Source #

inh :: Atts a -> a Source #

syn :: Atts a -> a Source #

type Semantics a = Const (a -> a) Source #

A node's Semantics maps its inherited attribute to its synthesized attribute.

type PreservingSemantics f a = Compose ((->) a) (Compose ((,) (Atts a)) f) Source #

A node's PreservingSemantics maps its inherited attribute to its synthesized attribute.

type Rule a = Atts a -> Atts a Source #

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

class Attribution t a g (deep :: Type -> Type) shallow where Source #

The core type class for defining the attribute grammar. The instances of this class typically have a form like

instance Attribution MyAttGrammar MyMonoid MyNode (Semantics MyAttGrammar) Identity where
  attribution MyAttGrammar{} (Identity MyNode{})
              Atts{inh= fromParent,
                   syn= fromChildren}
            = Atts{syn= toParent,
                   inh= toChildren}

Methods

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

The attribution rule for a given transformation and node.

Instances

Instances details
Attribution t a g deep shallow Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

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

type Feeder a = Feeder a a Source #

knit :: (Foldable (g sem), sem ~ Semantics a b, Monoid a, Monoid b) => Rule a b -> g sem sem -> sem (g sem sem) Source #

The core function to tie the recursive knot, turning a Rule for a node into its Semantics.

knitKeeping :: forall a b f g sem. (Foldable (g sem), sem ~ PreservingSemantics f a b, Monoid a, Monoid b, Foldable f, Functor f) => Rule a b -> f (g sem sem) -> sem (g sem sem) Source #

Another way to tie the recursive knot, using a Rule to add attributes to every node througha stateful calculation

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

Drop-in implementation of $

applyDefaultWithAttributes :: (p ~ Domain t, q ~ PreservingSemantics p a, x ~ g q q, Attribution t a g q p, Foldable (g q), Monoid a, Foldable p, Functor p) => t -> p x -> q x Source #

Drop-in implementation of $ that stores all attributes with every original node

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

Drop-in implementation of <$>

traverseDefaultWithAttributes :: forall t p q r a b g. (Transformation t, Domain t ~ p, Codomain t ~ Compose ((->) a) q, q ~ Compose ((,) (Atts a b)) p, r ~ Compose ((->) a) q, Traversable p, Functor t g, Traversable (Feeder a b p) g, At t (g r r)) => t -> p (g p p) -> a -> q (g q q) Source #

Drop-in implementation of traverse that stores all attributes with every original node