comonad-0.1.1: Haskell 98 comonads

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>

Control.Comonad

Contents

Description

A Comonad is the categorical dual of a Monad.

Synopsis

Functor and Comonad

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.

Instances

class Functor w => Comonad w whereSource

There are two ways to define a comonad:

I. Provide definitions for fmap, extract, and duplicate satisfying these laws:

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

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

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

(fmap cannot be defaulted, but a comonad which defines extend may simply set fmap equal to liftW.)

A comonad providing definitions for extend and duplicate, must also satisfy these laws:

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

(The first two are the defaults for extend and duplicate, and the third is the definition of liftW.)

Methods

extract :: w a -> aSource

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

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

Instances

class Comonad w => ComonadZip w whereSource

As a symmetric semi-monoidal comonad, an instance of ComonadZip is required to satisfy:

 extract (wzip a b) = (extract a, extract b)

By extension, the following law must also hold:

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

Minimum definition: <.>

Based on the ComonadZip from The Essence of Dataflow Programming by Tarmo Uustalu and Varmo Vene, but adapted to fit the conventions of Control.Monad and to provide a similar programming style to that of Control.Applicative.

Methods

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

 (<.>) = liftW2 id

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

 (.>) = liftW2 (const id)

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

 (<.) = liftW2 const

Instances

newtype Cokleisli w a b Source

The Cokleisli Arrows of a given Comonad

Constructors

Cokleisli 

Fields

runCokleisli :: w a -> b
 

Functions

Naming conventions

The functions in this library use the following naming conventions, based on those of Control.Monad.

  • A postfix 'W' always stands for a function in the Cokleisli category: The monad type constructor w is added to function results (modulo currying) and nowhere else. So, for example,
  filter  ::                (a ->   Bool) -> [a] ->   [a]
  filterW :: (Comonad w) => (w a -> Bool) -> w [a] -> [a]
  • A prefix 'w' generalizes an existing function to a comonadic form. Thus, for example:
  fix  :: (a -> a) -> a
  wfix :: w (w a -> a) -> a

When ambiguous, consistency with existing Control.Monad combinators supercedes other naming considerations.

Operators

(=>=) :: 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

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

Fixed points and folds

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

Comonadic fixed point

unfoldW :: Comonad w => (w b -> (a, b)) -> w b -> [a]Source

A generalized comonadic list anamorphism

Comonadic lifting

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

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

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

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

wzip :: ComonadZip w => w a -> w b -> w (a, b)Source

 wzip wa wb = (,) <$> wa <.> wb
 wzip = liftW2 (,) 

Called czip in Essence of Dataflow Programming