free-4.12.1: Monads for free

Copyright(C) 2008-2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityMPTCs, fundeps
Safe HaskellSafe
LanguageHaskell2010

Control.Comonad.Trans.Cofree

Description

The cofree comonad transformer

Synopsis

Documentation

newtype CofreeT f w a Source

This is a cofree comonad of some functor f, with a comonad w threaded through it at each level.

Constructors

CofreeT 

Fields

runCofreeT :: w (CofreeF f a (CofreeT f w a))
 

Instances

(Functor f, Comonad w) => ComonadCofree f (CofreeT f w) Source 
Functor f => ComonadTrans (CofreeT f) Source 
Alternative f => MonadTrans (CofreeT f) Source 
(Alternative f, Monad w) => Monad (CofreeT f w) Source 
(Functor f, Functor w) => Functor (CofreeT f w) Source 
(Alternative f, Applicative w) => Applicative (CofreeT f w) Source 
(Foldable f, Foldable w) => Foldable (CofreeT f w) Source 
(Traversable f, Traversable w) => Traversable (CofreeT f w) Source 
(Alternative f, MonadZip f, MonadZip m) => MonadZip (CofreeT f m) Source 
(Functor f, Comonad w) => Comonad (CofreeT f w) Source 
Eq (w (CofreeF f a (CofreeT f w a))) => Eq (CofreeT f w a) Source 
(Typeable (* -> *) f, Typeable (* -> *) w, Typeable * a, Data (w (CofreeF f a (CofreeT f w a))), Data a) => Data (CofreeT f w a) Source 
Ord (w (CofreeF f a (CofreeT f w a))) => Ord (CofreeT f w a) Source 
Read (w (CofreeF f a (CofreeT f w a))) => Read (CofreeT f w a) Source 
Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) Source 

type Cofree f = CofreeT f Identity Source

The cofree Comonad of a functor f.

cofree :: CofreeF f a (Cofree f a) -> Cofree f a Source

Wrap another layer around a cofree comonad value.

cofree is a right inverse of runCofree.

runCofree . cofree == id

runCofree :: Cofree f a -> CofreeF f a (Cofree f a) Source

Unpeel the first layer off a cofree comonad value.

runCofree is a right inverse of cofree.

cofree . runCofree == id

data CofreeF f a b Source

This is the base functor of the cofree comonad transformer.

Constructors

a :< (f b) infixr 5 

Instances

Functor f => Bifunctor (CofreeF f) Source 
Traversable f => Bitraversable (CofreeF f) Source 
Foldable f => Bifoldable (CofreeF f) Source 
Functor f => Functor (CofreeF f a) Source 
Foldable f => Foldable (CofreeF f a) Source 
Traversable f => Traversable (CofreeF f a) Source 
(Eq a, Eq (f b)) => Eq (CofreeF f a b) Source 
(Typeable (* -> *) f, Typeable * a, Typeable * b, Data a, Data (f b), Data b) => Data (CofreeF f a b) Source 
(Ord a, Ord (f b)) => Ord (CofreeF f a b) Source 
(Read a, Read (f b)) => Read (CofreeF f a b) Source 
(Show a, Show (f b)) => Show (CofreeF f a b) Source 

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

Allows you to peel a layer off a cofree comonad.

Methods

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

Remove a layer.

headF :: CofreeF f a b -> a Source

Extract the head of the base functor

tailF :: CofreeF f a b -> f b Source

Extract the tails of the base functor

coiterT :: (Functor f, Comonad w) => (w a -> f (w a)) -> w a -> CofreeT f w a Source

Unfold a CofreeT comonad transformer from a coalgebra and an initial comonad.