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

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Open

Contents

Description

"Open" functions, working on functors instead of trees.

Synopsis

Documentation

toList :: Foldable t => forall a. t a -> [a]

List of elements of a structure, from left to right.

toRevList :: Foldable f => f a -> [a] Source

Equivalent to reverse . toList.

Accumulating maps

mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)

The mapAccumL function behaves like a combination of fmap and foldl; it applies a function to each element of a structure, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)

The mapAccumR function behaves like a combination of fmap and foldr; it applies a function to each element of a structure, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new structure.

mapAccumL_ :: Traversable f => (a -> b -> (a, c)) -> a -> f b -> f c Source

mapAccumR_ :: Traversable f => (a -> b -> (a, c)) -> a -> f b -> f c Source

Open functions

holes :: Traversable f => f a -> f (a, a -> f a) Source

The children together with functions replacing that particular child.

holesList :: Traversable f => f a -> [(a, a -> f a)] Source

apply :: Traversable f => (a -> a) -> f a -> f (f a) Source

Apply the given function to each child in turn.

builder :: Traversable f => f a -> [b] -> f b Source

Builds up a structure from a list of the children. It is unsafe in the sense that it will throw an exception if there are not enough elements in the list.

Individual elements

project :: Foldable f => Int -> f a -> Maybe a Source

Extracts the ith child.

unsafeProject :: Foldable f => Int -> f a -> a Source

sizeF :: Foldable f => f a -> Int Source

Number of children. This is the generalization of length to foldable functors:

sizeF x = length (toList x)

Enumerations

enumerate :: Traversable f => f a -> (Int, f (Int, a)) Source

Enumerates children from the left to the right, starting with zero. Also returns the number of children. This is just a simple application of mapAccumL.

enumerateWith :: Traversable f => (Int -> a -> b) -> f a -> (Int, f b) Source

enumerateWith_ :: Traversable f => (Int -> a -> b) -> f a -> f b Source

Shapes

data Hole Source

This a data type defined to be a place-holder for childs. It is used in tree drawing, hashing, and Shape.

It is deliberately not made an instance of Show, so that you can choose your preferred style. For example, an acceptable choice is

instance Show Hole where show _ = "_"

Constructors

Hole 

Instances

data Shape f Source

A type encoding the "shape" of the functor data: We ignore all the fields whose type is the parameter type, but remember the rest:

newtype Shape f = Shape { unShape :: f Hole }

This can be used to decide whether two realizations are compatible.

Instances

EqF f => Eq (Shape f) Source 
OrdF f => Ord (Shape f) Source 
(Functor f, ShowF f) => Show (Shape f) Source 

shape :: Functor f => f a -> Shape f Source

Extracting the "shape" of the functor

Zips

zipF :: (Traversable f, EqF f) => f a -> f b -> Maybe (f (a, b)) Source

Zips two structures if they are compatible.

unzipF :: Functor f => f (a, b) -> (f a, f b) Source

zipWithF :: (Traversable f, EqF f) => (a -> b -> c) -> f a -> f b -> Maybe (f c) Source

Zipping two structures using a function.

unsafeZipWithF :: Traversable f => (a -> b -> c) -> f a -> f b -> f c Source

Unsafe version of zipWithF: does not check if the two structures are compatible. It is left-biased in the sense that the structure of the second argument is retained.

zipWithFM :: (Traversable f, EqF f, Monad m) => (a -> b -> m c) -> f a -> f b -> m (Maybe (f c)) Source

Monadic version of zipWithF. TODO: better name?

unsafeZipWithFM :: (Traversable f, Monad m) => (a -> b -> m c) -> f a -> f b -> m (f c) Source