fixplate-0.1.6: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Attributes

Contents

Description

Synthetising attributes, partly motivated by Attribute Grammars, and partly by recursion schemes.

TODO: better organization / interface to all these functions...

Synopsis

Documentation

newtype Attrib f a Source

A newtype wrapper around Attr f a so that we can make Attr f an instance of Functor, Foldable and Traversable (and Comonad). This is necessary since Haskell does not allow partial application of type synonyms.

Equivalent to the co-free comonad.

Constructors

Attrib 

Fields

unAttrib :: Attr f a
 

annMap :: Functor f => (a -> b) -> Attr f a -> Attr f b Source

Map over annotations

annMap f = unAttrib . fmap f . Attrib

Synthetised attributes

synthetise :: Functor f => (f a -> a) -> Mu f -> Attr f a Source

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)

See also synthCata.

synthetise' :: Functor f => (a -> f b -> b) -> Attr f a -> Attr f b Source

Generalization of scanr for trees. See also scanCata.

synthetiseList :: (Functor f, Foldable f) => ([a] -> a) -> Mu f -> Attr f a Source

List version of synthetise (compare with Uniplate)

synthetiseM :: (Traversable f, Monad m) => (f a -> m a) -> Mu f -> m (Attr f a) Source

Monadic version of synthetise.

Synthetised attributes as generalized cata- and paramorphisms

synthCata :: Functor f => (f a -> a) -> Mu f -> Attr f a Source

Synonym for synthetise, motivated by the equation

 attribute . synthCata f == cata f

That is, it attributes all subtrees with the result of the corresponding catamorphism.

scanCata :: Functor f => (a -> f b -> b) -> Attr f a -> Attr f b Source

Synonym for synthetise'. Note that this could be a special case of synthCata:

scanCata f == annZipWith (flip const) . synthCata (\(Ann a x) -> f a x)

Catamorphim (cata) is the generalization of foldr from lists to trees; synthCata is one generalization of scanr, and scanCata is another generalization.

synthPara :: Functor f => (f (Mu f, a) -> a) -> Mu f -> Attr f a Source

Attributes all subtrees with the result of the corresponding paramorphism.

 attribute . synthPara f == para f

synthPara' :: Functor f => (Mu f -> f a -> a) -> Mu f -> Attr f a Source

Another version of synthPara.

 attribute . synthPara' f == para' f

scanPara :: Functor f => (Attr f a -> f b -> b) -> Attr f a -> Attr f b Source

synthZygo_ :: Functor f => (f b -> b) -> (f (b, a) -> a) -> Mu f -> Attr f a Source

Synthetising zygomorphism.

attribute . synthZygo_ g h == zygo_ g h

synthZygo :: Functor f => (f b -> b) -> (f (b, a) -> a) -> Mu f -> Attr f (b, a) Source

synthZygoWith :: Functor f => (b -> a -> c) -> (f b -> b) -> (f (b, a) -> a) -> Mu f -> Attr f c Source

synthAccumCata :: Functor f => (f acc -> (acc, b)) -> Mu f -> (acc, Attr f b) Source

Accumulating catamorphisms. Generalization of mapAccumR from lists to trees.

synthAccumPara' :: Functor f => (Mu f -> f acc -> (acc, b)) -> Mu f -> (acc, Attr f b) Source

Accumulating paramorphisms.

mapAccumCata :: Functor f => (f acc -> b -> (acc, c)) -> Attr f b -> (acc, Attr f c) Source

Could be a special case of synthAccumCata:

mapAccumCata f == second (annZipWith (flip const)) . synthAccumCata (\(Ann b t) -> f b t) 
  where second g (x,y) = (x, g y)

synthCataM :: (Traversable f, Monad m) => (f a -> m a) -> Mu f -> m (Attr f a) Source

Synonym for synthetiseM. If you don't need the result, use cataM_ instead.

synthParaM :: (Traversable f, Monad m) => (f (Mu f, a) -> m a) -> Mu f -> m (Attr f a) Source

Monadic version of synthPara. If you don't need the result, use paraM_ instead.

synthParaM' :: (Traversable f, Monad m) => (Mu f -> f a -> m a) -> Mu f -> m (Attr f a) Source

Monadic version of synthPara'.

Inherited attributes

inherit :: Functor f => (Mu f -> a -> a) -> a -> Mu f -> Attr f a Source

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 a Source

Generalization of scanl from lists to trees.

inherit2 :: Functor f => (Mu f -> a -> (b, a)) -> a -> Mu f -> Attr f b Source

Generalization of inherit. TODO: better name?

inheritM :: (Traversable f, Monad m) => (Mu f -> a -> m a) -> a -> Mu f -> m (Attr f a) Source

Monadic version of inherit.

inheritM_ :: (Traversable f, Monad m) => (Mu f -> a -> m a) -> a -> Mu f -> m () Source

Top-down folds

topDownSweepM :: (Traversable f, Monad m) => (f () -> a -> m (f a)) -> a -> Mu f -> m () Source

Monadic top-down "sweep" of a tree. It's kind of a more complicated folding version of inheritM. This is unsafe in the sense that the user is responsible to retain the shape of the node. TODO: better name?

topDownSweepM' :: (Traversable f, Monad m) => (b -> f b -> a -> m (f a)) -> a -> Attr f b -> m () Source

An attributed version of topDownSweepM. Probably more useful.

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 b Source

synthAccumR_ :: Traversable f => (a -> Mu f -> (a, b)) -> a -> Mu f -> Attr f b Source

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.

Resynthetising transformations

synthTransform :: Traversable f => (f a -> a) -> (Attr f a -> Maybe (f (Attr f a))) -> Attr f a -> Attr f a Source

Bottom-up transformations which automatically resynthetise attributes in case of changes.

synthTransform' :: Traversable f => (f (Attr f a) -> a) -> (Attr f a -> Maybe (f (Attr f a))) -> Attr f a -> Attr f a Source

synthRewrite :: Traversable f => (f a -> a) -> (Attr f a -> Maybe (f (Attr f a))) -> Attr f a -> Attr f a Source

Bottom-up transformations to normal form (applying transformation exhaustively) which automatically resynthetise attributes in case of changes.

synthRewrite' :: Traversable f => (f (Attr f a) -> a) -> (Attr f a -> Maybe (f (Attr f a))) -> Attr f a -> Attr f a Source

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.

annZipWith :: Functor f => (a -> b -> c) -> Mu (Ann (Ann f a) b) -> Attr f c Source

annZip3 :: Functor f => Mu (Ann (Ann (Ann f a) b) c) -> Attr f (a, b, c) Source

Merges three layers of annotations into a single one.

annZipWith3 :: Functor f => (a -> b -> c -> d) -> Mu (Ann (Ann (Ann f a) b) c) -> Attr f d Source