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 | Haskell98 |
- 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
- gapo :: Corecursive t => (b -> Base t b) -> (a -> Base t (Either b a)) -> a -> t
- gcata :: (Recursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (w a) -> a) -> t -> a
- zygo :: Recursive t => (Base t b -> b) -> (Base t (b, a) -> a) -> t -> a
- gzygo :: (Recursive t, Comonad w) => (Base t b -> b) -> (forall c. Base t (w c) -> w (Base t c)) -> (Base t (EnvT b w a) -> a) -> t -> a
- histo :: Recursive t => (Base t (Cofree (Base t) a) -> a) -> t -> a
- ghisto :: (Recursive t, Functor h) => (forall b. Base t (h b) -> h (Base t b)) -> (Base t (Cofree h a) -> a) -> t -> a
- futu :: Corecursive t => (a -> Base t (Free (Base t) a)) -> a -> t
- chrono :: Functor f => (f (Cofree f b) -> b) -> (a -> f (Free f a)) -> a -> b
- gchrono :: (Functor f, Functor w, Functor m) => (forall c. f (w c) -> w (f c)) -> (forall c. m (f c) -> f (m c)) -> (f (Cofree w b) -> b) -> (a -> f (Free m a)) -> a -> b
- distCata :: Functor f => f (Identity a) -> Identity (f a)
- distPara :: Corecursive t => Base t (t, a) -> (t, Base t a)
- distParaT :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> Base t (EnvT t w a) -> EnvT t w (Base t a)
- distZygo :: Functor f => (f b -> b) -> f (b, a) -> (b, f a)
- distZygoT :: (Functor f, Comonad w) => (f b -> b) -> (forall c. f (w c) -> w (f c)) -> f (EnvT b w a) -> EnvT b w (f a)
- distHisto :: Functor f => f (Cofree f a) -> Cofree f (f a)
- distGHisto :: (Functor f, Functor h) => (forall b. f (h b) -> h (f b)) -> f (Cofree h a) -> Cofree h (f a)
- distFutu :: Functor f => Free f (f a) -> f (Free f a)
- distGFutu :: (Functor f, Functor h) => (forall b. h (f b) -> f (h b)) -> Free h (f a) -> f (Free h a)
- class Functor (Base t) => Corecursive t where
- gana :: (Corecursive t, Monad m) => (forall b. m (Base t b) -> Base t (m b)) -> (a -> Base t (m a)) -> a -> t
- distAna :: Functor f => Identity (f a) -> f (Identity a)
- distApo :: Recursive t => Either t (Base t a) -> Base t (Either t a)
- distGApo :: Functor f => (b -> f b) -> Either b (f a) -> f (Either b a)
- distGApoT :: (Functor f, Functor m) => (b -> f b) -> (forall c. m (f c) -> f (m c)) -> ExceptT b m (f a) -> f (ExceptT b m a)
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- ghylo :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b
- refix :: (Recursive s, Corecursive t, Base s ~ Base t) => s -> t
- fold :: Recursive t => (Base t a -> a) -> t -> a
- gfold :: (Recursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (w a) -> a) -> t -> a
- unfold :: Corecursive t => (a -> Base t a) -> a -> t
- gunfold :: (Corecursive t, Monad m) => (forall b. m (Base t b) -> Base t (m b)) -> (a -> Base t (m a)) -> a -> t
- refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- grefold :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b
- 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
- zygoHistoPrepro :: (Corecursive t, Recursive t) => (Base t b -> b) -> (forall c. Base t c -> Base t c) -> (Base t (EnvT b (Cofree (Base t)) a) -> a) -> t -> a
Base functors for fixed points
type family Base t :: * -> * Source #
type Base Natural Source # | |
type Base [a] Source # | |
type Base (Maybe a) Source # | |
type Base (NonEmpty a) Source # | |
type Base (Nu f) Source # | |
type Base (Mu f) Source # | |
type Base (Fix f) Source # | |
type Base (Either a b) Source # | |
type Base (Cofree f a) Source # | |
type Base (F f a) Source # | |
type Base (Free f a) Source # | |
type Base (CofreeT f w a) Source # | |
type Base (FreeT f m a) Source # | |
Base functor of []
.
Eq2 ListF Source # | |
Ord2 ListF Source # | |
Read2 ListF Source # | |
Show2 ListF Source # | |
Bifunctor ListF Source # | |
Bitraversable ListF Source # | |
Bifoldable ListF Source # | |
Functor (ListF a) Source # | |
Foldable (ListF a) Source # | |
Traversable (ListF a) Source # | |
Generic1 (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 # | |
(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
Mu (forall a. (f a -> a) -> a) |
Folding
class Functor (Base t) => Recursive t where Source #
project :: t -> Base t t Source #
cata :: (Base t a -> a) -> t -> a Source #
para :: (Base t (t, a) -> a) -> t -> a Source #
gpara :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (EnvT t w a) -> a) -> t -> a Source #
prepro :: Corecursive t => (forall b. Base t b -> Base t b) -> (Base t a -> a) -> t -> a Source #
Fokkinga's prepromorphism
gprepro :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (forall c. Base t c -> Base t c) -> (Base t (w a) -> a) -> t -> a Source #
Recursive Natural Source # | |
Recursive [a] Source # | |
Recursive (Maybe a) Source # | |
Recursive (NonEmpty a) Source # | |
Functor f => Recursive (Nu f) Source # | |
Functor f => Recursive (Mu f) Source # | |
Functor f => Recursive (Fix f) Source # | |
Recursive (Either a b) Source # | |
Functor f => Recursive (Cofree f a) Source # | |
Functor f => Recursive (F f a) Source # | |
Functor f => Recursive (Free f a) Source # | |
(Functor w, Functor f) => Recursive (CofreeT f w a) Source # | |
(Functor m, Functor f) => Recursive (FreeT f m a) Source # | |
Combinators
:: (Recursive t, Comonad w) | |
=> (forall b. Base t (w b) -> w (Base t b)) | a distributive law |
-> (Base t (w a) -> a) | a (Base t)-w-algebra |
-> t | fixed point |
-> a |
A generalized catamorphism
gzygo :: (Recursive t, Comonad w) => (Base t b -> b) -> (forall c. Base t (w c) -> w (Base t c)) -> (Base t (EnvT b w a) -> a) -> t -> a Source #
histo :: Recursive t => (Base t (Cofree (Base t) a) -> a) -> t -> a Source #
Course-of-value iteration
ghisto :: (Recursive t, Functor h) => (forall b. Base t (h b) -> h (Base t b)) -> (Base t (Cofree h a) -> a) -> t -> a Source #
gchrono :: (Functor f, Functor w, Functor m) => (forall c. f (w c) -> w (f c)) -> (forall c. m (f c) -> f (m c)) -> (f (Cofree w b) -> b) -> (a -> f (Free m a)) -> a -> b Source #
Distributive laws
distParaT :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> Base t (EnvT t w a) -> EnvT t w (Base t a) Source #
:: Functor f | |
=> (f b -> b) | |
-> f (b, a) -> (b, f a) | A distributive for semi-mutual recursion |
distZygoT :: (Functor f, Comonad w) => (f b -> b) -> (forall c. f (w c) -> w (f c)) -> f (EnvT b w a) -> EnvT b w (f a) Source #
distGHisto :: (Functor f, Functor h) => (forall b. f (h b) -> h (f b)) -> f (Cofree h a) -> Cofree h (f a) Source #
distGFutu :: (Functor f, Functor h) => (forall b. h (f b) -> f (h b)) -> Free h (f a) -> f (Free h a) Source #
Unfolding
class Functor (Base t) => Corecursive t where Source #
embed :: Base t t -> t Source #
ana :: (a -> Base t a) -> a -> t Source #
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
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 # | |
Functor f => Corecursive (Cofree f a) Source # | |
Functor f => Corecursive (F f a) Source # | |
Functor f => Corecursive (Free f a) Source # | It may be better to work with the instance for |
(Functor w, Functor f) => Corecursive (CofreeT f w a) Source # | |
(Functor m, Functor f) => Corecursive (FreeT f m a) Source # | |
Combinators
:: (Corecursive t, Monad m) | |
=> (forall b. m (Base t b) -> Base t (m b)) | a distributive law |
-> (a -> Base t (m a)) | a (Base t)-m-coalgebra |
-> a | seed |
-> t |
A generalized anamorphism
Distributive laws
distGApoT :: (Functor f, Functor m) => (b -> f b) -> (forall c. m (f c) -> f (m c)) -> ExceptT b m (f a) -> f (ExceptT b m a) Source #
Refolding
ghylo :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b Source #
A generalized hylomorphism
Changing representation
Common names
:: (Recursive t, Comonad w) | |
=> (forall b. Base t (w b) -> w (Base t b)) | a distributive law |
-> (Base t (w a) -> a) | a (Base t)-w-algebra |
-> t | fixed point |
-> a |
A generalized catamorphism
unfold :: Corecursive t => (a -> Base t a) -> a -> t Source #
:: (Corecursive t, Monad m) | |
=> (forall b. m (Base t b) -> Base t (m b)) | a distributive law |
-> (a -> Base t (m a)) | a (Base t)-m-coalgebra |
-> a | seed |
-> t |
A generalized anamorphism
grefold :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b Source #
A generalized hylomorphism
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/
Zygohistomorphic prepromorphisms
zygoHistoPrepro :: (Corecursive t, Recursive t) => (Base t b -> b) -> (forall c. Base t c -> Base t c) -> (Base t (EnvT b (Cofree (Base t)) a) -> a) -> t -> a Source #
Zygohistomorphic prepromorphisms:
A corrected and modernized version of http://www.haskell.org/haskellwiki/Zygohistomorphic_prepromorphisms