free-5.1.10: Monads for free
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.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

Instances

Instances details
( Functor f, ComonadEnv e w) => ComonadEnv e ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

ask :: CofreeT f w a -> e Source #

( Functor f, Comonad w) => ComonadCofree f ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

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

ComonadTrans ( CofreeT f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

lower :: Comonad w => CofreeT f w a -> w a Source #

Functor f => ComonadHoist ( CofreeT f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

cohoist :: ( Comonad w, Comonad v) => ( forall x. w x -> v x) -> CofreeT f w a -> CofreeT f v a Source #

Alternative f => MonadTrans ( CofreeT f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

lift :: Monad m => m a -> CofreeT f m a Source #

( Alternative f, Monad w) => Monad ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Functor f, Functor w) => Functor ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

fmap :: (a -> b) -> CofreeT f w a -> CofreeT f w b Source #

(<$) :: a -> CofreeT f w b -> CofreeT f w a Source #

( Alternative f, Applicative w) => Applicative ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Foldable f, Foldable w) => Foldable ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Traversable f, Traversable w) => Traversable ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

traverse :: Applicative f0 => (a -> f0 b) -> CofreeT f w a -> f0 ( CofreeT f w b) Source #

sequenceA :: Applicative f0 => CofreeT f w (f0 a) -> f0 ( CofreeT f w a) Source #

mapM :: Monad m => (a -> m b) -> CofreeT f w a -> m ( CofreeT f w b) Source #

sequence :: Monad m => CofreeT f w (m a) -> m ( CofreeT f w a) Source #

( Alternative f, MonadZip f, MonadZip m) => MonadZip ( CofreeT f m) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

mzip :: CofreeT f m a -> CofreeT f m b -> CofreeT f m (a, b) Source #

mzipWith :: (a -> b -> c) -> CofreeT f m a -> CofreeT f m b -> CofreeT f m c Source #

munzip :: CofreeT f m (a, b) -> ( CofreeT f m a, CofreeT f m b) Source #

( Functor f, Comonad w) => Comonad ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Eq (w ( CofreeF f a ( CofreeT f w a))) => Eq ( CofreeT f w a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Typeable f, Typeable w, Typeable a, Data (w ( CofreeF f a ( CofreeT f w a))), Data a) => Data ( CofreeT f w a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> CofreeT f w a -> c ( CofreeT f w a) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( CofreeT f w a) Source #

toConstr :: CofreeT f w a -> Constr Source #

dataTypeOf :: CofreeT f w a -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( CofreeT f w a)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( CofreeT f w a)) Source #

gmapT :: ( forall b. Data b => b -> b) -> CofreeT f w a -> CofreeT f w a Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> CofreeT f w a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> CofreeT f w a -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> CofreeT f w a -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> CofreeT f w a -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> CofreeT f w a -> m ( CofreeT f w a) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> CofreeT f w a -> m ( CofreeT f w a) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> CofreeT f w a -> m ( CofreeT f w a) Source #

