uniplate-1.6.13: Help writing simple, concise and fast generic operations.
Safe HaskellNone
LanguageHaskell2010

Data.Generics.Uniplate.Operations

Description

Definitions of Uniplate and Biplate classes, along with all the standard operations.

Import this module directly only if you are defining new Uniplate operations, otherwise import one of Data.Generics.Uniplate.Direct, Data.Generics.Uniplate.Typeable or Data.Generics.Uniplate.Data.

Most functions have an example of a possible use for the function. To illustate, I have used the Expr type as below:

data Expr = Val Int
          | Neg Expr
          | Add Expr Expr
Synopsis

The Classes

class Uniplate on where Source #

The standard Uniplate class, all operations require this. All definitions must define uniplate, while descend and descendM are optional.

Minimal complete definition

uniplate

Methods

uniplate :: on -> (Str on, Str on -> on) Source #

The underlying method in the class. Taking a value, the function should return all the immediate children of the same type, and a function to replace them.

Given uniplate x = (cs, gen)

cs should be a Str on, constructed of Zero, One and Two, containing all x's direct children of the same type as x. gen should take a Str on with exactly the same structure as cs, and generate a new element with the children replaced.

Example instance:

instance Uniplate Expr where
    uniplate (Val i  ) = (Zero               , \Zero                  -> Val i  )
    uniplate (Neg a  ) = (One a              , \(One a)               -> Neg a  )
    uniplate (Add a b) = (Two (One a) (One b), \(Two (One a) (One b)) -> Add a b)

descend :: (on -> on) -> on -> on Source #

Perform a transformation on all the immediate children, then combine them back. This operation allows additional information to be passed downwards, and can be used to provide a top-down transformation. This function can be defined explicitly, or can be provided by automatically in terms of uniplate.

For example, on the sample type, we could write:

descend f (Val i  ) = Val i
descend f (Neg a  ) = Neg (f a)
descend f (Add a b) = Add (f a) (f b)

descendM :: Applicative m => (on -> m on) -> on -> m on Source #

Applicative variant of descend

Instances

Instances details
Uniplate Bool Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

uniplate :: Bool -> (Str Bool, Str Bool -> Bool) Source #

descend :: (Bool -> Bool) -> Bool -> Bool Source #

descendM :: Applicative m => (Bool -> m Bool) -> Bool -> m Bool Source #

Uniplate Char Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

uniplate :: Char -> (Str Char, Str Char -> Char) Source #

descend :: (Char -> Char) -> Char -> Char Source #

descendM :: Applicative m => (Char -> m Char) -> Char -> m Char Source #

Uniplate Double Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Uniplate Float Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Uniplate Int Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

uniplate :: Int -> (Str Int, Str Int -> Int) Source #

descend :: (Int -> Int) -> Int -> Int Source #

descendM :: Applicative m => (Int -> m Int) -> Int -> m Int Source #

Uniplate Integer Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Uniplate () Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

uniplate :: () -> (Str (), Str () -> ()) Source #

descend :: (() -> ()) -> () -> () Source #

descendM :: Applicative m => (() -> m ()) -> () -> m () Source #

Data a => Uniplate a Source # 
Instance details

Defined in Data.Generics.Uniplate.Data

Methods

uniplate :: a -> (Str a, Str a -> a) Source #

descend :: (a -> a) -> a -> a Source #

descendM :: Applicative m => (a -> m a) -> a -> m a Source #

PlateAll a a => Uniplate a Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

uniplate :: a -> (Str a, Str a -> a) Source #

descend :: (a -> a) -> a -> a Source #

descendM :: Applicative m => (a -> m a) -> a -> m a Source #

Uniplate [Char] Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

uniplate :: [Char] -> (Str [Char], Str [Char] -> [Char]) Source #

descend :: ([Char] -> [Char]) -> [Char] -> [Char] Source #

descendM :: Applicative m => ([Char] -> m [Char]) -> [Char] -> m [Char] Source #

Uniplate (Ratio Integer) Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

class Uniplate to => Biplate from to where Source #

Children are defined as the top-most items of type to starting at the root. All instances must define biplate, while descendBi and descendBiM are optional.

Minimal complete definition

biplate

Methods

biplate :: from -> (Str to, Str to -> from) Source #

