Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
- type family Base t :: * -> *
- newtype Fix f = Fix (f (Fix f))
- newtype Mu f = Mu (forall a. (f a -> a) -> a)
- data Nu f where
- data family Prim t :: * -> *
- class Functor (Base t) => Foldable t where
- project :: t -> Base t t
- cata :: (Base t a -> a) -> t -> a
- para :: (Base t (t, a) -> a) -> t -> a
- gpara :: (Unfoldable t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (EnvT t w a) -> a) -> t -> a
- prepro :: Unfoldable t => (forall b. Base t b -> Base t b) -> (Base t a -> a) -> t -> a
- gprepro :: (Unfoldable 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
- gapo :: Unfoldable t => (b -> Base t b) -> (a -> Base t (Either b a)) -> a -> t
- gcata :: (Foldable t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (w a) -> a) -> t -> a
- zygo :: Foldable t => (Base t b -> b) -> (Base t (b, a) -> a) -> t -> a
- gzygo :: (Foldable 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 :: Foldable t => (Base t (Cofree (Base t) a) -> a) -> t -> a
- ghisto :: (Foldable t, Functor h) => (forall b. Base t (h b) -> h (Base t b)) -> (Base t (Cofree h a) -> a) -> t -> a
- futu :: Unfoldable t => (a -> Base t (Free (Base t) a)) -> a -> t
- distCata :: Functor f => f (Identity a) -> Identity (f a)
- distPara :: Unfoldable t => Base t (t, a) -> (t, Base t a)
- distParaT :: (Unfoldable 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) => Unfoldable t where
- embed :: Base t t -> t
- ana :: (a -> Base t a) -> a -> t
- apo :: Foldable t => (a -> Base t (Either t a)) -> a -> t
- postpro :: Foldable t => (forall b. Base t b -> Base t b) -> (a -> Base t a) -> a -> t
- gpostpro :: (Foldable 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
- gana :: (Unfoldable 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 :: Foldable 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)
- 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 :: (Foldable s, Unfoldable t, Base s ~ Base t) => s -> t
- fold :: Foldable t => (Base t a -> a) -> t -> a
- gfold :: (Foldable t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (w a) -> a) -> t -> a
- unfold :: Unfoldable t => (a -> Base t a) -> a -> t
- gunfold :: (Unfoldable 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 :: (Unfoldable t, Foldable 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
Fixed points
Mu (forall a. (f a -> a) -> a) |
Folding
class Functor (Base t) => Foldable t whereSource
project :: t -> Base t tSource
:: (Base t a -> a) | a (Base t)-algebra |
-> t | fixed point |
-> a | result |
para :: (Base t (t, a) -> a) -> t -> aSource
gpara :: (Unfoldable t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (EnvT t w a) -> a) -> t -> aSource
prepro :: Unfoldable t => (forall b. Base t b -> Base t b) -> (Base t a -> a) -> t -> aSource
Fokkinga's prepromorphism
gprepro :: (Unfoldable 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 -> aSource
Combinators
:: (Foldable 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 :: (Foldable 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 -> aSource
ghisto :: (Foldable t, Functor h) => (forall b. Base t (h b) -> h (Base t b)) -> (Base t (Cofree h a) -> a) -> t -> aSource
Distributive laws
distPara :: Unfoldable t => Base t (t, a) -> (t, Base t a)Source
distParaT :: (Unfoldable 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) => Unfoldable t whereSource
:: (a -> Base t a) | a (Base t)-coalgebra |
-> a | seed |
-> t | resulting fixed point |
apo :: Foldable t => (a -> Base t (Either t a)) -> a -> tSource
postpro :: Foldable t => (forall b. Base t b -> Base t b) -> (a -> Base t a) -> a -> tSource
Fokkinga's postpromorphism
gpostpro :: (Foldable 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 -> tSource
A generalized postpromorphism
Unfoldable [a] | |
Unfoldable (Maybe a) | |
Functor f => Unfoldable (Nu f) | |
Functor f => Unfoldable (Mu f) | |
Functor f => Unfoldable (Fix f) | |
Unfoldable (Either a b) |
Combinators
:: (Unfoldable 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
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 -> bSource
A generalized hylomorphism
Changing representation
Common names
:: (Foldable 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 :: Unfoldable t => (a -> Base t a) -> a -> tSource
:: (Unfoldable 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 -> bSource
A generalized hylomorphism
Mendler-style
mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> cSource
Mendler-style course-of-value iteration
Elgot (co)algebras
coelgot :: Functor f => ((a, f b) -> b) -> (a -> f a) -> a -> bSource
Elgot coalgebras: http://comonad.com/reader/2008/elgot-coalgebras/
Zygohistomorphic prepromorphisms
zygoHistoPrepro :: (Unfoldable t, Foldable t) => (Base t b -> b) -> (forall c. Base t c -> Base t c) -> (Base t (EnvT b (Cofree (Base t)) a) -> a) -> t -> aSource
Zygohistomorphic prepromorphisms:
A corrected and modernized version of http://www.haskell.org/haskellwiki/Zygohistomorphic_prepromorphisms