| Copyright | (C) 2008-2015 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Data.Functor.Foldable
Contents
Description
- type family Base t :: * -> *
- data ListF a b
- newtype Fix f = Fix (f (Fix f))
- unfix :: Fix f -> f (Fix f)
- newtype Mu f = Mu (forall a. (f a -> a) -> a)
- data Nu f where
- class Functor (Base t) => Recursive t where
- zygo :: Recursive t => (Base t b -> b) -> (Base t (b, a) -> a) -> t -> a
- mutu :: Recursive t => (Base t (a, a) -> a) -> (Base t (a, a) -> a) -> t -> a
- class Functor (Base t) => Corecursive t where
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- refix :: (Recursive s, Corecursive t, Base s ~ Base t) => s -> t
- mcata :: (forall y. (y -> c) -> f y -> c) -> Fix f -> c
- mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c
- elgot :: Functor f => (f a -> a) -> (b -> Either a (f b)) -> b -> a
- coelgot :: Functor f => ((a, f b) -> b) -> (a -> f a) -> a -> b
Base functors for fixed points
Base functor of [].
Instances
| Bitraversable ListF Source # | |
| Bifoldable ListF Source # | |
| Bifunctor ListF Source # | |
| Eq2 ListF Source # | |
| Ord2 ListF Source # | |
| Read2 ListF Source # | |
| Show2 ListF Source # | |
| Functor (ListF a) Source # | |
| Foldable (ListF a) Source # | |
| Traversable (ListF a) Source # | |
| Eq a => Eq1 (ListF a) Source # | |
| Ord a => Ord1 (ListF a) Source # | |
| Read a => Read1 (ListF a) Source # | |
| Show a => Show1 (ListF a) Source # | |
| Generic1 * (ListF a) Source # | |
| (Eq b, Eq a) => Eq (ListF a b) Source # | |
| (Ord b, Ord a) => Ord (ListF a b) Source # | |
| (Read b, Read a) => Read (ListF a b) Source # | |
| (Show b, Show a) => Show (ListF a b) Source # | |
| Generic (ListF a b) Source # | |
| type Rep1 * (ListF a) Source # | |
| type Rep (ListF a b) Source # | |
Fixed points
Instances
Constructors
| Mu (forall a. (f a -> a) -> a) |
Folding
class Functor (Base t) => Recursive t where Source #
Minimal complete definition
Combinators
Unfolding
class Functor (Base t) => Corecursive t where Source #
Minimal complete definition
Methods
embed :: Base t t -> t Source #
Arguments
| :: (a -> Base t a) | a (Base t)-coalgebra |
| -> a | seed |
| -> t | resulting fixed point |
apo :: (a -> Base t (Either t a)) -> a -> t Source #
postpro :: Recursive t => (forall b. Base t b -> Base t b) -> (a -> Base t a) -> a -> t Source #
Fokkinga's postpromorphism
gpostpro :: (Recursive t, Monad m) => (forall b. m (Base t b) -> Base t (m b)) -> (forall c. Base t c -> Base t c) -> (a -> Base t (m a)) -> a -> t Source #
A generalized postpromorphism
Instances
| Corecursive Natural Source # | |
| Corecursive [a] Source # | |
| Corecursive (Maybe a) Source # | |
| Corecursive (NonEmpty a) Source # | |
| Functor f => Corecursive (Nu f) Source # | |
| Functor f => Corecursive (Mu f) Source # | |
| Functor f => Corecursive (Fix f) Source # | |
| Corecursive (Either a b) Source # | |
Refolding
Changing representation
Mendler-style
mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c Source #
Mendler-style course-of-value iteration
Elgot (co)algebras
coelgot :: Functor f => ((a, f b) -> b) -> (a -> f a) -> a -> b Source #
Elgot coalgebras: http://comonad.com/reader/2008/elgot-coalgebras/