Synthetising attributes, partly motivated by Attribute Grammars.
- newtype Attrib f a = Attrib {}
- annMap :: Functor f => (a -> b) -> Attr f a -> Attr f b
- synthetise :: Functor f => (f a -> a) -> Mu f -> Attr f a
- synthetise' :: Functor f => (a -> f b -> b) -> Attr f a -> Attr f b
- synthetiseList :: (Functor f, Foldable f) => ([a] -> a) -> Mu f -> Attr f a
- synthetiseM :: (Traversable f, Monad m) => (f a -> m a) -> Mu f -> m (Attr f a)
- inherit :: Functor f => (Mu f -> a -> a) -> a -> Mu f -> Attr f a
- inherit' :: Functor f => (a -> b -> a) -> a -> Attr f b -> Attr f a
- synthAccumL :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> (a, Attr f b)
- synthAccumR :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> (a, Attr f b)
- synthAccumL_ :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> Attr f b
- synthAccumR_ :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> Attr f b
- enumerateNodes :: Traversable f => Mu f -> (Int, Attr f Int)
- enumerateNodes_ :: Traversable f => Mu f -> Attr f Int
- annZip :: Functor f => Mu (Ann (Ann f a) b) -> Attr f (a, b)
- annZipWith :: Functor f => (a -> b -> c) -> Mu (Ann (Ann f a) b) -> Attr f c
- annZip3 :: Functor f => Mu (Ann (Ann (Ann f a) b) c) -> Attr f (a, b, c)
- annZipWith3 :: Functor f => (a -> b -> c -> d) -> Mu (Ann (Ann (Ann f a) b) c) -> Attr f d
Documentation
A newtype wrapper around Attr f a
so that we can make Attr f
an instance of Functor, Foldable and Traversable. This is necessary
since Haskell does not allow partial application of type synonyms.
annMap :: Functor f => (a -> b) -> Attr f a -> Attr f bSource
Map over annotations
annMap f = unAttrib . fmap f . Attrib
Synthetised attributes
synthetise :: Functor f => (f a -> a) -> Mu f -> Attr f aSource
Synthetised attributes are created in a bottom-up manner.
As an example, the sizes
function computes the sizes of all
subtrees:
sizes :: (Functor f, Foldable f) => Mu f -> Attr f Int sizes = synthetise (\t -> 1 + sum t)
(note that sum
here is Data.Foldable.sum == Prelude.sum . Data.Foldable.toList
)
synthetise' :: Functor f => (a -> f b -> b) -> Attr f a -> Attr f bSource
Generalization of scanr
for trees.
synthetiseM :: (Traversable f, Monad m) => (f a -> m a) -> Mu f -> m (Attr f a)Source
Inherited attributes
inherit :: Functor f => (Mu f -> a -> a) -> a -> Mu f -> Attr f aSource
Inherited attributes are created in a top-down manner.
As an example, the depths
function computes the depth
(the distance from the root, incremented by 1) of all subtrees:
depths :: Functor f => Mu f -> Attr f Int depths = inherit (\_ i -> i+1) 0
inherit' :: Functor f => (a -> b -> a) -> a -> Attr f b -> Attr f aSource
Generalization of scanl
for trees
Traversals
synthAccumL :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> (a, Attr f b)Source
Synthetising attributes via an accumulating map in a left-to-right fashion
(the order is the same as in foldl
).
synthAccumR :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> (a, Attr f b)Source
Synthetising attributes via an accumulating map in a right-to-left fashion
(the order is the same as in foldr
).
synthAccumL_ :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> Attr f bSource
synthAccumR_ :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> Attr f bSource
enumerateNodes :: Traversable f => Mu f -> (Int, Attr f Int)Source
We use synthAccumL
to number the nodes from 0
to (n-1)
in
a left-to-right traversal fashion, where
n == length (universe tree)
is the number of substructures,
which is also returned.
enumerateNodes_ :: Traversable f => Mu f -> Attr f IntSource
Stacking attributes
annZip :: Functor f => Mu (Ann (Ann f a) b) -> Attr f (a, b)Source
Merges two layers of annotations into a single one.