comonad-3.0.0.2: Haskell 98 compatible comonads

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Comonad

Contents

Description

 

Synopsis

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 and duplicate 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

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 = liftW f = extend (f . extract)

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

Comonadic fixed point à la Menendez

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

Comonadic fixed point à la Orchard

(=>=) :: 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 -> b) -> w a -> w bSource

extend in operator form

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

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

Combining Comonads

class Comonad w => ComonadApply w whereSource

A ComonadApply w is a strong lax symmetric semi-monoidal comonad on the category Hask of Haskell types.

That it to say that w is a strong lax symmetric semi-monoidal functor on Hask, where both extract and duplicate are symmetric monoidal natural transformations.

Laws:

 (.) <$> u <@> v <@> w = u <@> (v <@> w)
 extract p (extract q) = extract (p <@> q)
 duplicate (p <*> q) = (\r s -> fmap (r <@> s)) <@> duplicate q <*> duplicate q

If our type is both a ComonadApply and Applicative we further require

 (<*>) = (<@>)

Finally, if you choose to define (<@) and (@>), the results of your definitions should match the following laws:

 a @> b = const id <$> a <@> b
 a <@ b = const <$> a <@> b

Methods

(<@>) :: w (a -> b) -> w a -> w bSource

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

(<@) :: w a -> w b -> w aSource

(<@@>) :: ComonadApply w => w a -> w (a -> b) -> w bSource

A variant of <@> with the arguments reversed.

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

Cokleisli Arrows

newtype Cokleisli w a b Source

The Cokleisli Arrows of a given Comonad

Constructors

Cokleisli 

Fields

runCokleisli :: w a -> b
 

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, Maybe and 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

Replace the contents of a functor uniformly with a constant value.