Ord (w ( CofreeF f a ( CofreeT f w a))) => Ord ( CofreeT f w a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Read (w ( CofreeF f a ( CofreeT f w a))) => Read ( CofreeT f w a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Show (w ( CofreeF f a ( CofreeT f w a))) => Show ( CofreeT f w a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

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

Instances details
Traversable f => Bitraversable ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> CofreeF f a b -> f0 ( CofreeF f c d) Source #

Foldable f => Bifoldable ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

bifold :: Monoid m => CofreeF f m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> CofreeF f a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> CofreeF f a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> CofreeF f a b -> c Source #

Functor f => Bifunctor ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

bimap :: (a -> b) -> (c -> d) -> CofreeF f a c -> CofreeF f b d Source #

first :: (a -> b) -> CofreeF f a c -> CofreeF f b c Source #

second :: (b -> c) -> CofreeF f a b -> CofreeF f a c Source #

Eq1 f => Eq2 ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

liftEq2 :: (a -> b -> Bool ) -> (c -> d -> Bool ) -> CofreeF f a c -> CofreeF f b d -> Bool Source #

Ord1 f => Ord2 ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

liftCompare2 :: (a -> b -> Ordering ) -> (c -> d -> Ordering ) -> CofreeF f a c -> CofreeF f b d -> Ordering Source #

Read1 f => Read2 ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Show1 f => Show2 ( CofreeF f) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

liftShowsPrec2 :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> ( Int -> b -> ShowS ) -> ([b] -> ShowS ) -> Int -> CofreeF f a b -> ShowS Source #

liftShowList2 :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> ( Int -> b -> ShowS ) -> ([b] -> ShowS ) -> [ CofreeF f a b] -> ShowS Source #

Generic1 ( CofreeF f a :: Type -> Type ) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep1 ( CofreeF f a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). CofreeF f a a0 -> Rep1 ( CofreeF f a) a0 Source #

to1 :: forall (a0 :: k). Rep1 ( CofreeF f a) a0 -> CofreeF f a a0 Source #

Functor f => Functor ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

fmap :: (a0 -> b) -> CofreeF f a a0 -> CofreeF f a b Source #

(<$) :: a0 -> CofreeF f a b -> CofreeF f a a0 Source #

Foldable f => Foldable ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

fold :: Monoid m => CofreeF f a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> CofreeF f a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> CofreeF f a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> CofreeF f a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> CofreeF f a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> CofreeF f a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> CofreeF f a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> CofreeF f a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> CofreeF f a a0 -> a0 Source #

toList :: CofreeF f a a0 -> [a0] Source #

null :: CofreeF f a a0 -> Bool Source #

length :: CofreeF f a a0 -> Int Source #

elem :: Eq a0 => a0 -> CofreeF f a a0 -> Bool Source #

maximum :: Ord a0 => CofreeF f a a0 -> a0 Source #

minimum :: Ord a0 => CofreeF f a a0 -> a0 Source #

sum :: Num a0 => CofreeF f a a0 -> a0 Source #

product :: Num a0 => CofreeF f a a0 -> a0 Source #

Traversable f => Traversable ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

traverse :: Applicative f0 => (a0 -> f0 b) -> CofreeF f a a0 -> f0 ( CofreeF f a b) Source #

sequenceA :: Applicative f0 => CofreeF f a (f0 a0) -> f0 ( CofreeF f a a0) Source #

mapM :: Monad m => (a0 -> m b) -> CofreeF f a a0 -> m ( CofreeF f a b) Source #

sequence :: Monad m => CofreeF f a (m a0) -> m ( CofreeF f a a0) Source #

( Eq1 f, Eq a) => Eq1 ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

liftEq :: (a0 -> b -> Bool ) -> CofreeF f a a0 -> CofreeF f a b -> Bool Source #

( Ord1 f, Ord a) => Ord1 ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Read1 f, Read a) => Read1 ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Show1 f, Show a) => Show1 ( CofreeF f a) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

liftShowsPrec :: ( Int -> a0 -> ShowS ) -> ([a0] -> ShowS ) -> Int -> CofreeF f a a0 -> ShowS Source #

liftShowList :: ( Int -> a0 -> ShowS ) -> ([a0] -> ShowS ) -> [ CofreeF f a a0] -> ShowS Source #

( Eq a, Eq (f b)) => Eq ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Typeable f, Typeable a, Typeable b, Data a, Data (f b), Data b) => Data ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

gfoldl :: ( forall d b0. Data d => c (d -> b0) -> d -> c b0) -> ( forall g. g -> c g) -> CofreeF f a b -> c ( CofreeF f a b) Source #

gunfold :: ( forall b0 r. Data b0 => c (b0 -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( CofreeF f a b) Source #

toConstr :: CofreeF f a b -> Constr Source #

dataTypeOf :: CofreeF f a b -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( CofreeF f a b)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( CofreeF f a b)) Source #

gmapT :: ( forall b0. Data b0 => b0 -> b0) -> CofreeF f a b -> CofreeF f a b Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> CofreeF f a b -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> CofreeF f a b -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> CofreeF f a b -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> CofreeF f a b -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> CofreeF f a b -> m ( CofreeF f a b) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> CofreeF f a b -> m ( CofreeF f a b) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> CofreeF f a b -> m ( CofreeF f a b) Source #

( Ord a, Ord (f b)) => Ord ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Read a, Read (f b)) => Read ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

( Show a, Show (f b)) => Show ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Generic ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep ( CofreeF f a b) :: Type -> Type Source #

type Rep1 ( CofreeF f a :: Type -> Type ) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

type Rep ( CofreeF f a b) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

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.

Instances

Instances details
ComonadCofree [] Tree Source #
Instance details

Defined in Control.Comonad.Cofree.Class

ComonadCofree Maybe NonEmpty Source #
Instance details

Defined in Control.Comonad.Cofree.Class

Functor f => ComonadCofree f ( Cofree f) Source #
Instance details

Defined in Control.Comonad.Cofree

Comonad w => ComonadCofree Identity ( CoiterT w) Source #
Instance details

Defined in Control.Comonad.Trans.Coiter

( ComonadCofree f w, Monoid m) => ComonadCofree f ( TracedT m w) Source #
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: TracedT m w a -> f ( TracedT m w a) Source #

ComonadCofree f w => ComonadCofree f ( StoreT s w) Source #
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: StoreT s w a -> f ( StoreT s w a) Source #

ComonadCofree f w => ComonadCofree f ( EnvT e w) Source #
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: EnvT e w a -> f ( EnvT e w a) Source #

ComonadCofree f w => ComonadCofree f ( IdentityT w) Source #
Instance details

Defined in Control.Comonad.Cofree.Class

( Functor f, Comonad w) => ComonadCofree f ( CofreeT f w) Source #
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

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

ComonadCofree ( Const b :: Type -> Type ) ( (,) b) Source #
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: (b, a) -> Const b (b, a) Source #

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

transCofreeT :: ( Functor g, Comonad w) => ( forall x. f x -> g x) -> CofreeT f w a -> CofreeT g w a Source #

Lift a natural transformation from f to g into a comonad homomorphism from CofreeT f w to CofreeT g w

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.