free-4.2: Monads for free

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

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) 
Functor f => ComonadTrans (CofreeT f) 
(Functor f, Functor w) => Functor (CofreeT f w) 
(Typeable1 f, Typeable1 w) => Typeable1 (CofreeT f w) 
(Foldable f, Foldable w) => Foldable (CofreeT f w) 
(Traversable f, Traversable w) => Traversable (CofreeT f w) 
(Functor f, Comonad w) => Comonad (CofreeT f w) 
Eq (w (CofreeF f a (CofreeT f w a))) => Eq (CofreeT f w a) 
(Typeable1 f, Typeable1 w, Typeable a, Data (w (CofreeF f a (CofreeT f w a))), Data a) => Data (CofreeT f w a) 
Ord (w (CofreeF f a (CofreeT f w a))) => Ord (CofreeT f w a) 
Read (w (CofreeF f a (CofreeT f w a))) => Read (CofreeT f w a) 
Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) 

data CofreeF f a b Source

This is the base functor of the cofree comonad transformer.

Constructors

a :< (f b) 

Instances

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

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.

headF :: CofreeF f a b -> aSource

Extract the head of the base functor

tailF :: CofreeF f a b -> f bSource

Extract the tails of the base functor

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

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