| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Comonad
Contents
Synopsis
- class Functor w => Comonad (w :: * -> *) where
- wfix :: Comonad w => w (w a -> a) -> a
- cfix :: Comonad w => (w a -> a) -> w a
- kfix :: ComonadApply w => 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 :: k -> *) (a :: k) b :: forall k. (k -> *) -> k -> * -> * = Cokleisli {
- runCokleisli :: w a -> b
Comonad
class Functor w => Comonad (w :: * -> *) where #
There are two ways to define a comonad:
I. Provide definitions for extract and extend
satisfying these laws:
extendextract=idextract.extendf = fextendf .extendg =extend(f .extendg)
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= fextract=>=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=idfmapextract.duplicate=idduplicate.duplicate=fmapduplicate.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:
extendf =fmapf .duplicateduplicate=extendidfmapf =extend(f .extract)
These are the default definitions of extend and duplicate and
the definition of liftW respectively.
Methods
Instances
kfix :: ComonadApply w => w (w a -> a) -> w a #
Comonadic fixed point à la Kenneth Foner:
This is the evaluate function from his "Getting a Quick Fix on Comonads" talk.
(=>=) :: Comonad w => (w a -> b) -> (w b -> c) -> w a -> c infixr 1 #
Left-to-right Cokleisli composition
(=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> c infixr 1 #
Right-to-left Cokleisli composition
ComonadApply
class Comonad w => ComonadApply (w :: * -> *) where #
ComonadApply is to Comonad like Applicative is to Monad.
Mathematically, it 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<@>q) =extractp (extractq)duplicate(p<@>q) = (<@>)<$>duplicatep<@>duplicateq
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 =constid<$>a<@>b a<@b =const<$>a<@>b
Instances
| ComonadApply Identity | |
| ComonadApply NonEmpty | |
| ComonadApply Tree | |
| ComonadApply Log | |
| Semigroup m => ComonadApply ((,) m) | |
| ComonadApply f => ComonadApply (Cofree f) | |
| Monoid s => ComonadApply (ReifiedGetter s) | |
Defined in Control.Lens.Reified Methods (<@>) :: ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b # (@>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b # (<@) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a # | |
| ComonadApply w => ComonadApply (IdentityT w) | |
| (ComonadApply f, ComonadApply g) => ComonadApply (Day f g) | |
| Monoid m => ComonadApply ((->) m :: * -> *) | |
| (a ~ b, Conjoined p) => ComonadApply (Bazaar p a b) | |
| (a ~ b, Conjoined p) => ComonadApply (Bazaar1 p a b) | |
| (a ~ b, Conjoined p) => ComonadApply (BazaarT p g a b) | |
| (a ~ b, Conjoined p) => ComonadApply (BazaarT1 p g a b) | |
(<@@>) :: ComonadApply w => w a -> w (a -> b) -> w b infixl 4 #
A variant of <@> with the arguments reversed.
liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c #
Lift a binary function into a Comonad with zipping
liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d #
Lift a ternary function into a Comonad with zipping
Newtypes
newtype Cokleisli (w :: k -> *) (a :: k) b :: forall k. (k -> *) -> k -> * -> * #
Constructors
| Cokleisli | |
Fields
| |