Copyright | (C) 2008-2013 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | MPTCs, fundeps |
Safe Haskell | Safe |
Language | Haskell2010 |
Cofree comonads
- data Cofree f a = a :< (f (Cofree f a))
- class (Functor f, Comonad w) => ComonadCofree f w | w -> f where
- unwrap :: w a -> f (w a)
- section :: Comonad f => f a -> Cofree f a
- coiter :: Functor f => (a -> f a) -> a -> Cofree f a
- coiterW :: (Comonad w, Functor f) => (w a -> f (w a)) -> w a -> Cofree f a
- unfold :: Functor f => (b -> (a, f b)) -> b -> Cofree f a
- unfoldM :: (Traversable f, Monad m) => (b -> m (a, f b)) -> b -> m (Cofree f a)
- hoistCofree :: Functor f => (forall x. f x -> g x) -> Cofree f a -> Cofree g a
- _extract :: Functor f => (a -> f a) -> Cofree g a -> f (Cofree g a)
- _unwrap :: Functor f => (g (Cofree g a) -> f (g (Cofree g a))) -> Cofree g a -> f (Cofree g a)
- telescoped :: Functor f => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (a -> f a) -> Cofree g a -> f (Cofree g a)
Documentation
The Cofree
Comonad
of a functor f
.
Formally
A Comonad
v
is a cofree Comonad
for f
if every comonad homomorphism
from another comonad w
to v
is equivalent to a natural transformation
from w
to f
.
A cofree
functor is right adjoint to a forgetful functor.
Cofree is a functor from the category of functors to the category of comonads
that is right adjoint to the forgetful functor from the category of comonads
to the category of functors that forgets how to extract
and
duplicate
, leaving you with only a Functor
.
In practice, cofree comonads are quite useful for annotating syntax trees, or talking about streams.
A number of common comonads arise directly as cofree comonads.
For instance,
forms the a comonad for a non-empty list.Cofree
Maybe
is a product.Cofree
(Const
b)
forms an infinite stream.Cofree
Identity
describes a Moore machine with states labeled with values of type a, and transitions on edges of type b.Cofree
((->) b)'
Furthermore, if the functor f
forms a monoid (for example, by
being an instance of Alternative
), the resulting Comonad
is
also a Monad
. See
Monadic Augment and Generalised Shortcut Fusion by Neil Ghani et al., Section 4.3
for more details.
In particular, if f a ≡ [a]
, the
resulting data structure is a Rose tree.
For a practical application, check
Higher Dimensional Trees, Algebraically by Neil Ghani et al.
class (Functor f, Comonad w) => ComonadCofree f w | w -> f where Source
Allows you to peel a layer off a cofree comonad.
ComonadCofree [] Tree Source | |
ComonadCofree Maybe NonEmpty Source | |
ComonadCofree f w => ComonadCofree f (IdentityT w) Source | |
Functor f => ComonadCofree f (Cofree f) Source | |
Comonad w => ComonadCofree Identity (CoiterT w) Source | |
(ComonadCofree f w, Monoid m) => ComonadCofree f (TracedT m w) Source | |
ComonadCofree f w => ComonadCofree f (StoreT s w) Source | |
ComonadCofree f w => ComonadCofree f (EnvT e w) Source | |
(Functor f, Comonad w) => ComonadCofree f (CofreeT f w) Source | |
ComonadCofree (Const b) ((,) b) Source |
coiterW :: (Comonad w, Functor f) => (w a -> f (w a)) -> w a -> Cofree f a Source
Like coiter for comonadic values.
unfold :: Functor f => (b -> (a, f b)) -> b -> Cofree f a Source
Unfold a cofree comonad from a seed.
unfoldM :: (Traversable f, Monad m) => (b -> m (a, f b)) -> b -> m (Cofree f a) Source
Unfold a cofree comonad from a seed, monadically.
hoistCofree :: Functor f => (forall x. f x -> g x) -> Cofree f a -> Cofree g a Source
Lenses into cofree comonads
_unwrap :: Functor f => (g (Cofree g a) -> f (g (Cofree g a))) -> Cofree g a -> f (Cofree g a) Source
telescoped :: Functor f => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (a -> f a) -> Cofree g a -> f (Cofree g a) Source
Construct an Lens
into a
given a list of lenses into the base functor.
When the input list is empty, this is equivalent to Cofree
g_extract
.
When the input list is non-empty, this composes the input lenses
with _unwrap
to walk through the
before using
Cofree
g_extract
to get the element at the final location.
For more on lenses see the lens
package on hackage.
telescoped :: [Lens' (g (Cofree
g a)) (Cofree
g a)] -> Lens' (Cofree
g a) a
telescoped :: [Traversal' (g (Cofree
g a)) (Cofree
g a)] -> Traversal' (Cofree
g a) a
telescoped :: [Getter (g (Cofree
g a)) (Cofree
g a)] -> Getter (Cofree
g a) a
telescoped :: [Fold (g (Cofree
g a)) (Cofree
g a)] -> Fold (Cofree
g a) a
telescoped :: [Setter' (g (Cofree
g a)) (Cofree
g a)] -> Setter' (Cofree
g a) a