free-5.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.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 from 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)) infixr 5 
Instances
ComonadTrans Cofree Source #

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

Instance details

Defined in Control.Comonad.Cofree

Methods

lower :: Comonad w => Cofree w a -> w a #

ComonadHoist Cofree Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

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

ComonadEnv e w => ComonadEnv e (Cofree w) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

ask :: Cofree w a -> e #

ComonadStore s w => ComonadStore s (Cofree w) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

pos :: Cofree w a -> s #

peek :: s -> Cofree w a -> a #

peeks :: (s -> s) -> Cofree w a -> a #

seek :: s -> Cofree w a -> Cofree w a #

seeks :: (s -> s) -> Cofree w a -> Cofree w a #

experiment :: Functor f => (s -> f s) -> Cofree w a -> f a #

ComonadTraced m w => ComonadTraced m (Cofree w) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

trace :: m -> Cofree w a -> a #

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

Defined in Control.Comonad.Cofree

Methods

unwrap :: Cofree f a -> f (Cofree f a) Source #

Alternative f => Monad (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

(>>=) :: Cofree f a -> (a -> Cofree f b) -> Cofree f b #

(>>) :: Cofree f a -> Cofree f b -> Cofree f b #

return :: a -> Cofree f a #

fail :: String -> Cofree f a #

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

Defined in Control.Comonad.Cofree

Methods

fmap :: (a -> b) -> Cofree f a -> Cofree f b #

(<$) :: a -> Cofree f b -> Cofree f a #

Alternative f => Applicative (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

pure :: a -> Cofree f a #

(<*>) :: Cofree f (a -> b) -> Cofree f a -> Cofree f b #

liftA2 :: (a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c #

(*>) :: Cofree f a -> Cofree f b -> Cofree f b #

(<*) :: Cofree f a -> Cofree f b -> Cofree f a #

Foldable f => Foldable (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

fold :: Monoid m => Cofree f m -> m #

foldMap :: Monoid m => (a -> m) -> Cofree f a -> m #

foldr :: (a -> b -> b) -> b -> Cofree f a -> b #

foldr' :: (a -> b -> b) -> b -> Cofree f a -> b #

foldl :: (b -> a -> b) -> b -> Cofree f a -> b #

foldl' :: (b -> a -> b) -> b -> Cofree f a -> b #

foldr1 :: (a -> a -> a) -> Cofree f a -> a #

foldl1 :: (a -> a -> a) -> Cofree f a -> a #

toList :: Cofree f a -> [a] #

null :: Cofree f a -> Bool #

length :: Cofree f a -> Int #

elem :: Eq a => a -> Cofree f a -> Bool #

maximum :: Ord a => Cofree f a -> a #

minimum :: Ord a => Cofree f a -> a #

sum :: Num a => Cofree f a -> a #

product :: Num a => Cofree f a -> a #

Traversable f => Traversable (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Cofree f a -> f0 (Cofree f b) #

sequenceA :: Applicative f0 => Cofree f (f0 a) -> f0 (Cofree f a) #

mapM :: Monad m => (a -> m b) -> Cofree f a -> m (Cofree f b) #

sequence :: Monad m => Cofree f (m a) -> m (Cofree f a) #

Eq1 f => Eq1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftEq :: (a -> b -> Bool) -> Cofree f a -> Cofree f b -> Bool #

Ord1 f => Ord1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftCompare :: (a -> b -> Ordering) -> Cofree f a -> Cofree f b -> Ordering #

Read1 f => Read1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Cofree f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Cofree f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Cofree f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Cofree f a] #

Show1 f => Show1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Cofree f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Cofree f a] -> ShowS #

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

Defined in Control.Comonad.Cofree

Methods

mzip :: Cofree f a -> Cofree f b -> Cofree f (a, b) #

mzipWith :: (a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c #

munzip :: Cofree f (a, b) -> (Cofree f a, Cofree f b) #

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

Defined in Control.Comonad.Cofree

Methods

extract :: Cofree f a -> a #

duplicate :: Cofree f a -> Cofree f (Cofree f a) #

extend :: (Cofree f a -> b) -> Cofree f a -> Cofree f b #

ComonadApply f => ComonadApply (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

(<@>) :: Cofree f (a -> b) -> Cofree f a -> Cofree f b #

(@>) :: Cofree f a -> Cofree f b -> Cofree f b #

(<@) :: Cofree f a -> Cofree f b -> Cofree f a #

Distributive f => Distributive (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

distribute :: Functor f0 => f0 (Cofree f a) -> Cofree f (f0 a) #

collect :: Functor f0 => (a -> Cofree f b) -> f0 a -> Cofree f (f0 b) #

distributeM :: Monad m => m (Cofree f a) -> Cofree f (m a) #

collectM :: Monad m => (a -> Cofree f b) -> m a -> Cofree f (m b) #

Traversable1 f => Traversable1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Cofree f a -> f0 (Cofree f b) #

sequence1 :: Apply f0 => Cofree f (f0 b) -> f0 (Cofree f b) #

Foldable1 f => Foldable1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

fold1 :: Semigroup m => Cofree f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Cofree f a -> m #

toNonEmpty :: Cofree f a -> NonEmpty a #

Apply f => Apply (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

(<.>) :: Cofree f (a -> b) -> Cofree f a -> Cofree f b #

(.>) :: Cofree f a -> Cofree f b -> Cofree f b #

(<.) :: Cofree f a -> Cofree f b -> Cofree f a #

liftF2 :: (a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c #

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

Defined in Control.Comonad.Cofree

Methods

duplicated :: Cofree f a -> Cofree f (Cofree f a) #

extended :: (Cofree f a -> b) -> Cofree f a -> Cofree f b #

Functor f => Generic1 (Cofree f :: * -> *) Source # 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep1 (Cofree f) :: k -> * #

Methods

from1 :: Cofree f a -> Rep1 (Cofree f) a #

to1 :: Rep1 (Cofree f) a -> Cofree f a #

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

Defined in Control.Comonad.Cofree

Methods

(==) :: Cofree f a -> Cofree f a -> Bool #

(/=) :: Cofree f a -> Cofree f a -> Bool #

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

Defined in Control.Comonad.Cofree

Methods

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

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

toConstr :: Cofree f a -> Constr #

dataTypeOf :: Cofree f a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Cofree f a -> Cofree f a #

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

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

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

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

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

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

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

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

Defined in Control.Comonad.Cofree

Methods

compare :: Cofree f a -> Cofree f a -> Ordering #

(<) :: Cofree f a -> Cofree f a -> Bool #

(<=) :: Cofree f a -> Cofree f a -> Bool #

(>) :: Cofree f a -> Cofree f a -> Bool #

(>=) :: Cofree f a -> Cofree f a -> Bool #

max :: Cofree f a -> Cofree f a -> Cofree f a #

min :: Cofree f a -> Cofree f a -> Cofree f a #

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

Defined in Control.Comonad.Cofree

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

Defined in Control.Comonad.Cofree

Methods

showsPrec :: Int -> Cofree f a -> ShowS #

show :: Cofree f a -> String #

showList :: [Cofree f a] -> ShowS #

Generic (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) :: * -> * #

Methods

from :: Cofree f a -> Rep (Cofree f a) x #

to :: Rep (Cofree f a) x -> Cofree f a #

type Rep1 (Cofree f :: * -> *) Source # 
Instance details

Defined in Control.Comonad.Cofree

type Rep (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

type Rep (Cofree f a) = D1 (MetaData "Cofree" "Control.Comonad.Cofree" "free-5.1-5DqT5y8WzG7CmjGqAVwxRB" False) (C1 (MetaCons ":<" (InfixI RightAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Cofree f a)))))

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

Allows you to peel a layer off a cofree comonad.

Minimal complete definition

unwrap

Methods

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

Remove a layer.

Instances
ComonadCofree [] Tree Source # 
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: Tree a -> [Tree a] Source #

ComonadCofree Maybe NonEmpty Source # 
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: NonEmpty a -> Maybe (NonEmpty a) Source #

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

Defined in Control.Comonad.Cofree

Methods

unwrap :: Cofree f a -> f (Cofree f a) Source #

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

Defined in Control.Comonad.Trans.Coiter

Methods

unwrap :: CoiterT w a -> Identity (CoiterT w a) Source #

(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

Methods

unwrap :: IdentityT w a -> f (IdentityT w a) 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 #

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

Defined in Control.Comonad.Cofree.Class

Methods

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

section :: Comonad f => f a -> Cofree f a Source #

coiter :: Functor f => (a -> f a) -> a -> Cofree f a Source #

Use coiteration to generate a cofree comonad from a seed.

coiter f = unfold (id &&& f)

coiterW :: (Comonad w, Functor f) => (w a -> f (w a)) -> w a -> Cofree f a Source #

Like coiter for comonadic values.

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

Unfold a cofree comonad from a seed.

unfoldM :: (Traversable f, Monad m) => (b -> m (a, f b)) -> b -> m (Cofree f a) Source #

Unfold a cofree comonad from a seed, monadically.

hoistCofree :: Functor f => (forall x. f x -> g x) -> Cofree f a -> Cofree g a Source #

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 => [(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 an Lens into a Cofree g given a list of lenses into the base functor. When the input list is empty, this is equivalent to _extract. When the input list is non-empty, this composes the input lenses with _unwrap to walk through the Cofree g before using _extract to get the element at the final location.

For more on lenses see the lens package on hackage.

telescoped :: [Lens' (g (Cofree g a)) (Cofree g a)]      -> Lens' (Cofree g a) a
telescoped :: [Traversal' (g (Cofree g a)) (Cofree g a)] -> Traversal' (Cofree g a) a
telescoped :: [Getter (g (Cofree g a)) (Cofree g a)]     -> Getter (Cofree g a) a
telescoped :: [Fold (g (Cofree g a)) (Cofree g a)]       -> Fold (Cofree g a) a
telescoped :: [Setter' (g (Cofree g a)) (Cofree g a)]    -> Setter' (Cofree g a) a

telescoped_ :: Functor f => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a) Source #

Construct an Lens into a Cofree g given a list of lenses into the base functor. The only difference between this and telescoped is that telescoped focuses on a single value, but this focuses on the entire remaining subtree. When the input list is empty, this is equivalent to id. When the input list is non-empty, this composes the input lenses with _unwrap to walk through the Cofree g.

For more on lenses see the lens package on hackage.

telescoped :: [Lens' (g (Cofree g a)) (Cofree g a)]      -> Lens' (Cofree g a) (Cofree g a)
telescoped :: [Traversal' (g (Cofree g a)) (Cofree g a)] -> Traversal' (Cofree g a) (Cofree g a)
telescoped :: [Getter (g (Cofree g a)) (Cofree g a)]     -> Getter (Cofree g a) (Cofree g a)
telescoped :: [Fold (g (Cofree g a)) (Cofree g a)]       -> Fold (Cofree g a) (Cofree g a)
telescoped :: [Setter' (g (Cofree g a)) (Cofree g a)]    -> Setter' (Cofree g a) (Cofree g a)

shoots :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a) Source #

A Traversal' that gives access to all non-leaf a elements of a Cofree g a, where non-leaf is defined as x from (x :< xs) where null xs is False.

Because this doesn't give access to all values in the Cofree g, it cannot be used to change types.

shoots :: Traversable g => Traversal' (Cofree g a) a

N.B. On GHC < 7.9, this is slightly less flexible, as it has to use null (toList xs) instead.

leaves :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a) Source #

A Traversal' that gives access to all leaf a elements of a Cofree g a, where leaf is defined as x from (x :< xs) where null xs is True.

Because this doesn't give access to all values in the Cofree g, it cannot be used to change types.

shoots :: Traversable g => Traversal' (Cofree g a) a

N.B. On GHC < 7.9, this is slightly less flexible, as it has to use null (toList xs) instead.