comonad-0.4.0: Haskell 98 comonads

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>

Control.Comonad

Contents

Description

A Comonad is the categorical dual of a Monad.

Synopsis

Functors

class Functor f where

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

 fmap id  ==  id
 fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Data.Maybe.Maybe and System.IO.IO satisfy these laws.

Methods

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

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

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

(<$>) :: Functor f => (a -> b) -> f a -> f b

An infix synonym for fmap.

($>) :: Functor f => f a -> b -> f bSource

Comonads

class Functor w => Comonad w whereSource

There are two ways to define a comonad:

I. Provide definitions for extract and extend satisfying these laws:

 extend extract      = id
 extract . extend f  = f
 extend f . extend g = extend (f . extend g)

In this case, you may simply set fmap = liftW.

These laws are directly analogous to the laws for monads and perhaps can be made clearer by viewing them as laws stating that Cokleisli composition must be associative, and has extract for a unit:

 f =>= extract   = f
 extract =>= f   = f
 (f =>= g) =>= h = f =>= (g =>= h)

II. Alternately, you may choose to provide definitions for fmap, extract, and duplicate satisfying these laws:

 extract . duplicate      = id
 fmap extract . duplicate = id
 duplicate . duplicate    = fmap duplicate . duplicate

In this case you may not rely on the ability to define fmap in terms of liftW.

You may of course, choose to define both duplicate and extend. In that case you must also satisfy these laws:

 extend f  = fmap f . duplicate
 duplicate = extend id
 fmap f    = extend (f . extract)

These are the default definitions of extend andduplicate and the definition of liftW respectively.

Methods

extract :: w a -> aSource

 extract . fmap f = f . extract

duplicate :: w a -> w (w a)Source

 duplicate = extend id
 fmap (fmap f) . duplicate = duplicate . fmap f

extend :: (w a -> b) -> w a -> w bSource

 extend f  = fmap f . duplicate

Instances

(=>=) :: Comonad w => (w a -> b) -> (w b -> c) -> w a -> cSource

Left-to-right Cokleisli composition

(=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> cSource

Right-to-left Cokleisli composition

(=>>) :: Comonad w => w a -> (w a -> b) -> w bSource

extend with the arguments swapped. Dual to >>= for a Monad.

(<<=) :: Comonad w => (w a -> b) -> w a -> w bSource

extend in operator form

liftW :: Comonad w => (a -> b) -> w a -> w bSource

A suitable default definition for fmap for a Comonad. Promotes a function to a comonad.

 fmap f    = extend (f . extract)

wfix :: Comonad w => w (w a -> a) -> aSource

Comonadic fixed point

FunctorApply - strong lax symmetric semimonoidal endofunctors

class Functor f => FunctorApply f whereSource

A strong lax symmetric semi-monoidal functor.

Methods

(<.>) :: f (a -> b) -> f a -> f bSource

(.>) :: f a -> f b -> f bSource

a .> b = const id $ a . b

(<.) :: f a -> f b -> f aSource

(<..>) :: FunctorApply w => w a -> w (a -> b) -> w bSource

A variant of <.> with the arguments reversed.

liftF2 :: FunctorApply w => (a -> b -> c) -> w a -> w b -> w cSource

Lift a binary function into a comonad with zipping

liftF3 :: FunctorApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w dSource

Lift a ternary function into a comonad with zipping

ComonadApply - strong lax symmetric semimonoidal comonads

class (Comonad w, FunctorApply w) => ComonadApply w Source

A strong lax symmetric semi-monoidal comonad. As such an instance of ComonadApply is required to satisfy:

 extract (a <.> b) = extract a (extract b)

This class is based on ComonadZip from "The Essence of Dataflow Programming" by Tarmo Uustalu and Varmo Vene, but adapted to fit the programming style of Control.Applicative. Applicative can be seen as a similar law over and above FunctorApply that:

 pure (a b) = pure a <.> pure b

Instances

ComonadApply Identity 
Monoid m => ComonadApply ((->) m)

Only requires a Semigroup, but no such class exists

Monoid m => ComonadApply ((,) m)

Only requires a Semigroup, but no such class exists

ComonadApply w => ComonadApply (IdentityT w) 
ComonadApply f => ComonadApply (WrappedApply f) 

liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w cSource

Lift a binary function into a comonad with zipping

liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w dSource

Lift a ternary function into a comonad with zipping

Wrappers

newtype Cokleisli w a b Source

The Cokleisli Arrows of a given Comonad

Constructors

Cokleisli 

Fields

runCokleisli :: w a -> b
 

newtype WrappedApplicative f a Source

Wrap Applicatives to be used as a member of FunctorApply

Constructors

WrappedApplicative 

Fields

unwrapApplicative :: f a
 

newtype WrappedApply f a Source

Transform a strong lax symmetric semi-monoidal endofunctor into a strong lax symmetric monoidal endofunctor by adding a unit.

Constructors

WrapApply 

Fields

unwrapApply :: Either (f a) a