Return all the top most children of type to within from.

If from == to then this function should return the root as the single child.

descendBi :: (to -> to) -> from -> from Source #

Like descend but with more general types. If from == to then this function does not descend. Therefore, when writing definitions it is highly unlikely that this function should be used in the recursive case. A common pattern is to first match the types using descendBi, then continue the recursion with descend.

descendBiM :: Applicative m => (to -> m to) -> from -> m from Source #

Instances

Instances details
(Data a, Data b, Uniplate b) => Biplate a b Source # 
Instance details

Defined in Data.Generics.Uniplate.Data

Methods

biplate :: a -> (Str b, Str b -> a) Source #

descendBi :: (b -> b) -> a -> a Source #

descendBiM :: Applicative m => (b -> m b) -> a -> m a Source #

(Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

biplate :: a -> (Str b, Str b -> a) Source #

descendBi :: (b -> b) -> a -> a Source #

descendBiM :: Applicative m => (b -> m b) -> a -> m a Source #

Biplate [Char] Char Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

biplate :: [Char] -> (Str Char, Str Char -> [Char]) Source #

descendBi :: (Char -> Char) -> [Char] -> [Char] Source #

descendBiM :: Applicative m => (Char -> m Char) -> [Char] -> m [Char] Source #

Biplate (Ratio Integer) Integer Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Biplate [Char] [Char] Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Methods

biplate :: [Char] -> (Str [Char], Str [Char] -> [Char]) Source #

descendBi :: ([Char] -> [Char]) -> [Char] -> [Char] Source #

descendBiM :: Applicative m => ([Char] -> m [Char]) -> [Char] -> m [Char] Source #

Biplate (Ratio Integer) (Ratio Integer) Source # 
Instance details

Defined in Data.Generics.Uniplate.Direct

Single Type Operations

Queries

universe :: Uniplate on => on -> [on] Source #

Get all the children of a node, including itself and all children.

universe (Add (Val 1) (Neg (Val 2))) =
    [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]

This method is often combined with a list comprehension, for example:

vals x = [i | Val i <- universe x]

children :: Uniplate on => on -> [on] Source #

Get the direct children of a node. Usually using universe is more appropriate.

Transformations

transform :: Uniplate on => (on -> on) -> on -> on Source #

Transform every element in the tree, in a bottom-up manner.

For example, replacing negative literals with literals:

negLits = transform f
   where f (Neg (Lit i)) = Lit (negate i)
         f x = x

transformM :: (Monad m, Applicative m, Uniplate on) => (on -> m on) -> on -> m on Source #

Applicative variant of transform

rewrite :: Uniplate on => (on -> Maybe on) -> on -> on Source #

Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:

propRewrite r x = all (isNothing . r) (universe (rewrite r x))

Usually transform is more appropriate, but rewrite can give better compositionality. Given two single transformations f and g, you can construct f mplus g which performs both rewrites until a fixed point.

rewriteM :: (Monad m, Applicative m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on Source #

Applicative variant of rewrite

Others

contexts :: Uniplate on => on -> [(on, on -> on)] Source #

Return all the contexts and holes.

universe x == map fst (contexts x)
all (== x) [b a | (a,b) <- contexts x]

holes :: Uniplate on => on -> [(on, on -> on)] Source #

The one depth version of contexts

children x == map fst (holes x)
all (== x) [b a | (a,b) <- holes x]

para :: Uniplate on => (on -> [r] -> r) -> on -> r Source #

Perform a fold-like computation on each value, technically a paramorphism

Multiple Type Operations

Queries

universeBi :: Biplate from to => from -> [to] Source #

childrenBi :: Biplate from to => from -> [to] Source #

Return the children of a type. If to == from then it returns the original element (in contrast to children)

Transformations

transformBi :: Biplate from to => (to -> to) -> from -> from Source #

transformBiM :: (Monad m, Applicative m, Biplate from to) => (to -> m to) -> from -> m from Source #

rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> from Source #

rewriteBiM :: (Monad m, Applicative m, Biplate from to) => (to -> m (Maybe to)) -> from -> m from Source #

Others

contextsBi :: Biplate from to => from -> [(to, to -> from)] Source #

holesBi :: Biplate from to => from -> [(to, to -> from)] Source #