free-4.6.1: Monads for free

PortabilityMPTCs, fundeps
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Comonad.Cofree

Contents

Description

Cofree comonads

Synopsis

Documentation

data Cofree f a Source

The Cofree Comonad of a functor f.

Formally

A Comonad v is a cofree Comonad for f if every comonad homomorphism 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 forms the a comonad for a non-empty list.
  • Cofree (Const b) is a product.
  • Cofree Identity forms an infinite stream.
  • Cofree ((->) b)' describes a Moore machine with states labeled with values of type a, and transitions on edges of type 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.

Constructors

a :< (f (Cofree f a)) 

Instances

ComonadTrans Cofree

This is not a true Comonad transformer, but this instance is convenient.

ComonadTraced m w => ComonadTraced m (Cofree w) 
ComonadStore s w => ComonadStore s (Cofree w) 
ComonadEnv e w => ComonadEnv e (Cofree w) 
Functor f => ComonadCofree f (Cofree f) 
Alternative f => Monad (Cofree f) 
Functor f => Functor (Cofree f) 
Typeable1 f => Typeable1 (Cofree f) 
Alternative f => Applicative (Cofree f) 
Foldable f => Foldable (Cofree f) 
Traversable f => Traversable (Cofree f) 
(Alternative f, MonadZip f) => MonadZip (Cofree f) 
Functor f => Comonad (Cofree f) 
ComonadApply f => ComonadApply (Cofree f) 
Distributive f => Distributive (Cofree f) 
Traversable1 f => Traversable1 (Cofree f) 
Foldable1 f => Foldable1 (Cofree f) 
Apply f => Apply (Cofree f) 
Functor f => Extend (Cofree f) 
(Eq (f (Cofree f a)), Eq a) => Eq (Cofree f a) 
(Typeable1 f, Data (f (Cofree f a)), Data a) => Data (Cofree f a) 
(Ord (f (Cofree f a)), Ord a) => Ord (Cofree f a) 
(Read (f (Cofree f a)), Read a) => Read (Cofree f a) 
(Show (f (Cofree f a)), Show a) => Show (Cofree f a) 
(Typeable1 f, Typeable a) => Typeable (Cofree f a) 

class (Functor f, Comonad w) => ComonadCofree f w | w -> f whereSource

Allows you to peel a layer off a cofree comonad.

Methods

unwrap :: w a -> f (w a)Source

Remove a layer.

section :: Comonad f => f a -> Cofree f aSource

coiter :: Functor f => (a -> f a) -> a -> Cofree f aSource

Use coiteration to generate a cofree comonad from a seed.

coiter f = unfold (id &&& f)

unfold :: Functor f => (b -> (a, f b)) -> b -> Cofree f aSource

Unfold a cofree comonad from a seed.

Lenses into cofree comonads

_extract :: Functor f => (a -> f a) -> Cofree g a -> f (Cofree g a)Source

This is a lens that can be used to read or write from the target of extract.

Using (^.) from the lens package:

foo ^. _extract == extract foo

For more on lenses see the lens package on hackage

_extract :: Lens' (Cofree g a) a

_unwrap :: Functor f => (g (Cofree g a) -> f (g (Cofree g a))) -> Cofree g a -> f (Cofree g a)Source

This is a lens that can be used to read or write to the tails of a Cofree Comonad.

Using (^.) from the lens package:

foo ^. _unwrap == unwrap foo

For more on lenses see the lens package on hackage

_unwrap :: Lens' (Cofree g a) (g (Cofree g a))

telescoped :: (Functor f, Functor g) => [(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 a Lens into a Cofree f given a list of lenses into the base functor.

For more on lenses see the lens package on hackage.

telescoped :: Functor g => [Lens' (Cofree g a) (g (Cofree g a))] -> Lens' (Cofree g a) a