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

Transformation.AG.Dimorphic

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 b, Functor (Auto t) g, At (Auto t) (g (Semantics a b) (Semantics a b))) => Functor (Auto t) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

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 b, Foldable (g q), Monoid a, Monoid b, Foldable p, Attribution (Auto t) a b g q p) => At (Auto t) (g (Semantics a b) (Semantics a b)) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Auto t -> Domain (Auto t) (g (Semantics a b) (Semantics a b)) -> Codomain (Auto t) (g (Semantics a b) (Semantics a b)) 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 b, Functor f, Functor (Keep t) g, At (Keep t) (g (PreservingSemantics f a b) (PreservingSemantics f a b))) => Functor (Keep t) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

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 b, Traversable (Feeder a b f) g, Functor (Keep t) g, At (Keep t) (g (PreservingSemantics f a b) (PreservingSemantics f a b))) => Traversable (Keep t) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

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 b, Foldable (g q), Monoid a, Monoid b, Foldable p, Functor p, Attribution (Keep t) a b g q p) => At (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Keep t -> Domain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) -> Codomain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) Source #

data Atts a b Source #

Constructors

Atts 

Fields

Instances

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

Defined in Transformation.AG.Dimorphic

Methods

($) :: Keep t -> Domain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) -> Codomain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) 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

(Data a, Data b) => Data (Atts a b) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Atts a b -> c (Atts a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Atts a b) #

toConstr :: Atts a b -> Constr #

dataTypeOf :: Atts a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Atts a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Atts a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Atts a b -> Atts a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atts a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atts a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Atts a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Atts a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Atts a b -> m (Atts a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Atts a b -> m (Atts a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Atts a b -> m (Atts a b) #

(Monoid a, Monoid b) => Monoid (Atts a b) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

mempty :: Atts a b #

mappend :: Atts a b -> Atts a b -> Atts a b #

mconcat :: [Atts a b] -> Atts a b #

(Semigroup a, Semigroup b) => Semigroup (Atts a b) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

(<>) :: Atts a b -> Atts a b -> Atts a b #

sconcat :: NonEmpty (Atts a b) -> Atts a b #

stimes :: Integral b0 => b0 -> Atts a b -> Atts a b #

(Show a, Show b) => Show (Atts a b) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

showsPrec :: Int -> Atts a b -> ShowS #

show :: Atts a b -> String #

showList :: [Atts a b] -> ShowS #

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

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

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

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

type Rule a b = Atts a b -> Atts a b 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.

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

class Attribution t a b 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 b Source #

The attribution rule for a given transformation and node.

Instances

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

Defined in Transformation.AG.Dimorphic

Methods

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

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

Drop-in implementation of $

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

Drop-in implementation of <$>

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

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

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

data Feeder a b (f :: Type -> Type) Source #

Constructors

Feeder 

Instances

Instances details
Transformation (Feeder a b f) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Associated Types

type Domain (Feeder a b f) :: Type -> Type Source #

type Codomain (Feeder a b f) :: Type -> Type Source #

At (Feeder a b f) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Feeder a b f -> Domain (Feeder a b f) g -> Codomain (Feeder a b f) g Source #

(Traversable f, Traversable (Feeder a b f) g) => Traversable (Feeder a b f) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

traverse :: Codomain (Feeder a b f) ~ Compose m f0 => Feeder a b f -> Domain (Feeder a b f) (g (Domain (Feeder a b f)) (Domain (Feeder a b f))) -> m (f0 (g f0 f0)) Source #

type Codomain (Feeder a b f) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

type Codomain (Feeder a b f) = Compose ((->) a) (Compose ((,) (Atts a b)) f)
type Domain (Feeder a b f) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

type Domain (Feeder a b f) = Compose ((->) a) (Compose ((,) (Atts a b)) f)