| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Safe-Infered | 
Control.Comonad
Description
- class Functor w => Comonad w where
- liftW :: Comonad w => (a -> b) -> w a -> w b
- wfix :: Comonad w => w (w a -> a) -> a
- cfix :: Comonad w => (w a -> a) -> w a
- (=>=) :: Comonad w => (w a -> b) -> (w b -> c) -> w a -> c
- (=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> c
- (<<=) :: Comonad w => (w a -> b) -> w a -> w b
- (=>>) :: Comonad w => w a -> (w a -> b) -> w b
- class Comonad w => ComonadApply w where
- (<@@>) :: ComonadApply w => w a -> w (a -> b) -> w b
- liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c
- liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d
- newtype  Cokleisli w a b = Cokleisli {- runCokleisli :: w a -> b
 
- class Functor f where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- ($>) :: Functor f => f a -> b -> f b
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.
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
Instances
| ComonadApply Tree | |
| ComonadApply NonEmpty | |
| ComonadApply Identity | |
| Monoid m => ComonadApply ((->) m) | |
| Semigroup m => ComonadApply ((,) m) | |
| ComonadApply w => ComonadApply (IdentityT w) | 
(<@@>) :: 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
Constructors
| Cokleisli | |
| Fields 
 | |
Instances
| Typeable1 w => Typeable2 (Cokleisli w) | |
| Comonad w => Arrow (Cokleisli w) | |
| Comonad w => ArrowChoice (Cokleisli w) | |
| Comonad w => ArrowApply (Cokleisli w) | |
| ComonadApply w => ArrowLoop (Cokleisli w) | |
| Comonad w => Category (Cokleisli w) | |
| Monad (Cokleisli w a) | |
| Functor (Cokleisli w a) | |
| Applicative (Cokleisli w a) | 
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.
Instances
| Functor [] | |
| Functor IO | |
| Functor ZipList | |
| Functor Tree | |
| Functor Option | |
| Functor NonEmpty | |
| Functor Identity | |
| Functor ((->) r) | |
| Functor (Either a) | |
| Functor ((,) a) | |
| Functor (Const m) | |
| Monad m => Functor (WrappedMonad m) | |
| Functor m => Functor (IdentityT m) | |
| Arrow a => Functor (WrappedArrow a b) | |
| Functor (Cokleisli w a) |