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

Safe HaskellSafe-Infered

Data.Generics.Fixplate.Open

Contents

Description

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

Synopsis

Documentation

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

List of elements of a structure.

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 cSource

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

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 bSource

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 aSource

Extracts the ith child.

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

sizeF :: Foldable f => f a -> IntSource

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 bSource

Zips

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 () }

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

Instances

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

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

Extracting the "shape" of the functor

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 cSource

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