comonad-transformers-1.6.3: Comonad transformers

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>

Control.Comonad.Trans.Stream

Contents

Description

The f-branching stream comonad, aka the cofree comonad for a Functor f.

Provided here as a comonad-transformer version of the 'ListT done right' monad transformer.

Synopsis

The Stream comonad

type Stream f = StreamT f IdentitySource

Isomorphic to the definition:

 data Stream f a = a :< f (Stream f a)

stream :: a -> f (Stream f a) -> Stream f aSource

cons onto an f-branching stream

runStream :: Stream f a -> (a, f (Stream f a))Source

uncons from an f-branching stream

unfolds :: Functor f => (a -> (b, f a)) -> a -> Stream f bSource

unfold a stream from a seed.

The Stream comonad transformer

data StreamT f w a Source

The f-branching stream comonad transformer is a comonadic version of the "ListT done Right" monad transformer. You can extract the underlying comonadic value by using lower or runStream

Constructors

StreamT 

Fields

runStreamT :: w (Node f w a)
 

Instances

Functor f => ComonadTrans (StreamT f) 
Functor f => ComonadHoist (StreamT f) 
(Functor w, Functor f) => Functor (StreamT f w) 
(Typeable1 f, Typeable1 w) => Typeable1 (StreamT f w) 
(Foldable w, Foldable f) => Foldable (StreamT f w) 
(Traversable w, Traversable f) => Traversable (StreamT f w) 
(Comonad w, Functor f) => Comonad (StreamT f w) 
(Comonad w, Functor f) => Extend (StreamT f w) 
(Comonad w, Apply w, Apply f) => Apply (StreamT f w) 
(Typeable1 f, Typeable1 w, Data (w (Node f w a)), Data (Node f w a), Data (f (StreamT f w a)), Data a) => Data (StreamT f w a) 
(Show (w (Node f w a)), Show (Node f w a), Show a, Show (f (StreamT f w a))) => Show (StreamT f w a) 
(Typeable1 f, Typeable1 w, Typeable a) => Typeable (StreamT f w a) 

Operations

tails :: Comonad w => StreamT f w a -> f (StreamT f w a)Source

unfoldsW :: (Comonad w, Functor f) => (w a -> (b, f a)) -> w a -> StreamT f w bSource

StreamT nodes

data Node f w a Source

Constructors

a :< (f (StreamT f w a)) 

Instances

(Functor w, Functor f) => Functor (Node f w) 
(Typeable1 f, Typeable1 w) => Typeable1 (Node f w) 
(Typeable1 f, Typeable1 w, Data a, Data (f (StreamT f w a)), Data (StreamT f w a)) => Data (Node f w a) 
(Show a, Show (StreamT f w a), Show (f (StreamT f w a)), Show (w (Node f w a))) => Show (Node f w a) 
(Typeable1 f, Typeable1 w, Typeable a) => Typeable (Node f w a)