| 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 | 
Control.Comonad.Cofree
Contents
Description
Cofree comonads
- data Cofree f a = a :< (f (Cofree f a))
- class (Functor f, Comonad w) => ComonadCofree f w | w -> f where
- 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)
- telescoped_ :: Functor f => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a)
- shoots :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a)
- leaves :: (Applicative f, Traversable g) => (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,
- Cofree- Maybe
- Cofree(- Constb)
- Cofree- Identity
- 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.
Instances
class (Functor f, Comonad w) => ComonadCofree f w | w -> f where Source #
Allows you to peel a layer off a cofree comonad.
Minimal complete definition
Instances
| ComonadCofree [] Tree Source # | |
| ComonadCofree Maybe NonEmpty 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 # | |
| ComonadCofree f w => ComonadCofree f (IdentityT * 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.
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 Cofree g_extract.
 When the input list is non-empty, this composes the input lenses
 with _unwrap to walk through the Cofree g_extract to get the element at the final location.
For more on lenses see the lens package on hackage.
telescoped :: [Lens' (g (Cofreeg a)) (Cofreeg a)] -> Lens' (Cofreeg a) a
telescoped :: [Traversal' (g (Cofreeg a)) (Cofreeg a)] -> Traversal' (Cofreeg a) a
telescoped :: [Getter (g (Cofreeg a)) (Cofreeg a)] -> Getter (Cofreeg a) a
telescoped :: [Fold (g (Cofreeg a)) (Cofreeg a)] -> Fold (Cofreeg a) a
telescoped :: [Setter' (g (Cofreeg a)) (Cofreeg a)] -> Setter' (Cofreeg a) a
telescoped_ :: Functor f => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a) Source #
Construct an Lens into a Cofree gtelescoped is that telescoped focuses on a single value, but this focuses on the entire remaining subtree.
 When the input list is empty, this is equivalent to id.
 When the input list is non-empty, this composes the input lenses
 with _unwrap to walk through the Cofree g
For more on lenses see the lens package on hackage.
telescoped :: [Lens' (g (Cofreeg a)) (Cofreeg a)] -> Lens' (Cofreeg a) (Cofreeg a)
telescoped :: [Traversal' (g (Cofreeg a)) (Cofreeg a)] -> Traversal' (Cofreeg a) (Cofreeg a)
telescoped :: [Getter (g (Cofreeg a)) (Cofreeg a)] -> Getter (Cofreeg a) (Cofreeg a)
telescoped :: [Fold (g (Cofreeg a)) (Cofreeg a)] -> Fold (Cofreeg a) (Cofreeg a)
telescoped :: [Setter' (g (Cofreeg a)) (Cofreeg a)] -> Setter' (Cofreeg a) (Cofreeg a)
shoots :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a) Source #
A Traversal' that gives access to all non-leaf a elements of a
 Cofree gx from (x :< xs) where
 null xs is False.
Because this doesn't give access to all values in the Cofree g
shoots :: Traversable g => Traversal' (Cofree g a) a
N.B. On GHC < 7.9, this is slightly less flexible, as it has to
 use null (toList xs) instead.
leaves :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a) Source #
A Traversal' that gives access to all leaf a elements of a
 Cofree gx from (x :< xs) where
 null xs is True.
Because this doesn't give access to all values in the Cofree g
shoots :: Traversable g => Traversal' (Cofree g a) a
N.B. On GHC < 7.9, this is slightly less flexible, as it has to
 use null (toList xs) instead.