Copyright | (C) 2008-2015 Edward Kmett (C) 2004 Dave Menendez |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
- 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
- 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 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 where Source #
There are two ways to define a comonad:
I. Provide definitions for extract
and extend
satisfying these laws:
extend
extract
=id
extract
.extend
f = fextend
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
= 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
=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
idfmap
f =extend
(f .extract
)
These are the default definitions of extend
and duplicate
and
the definition of liftW
respectively.
Comonad NonEmpty Source # | |
Comonad Identity Source # | |
Comonad Tree Source # | |
Comonad ((,) e) Source # | |
Comonad (Arg e) Source # | |
Comonad (Tagged * s) Source # | |
Comonad w => Comonad (IdentityT * w) Source # | |
Comonad w => Comonad (EnvT e w) Source # | |
Comonad w => Comonad (StoreT s w) Source # | |
(Comonad w, Monoid m) => Comonad (TracedT m w) Source # | |
Monoid m => Comonad ((->) LiftedRep LiftedRep m) Source # | |
(Comonad f, Comonad g) => Comonad (Sum * f g) Source # | |
kfix :: ComonadApply w => w (w a -> a) -> w a Source #
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 Source #
Left-to-right Cokleisli
composition
(=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> c infixr 1 Source #
Right-to-left Cokleisli
composition
Combining Comonads
class Comonad w => ComonadApply w where Source #
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) =extract
p (extract
q)duplicate
(p<@>
q) = (<@>
)<$>
duplicate
p<@>
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
(<@>) :: w (a -> b) -> w a -> w b infixl 4 Source #
(<@>) :: Applicative w => w (a -> b) -> w a -> w b infixl 4 Source #
ComonadApply NonEmpty Source # | |
ComonadApply Identity Source # | |
ComonadApply Tree Source # | |
Semigroup m => ComonadApply ((,) m) Source # | |
ComonadApply w => ComonadApply (IdentityT * w) Source # | |
(Semigroup e, ComonadApply w) => ComonadApply (EnvT e w) Source # | |
(ComonadApply w, Semigroup s) => ComonadApply (StoreT s w) Source # | |
(ComonadApply w, Monoid m) => ComonadApply (TracedT m w) Source # | |
Monoid m => ComonadApply ((->) LiftedRep LiftedRep m) Source # | |
(<@@>) :: ComonadApply w => w a -> w (a -> b) -> w b infixl 4 Source #
A variant of <@>
with the arguments reversed.
liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c Source #
Lift a binary function into a Comonad
with zipping
liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d Source #
Lift a ternary function into a Comonad
with zipping
Cokleisli Arrows
newtype Cokleisli w a b Source #
Cokleisli | |
|
Comonad w => Arrow (Cokleisli w) Source # | |
Comonad w => ArrowChoice (Cokleisli w) Source # | |
Comonad w => ArrowApply (Cokleisli w) Source # | |
ComonadApply w => ArrowLoop (Cokleisli w) Source # | |
Comonad w => Category * (Cokleisli w) Source # | |
Monad (Cokleisli w a) Source # | |
Functor (Cokleisli w a) Source # | |
Applicative (Cokleisli w a) Source # | |
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.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
($>) :: Functor f => f a -> b -> f b infixl 4 #
Flipped version of <$
.
Examples
Replace the contents of a
with a constant Maybe
Int
String
:
>>>
Nothing $> "foo"
Nothing>>>
Just 90210 $> "foo"
Just "foo"
Replace the contents of an
with a constant
Either
Int
Int
String
, resulting in an
:Either
Int
String
>>>
Left 8675309 $> "foo"
Left 8675309>>>
Right 8675309 $> "foo"
Right "foo"
Replace each element of a list with a constant String
:
>>>
[1,2,3] $> "foo"
["foo","foo","foo"]
Replace the second element of a pair with a constant String
:
>>>
(1,2) $> "foo"
(1,"foo")
Since: 4.7.0.0