Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
"Open" functions, working on functors instead of trees.
- toList :: Foldable t => forall a. t a -> [a]
- toRevList :: Foldable f => f a -> [a]
- mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumL_ :: Traversable f => (a -> b -> (a, c)) -> a -> f b -> f c
- mapAccumR_ :: Traversable f => (a -> b -> (a, c)) -> a -> f b -> f c
- holes :: Traversable f => f a -> f (a, a -> f a)
- holesList :: Traversable f => f a -> [(a, a -> f a)]
- apply :: Traversable f => (a -> a) -> f a -> f (f a)
- builder :: Traversable f => f a -> [b] -> f b
- project :: Foldable f => Int -> f a -> Maybe a
- unsafeProject :: Foldable f => Int -> f a -> a
- sizeF :: Foldable f => f a -> Int
- enumerate :: Traversable f => f a -> (Int, f (Int, a))
- enumerateWith :: Traversable f => (Int -> a -> b) -> f a -> (Int, f b)
- enumerateWith_ :: Traversable f => (Int -> a -> b) -> f a -> f b
- data Hole = Hole
- data Shape f
- shape :: Functor f => f a -> Shape f
- zipF :: (Traversable f, EqF f) => f a -> f b -> Maybe (f (a, b))
- unzipF :: Functor f => f (a, b) -> (f a, f b)
- zipWithF :: (Traversable f, EqF f) => (a -> b -> c) -> f a -> f b -> Maybe (f c)
- unsafeZipWithF :: Traversable f => (a -> b -> c) -> f a -> f b -> f c
- zipWithFM :: (Traversable f, EqF f, Monad m) => (a -> b -> m c) -> f a -> f b -> m (Maybe (f c))
- unsafeZipWithFM :: (Traversable f, Monad m) => (a -> b -> m c) -> f a -> f b -> m (f c)
Documentation
Accumulating maps
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #
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
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
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 _ = "_"
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.
Zips
zipF :: (Traversable f, EqF f) => f a -> f b -> Maybe (f (a, b)) Source #
Zips two structures if they are compatible.
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 #