Vous êtes sur la page 1sur 11

5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free

Page 1 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
Share
24

More

Next Blog dpiponi@gmail.com

New Post

Design

Sign Out
A Neighborhood of Infinity
Friday, May 23, 2014
Cofree meets Free
> {-# LANGUAGE RankNTypes, MultiParamTypeClasses, TypeOperators #-}
Introduction
After I spoke at BayHac 2014 about free monads I was asked about cofree comonads. So this is
intended as a sequel to that talk. Not only am I going to try to explain what cofree comonads are.
I'm also going to point out a very close relationship between cofree comonads and free monads.
At the beginning of the talk the Google Hangout software seems to have switched to the laptop
camera so you can't see the slides in the video. However the slides are here.
Cothings as machines
I often think of coalgebraic things as machines. They have some internal state and you can press
buttons to change that internal state. For example here is a type class for a machine with two
buttons that's related to a magma:
> class TwoButton a where
> press :: a -> (a, a)
The idea is that the state of the machine is given by some type a and you could press either the left
button or the right button. The result of pressing one or other button is given by these two
functions:
> pressLeft, pressRight :: TwoButton a => a -> a
> pressLeft = fst . press
> pressRight = snd . press
(As with many metaphors used to explain Haskell type classes your mileage may vary. Sometimes
you'll have to stretch your imagination to see what the set of buttons is for a particular cothing.)
Comonads
Just as monads are a kind of generalised algebraic structure (for example see my talk), comonads
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 2 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
are a generalised kind of machine. The idea is that for any state of the machine there is a bunch of
buttons we could press. But we don't have two buttons, or any fixed number of buttons. We
instead have a functorful of buttons (if you think of functors by analogy with containers). We also
don't get to directly see the internal state of the machine but instead we get to make observations.
Here's the type class:
> class Comonad w where
> extract :: w a -> a
> duplicate :: w a -> w (w a)
The state of the machine is given by w a. We observe the state using the extract function. And
when we come to press a button, we have a functorful of new states that it could end up in. The
duplicate function gives the container of those new states.
For example, various kinds of zipper give rise to comonads. Zippers allow you to "focus" on a part
of a data structure. The extract operation allows you to observe the point that currently has
focus. There is one button for every position in the structure where the focus could be. Pressing
the corresponding button moves the focus to that point. Similarly the Store comonad has one
button for each value you can store in the field it represents. Press the button and the value gets
stored in the field.
Cofreeness as a way to memoise
Cofree coalgebras can be thought of as memoised forms of elements of coalgebras. For example,
the TwoButton machine above has a function, press, as part of its definition. Memoising an
element of such a thing means tabulating everything that could possibly happen if you pressed
the buttons so we no longer need the press function. One approach is to try something like this:
data CofreeTwoButton = Memo CofreeTwoButton CofreeTwoButton
The structure contains two CofreeTwoButtons, each giving the result of pressing one of the two
buttons. Any element of CofreeTwoButton may now be memoised like so:
memoiseTwoButton :: TwoButton m => m -> CofreeTwoButton
memoiseTwoButton m = Memo (memoiseTwoButton (pressLeft m)) (memoiseTwoButton (pressRight m))
It definitely tabulates the result of pressing buttons. But it has a major flaw. We have no way of
seeing what's stored in the table! To make this useful we want to also store some data in the table
that we can peek at. So here is a better definition:
> data CofreeTwoButton a = Memo a (CofreeTwoButton a) (CofreeTwoButton a)
> memoiseTwoButton :: TwoButton m => (m -> a) -> m -> CofreeTwoButton a
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 3 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
> memoiseTwoButton f m = Memo (f m) (memoiseTwoButton f (pressLeft m)) (memoiseTwoButton f (pressRight m))
The first argument to memoiseTwoButton says what we want to store in the table and then
memoiseTwoButton goes ahead and stores it. We can use the identity function if we want to store
the original elements.
Note how this is like foldMap:
foldMap :: Monoid m => (a -> m) -> t a -> m
if we replace t by the list functor and remember that lists are free monoids. The main difference is
that arrows have been reversed. Where foldMap takes an element of a free monoid and interprets
it as an element of another monoid, memoiseTwoButton packs an element of a TwoButton into a
cofree structure. The "interpretation" and "packing" here are both homomorphisms for their
respective structures. Homomorphisms respect equations so if an equation holds between
elements of a free monoid we expect it to also hold when interpreted in another monoid. But any
element of a free monoid can be interpreted in any other monoid meaning that any equation that
holds between elements of a free monoid must hold in any monoid. That's why free monoids are
designed so that the only equations that hold between elements are those that follow from the
monoid laws.
With the TwoButton we have a dualised version of the above. Every element of every TwoButton can
be packed into the CofreeTwoButton. So every equation in the original structure will still hold after
the packing. So every equation that holds in some TwoButton must have some solution in
CofreeTwoButton. That gives an idea of what a CofreeTwoButton is by analogy with the free
monoid.
Cofree comonads
A cofree comonad is basically a memoised comonad. So the data structure is:
> data Cofree f a = Cofree a (f (Cofree f a))
At each point in the "table" we store some observable value of type a. And we have a functorful of
buttons, so we expect to have a functorful of new states we could transition to. The Functor
instance looks like:
> instance Functor f => Functor (Cofree f) where
> fmap f (Cofree a fs) = Cofree (f a) (fmap (fmap f) fs)
We apply f to the observable value and then push the fmap f down to the child nodes.
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 4 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
The duplicate function takes a memoised state and replaces the observable stored at each
position with the memoised state that gives rise to the observable.
> instance Functor f => Comonad (Cofree f) where
> extract (Cofree a _) = a
> duplicate c@(Cofree _ fs) = Cofree c (fmap duplicate fs)
Now by analogy with memoiseTwoButton we can memoise comonads.
> memoiseComonad :: (Comonad w, Functor f) =>
> (forall x.w x -> f x) -> (forall x.w x -> Cofree f x)
> memoiseComonad f w = Cofree (extract w) (fmap (memoiseComonad f) (f (duplicate w)))
So that's what a cofree comonad is: it's a type that can be used to memoise all of the states that
are accessible from a state in a comonad by pressing its buttons.
Cofree comonad meets free monad
But that's not all. There is a close relationship between cofree comonads and free monads. So to
get going, here's a free monad type:
> data Free f a = Id a | Free (f (Free f a))
> join' :: Functor f => Free f (Free f a) -> Free f a
> join' (Id x) = x
> join' (Free fa) = Free (fmap join' fa)
> instance Functor f => Functor (Free f) where
> fmap f (Id x) = Id (f x)
> fmap f (Free fa) = Free (fmap (fmap f) fa)
> instance Functor f => Monad (Free f) where
> return = Id
> m >>= f = join' (fmap f m)
Now I'll define a kind of pairing between functors. Given a way to combine two kinds of element,
the pairing gives a way to combine a pair of containers of those elements.
> class (Functor f, Functor g) => Pairing f g where
> pair :: (a -> b -> r) -> f a -> g b -> r
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 5 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
> data Identity a = Identity a
> instance Functor Identity where
> fmap f (Identity x) = Identity (f x)
> instance Pairing Identity Identity where
> pair f (Identity a) (Identity b) = f a b
> data (f :+: g) x = LeftF (f x) | RightF (g x)
> instance (Functor f, Functor g) => Functor (f :+: g) where
> fmap f (LeftF x) = LeftF (fmap f x)
> fmap f (RightF x) = RightF (fmap f x)
> data (f :*: g) x = f x :*: g x
> instance (Functor f, Functor g) => Functor (f :*: g) where
> fmap f (x :*: y) = fmap f x :*: fmap f y
> instance (Pairing f f', Pairing g g') => Pairing (f :+: g) (f' :*: g') where
> pair p (LeftF x) (a :*: _) = pair p x a
> pair p (RightF x) (_ :*: b) = pair p x b
> instance (Pairing f f', Pairing g g') => Pairing (f :*: g) (f' :+: g') where
> pair p (a :*: _) (LeftF x) = pair p a x
> pair p (_ :*: b) (RightF x) = pair p b x
> instance Pairing ((->) a) ((,) a) where
> pair p f = uncurry (p . f)
Given a pairing between f and g we get one between Cofree f and Free g.
> instance Pairing f g => Pairing (Cofree f) (Free g) where
> pair p (Cofree a _) (Id x) = p a x
> pair p (Cofree _ fs) (Free gs) = pair (pair p) fs gs
An element of Free g can be thought of as an expression written in a DSL. So this pairing gives a
way to apply a monadic expression to a memoised comonad. In other words, if you think of
comonads as machines, monads give a language that can be used to compute something based on
the output of the machine.
Here's an almost trivial example just so you can see everything working together. A reasonable
definition of a comagma structure on the type a is a -> UpDown a with UpDown defined as:
> data UpDown a = Up a | Down a
> instance Functor UpDown where
> fmap f (Up a) = Up (f a)
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 6 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
> fmap f (Down a) = Down (f a)
> type CofreeComagma a = Cofree UpDown a
A well known comagma structure on the positive integers is given by the famous Collatz
conjecture:
> collatz :: Integer -> UpDown Integer
> collatz n = if even n then Down (n `div` 2) else Up (3*n+1)
We can memoise this as a cofree comonad:
> memoisedCollatz :: Integer -> CofreeComagma Integer
> memoisedCollatz n = Cofree n (fmap memoisedCollatz (collatz n))
Here's a picture of memoisedCollatz 12:
Now let's make the dual functor in readiness for building the dual monad:
> data Two a = Two a a
> instance Functor Two where
> fmap f (Two a b) = Two (f a) (f b)
And here we set up a pairing:
> instance Pairing UpDown Two where
> pair f (Up a) (Two b _) = f a b
> pair f (Down a) (Two _ c) = f a c
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 7 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
> execute :: Cofree UpDown x -> Free Two (x -> r) -> r
> execute w m = pair (flip ($)) w m
This gives rise to a free monad isomorphic to the one in my talk:
> data Direction = WentUp | WentDown deriving Show
> choose :: Free Two Direction
> choose = Free (Two (return WentUp) (return WentDown))
And here's an example of some code written in the corresponding DSL:
> ex1 :: Free Two (Integer -> String)
> ex1 = do
> x <- choose
> y <- choose
> case (x, y) of
> (WentDown, WentDown) -> return (\z -> "Decreased twice " ++ show z)
> _ -> return show
It can be represented as:
And here's what happens when they meet:
> go1 :: String
> go1 = execute (memoisedCollatz 12) ex1
This can be understood through the combined picture:
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 8 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
References
On getting monads from comonads more generally see Monads from Comonads. For more on
memoising and how it's really all about the Yoneda lemma see Memoizing Polymorphic
Functions. I'm waiting for Tom Leinster to publish some related work. The pairing above gives a
way for elements of free monads to pick out elements of cofree comonads and is a special case of
what I'm talking about here. But I think Tom has some unpublished work that goes further.
If you think of a comonad as a compressed object that is decompressed by a monadic decision
tree, then you'd expect some form of information theoretical description to apply. That makes me
think of Convex spaces and an operadic approach to entropy.
Posted by Dan Piponi at Friday, May 23, 2014
7 comments:
Edward Kmett said...
I used to have a version of your Pairing class in an earlier version of the adjunctions package, under the less
informative name 'Zap'.
http://comonad.com/reader/2008/zapping-strong-adjunctions/
I general it is just about asking for a sum from one of the types whenever the other is a product and vice
versa and it can annihilate values with functions from that value
The problem I had with it as a class was that both
instance Adjunction f g => Zap f g
instance Adjunction f g => Zap g f
are reasonable.
This caused me to eventually switch it over to a data type carrying the mapping:
http://hackage.haskell.org/package/adjunctions-0.6.0/docs/Data-Functor-Zap.html
But with very few users I eventually dropped the feature; I think only Sjoerd Visscher ever noticed it was
there. ;)
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 9 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
I could reintroduce it without the automated lifting from Adjunction if folks are interested.
Friday, 23 May, 2014
heisenbug said...
A quick search revealed this paper: http://math.ucr.edu/home/baez/information_loss.pdf
Saturday, 24 May, 2014
Dan Piponi said...
@heisenbug Yeah, I know about those papers because I followed their unfolding at the n-category cafe. But I
think coalgebras may add a twist. I think random processes are nicely described coalgebraically but the
decisions tree driven by such processes are nicely thought of as algebraic.
Saturday, 24 May, 2014
Unknown said...
The relationship between Pairing functors looks a lot like the relationship between `w` and `Co w`.
Saturday, 24 May, 2014
Dan Piponi said...
@Unknown That's why I linked to Ed's page about Co :-)
It's a special case of that relationship. But I think it's nice to unpack it for free monads and cofree comonads
because they give a lot of insight into what's happening more generally.
Saturday, 24 May, 2014
Sjoerd Visscher said...
The only instance that is a Pairing but not an Adjunction that I can think of is where you have two
adjunctions intertwined, i.e.
instance (Adjunction f1 g1, Adjunction f2 g2) => Pairing (Compose f1 g2) (Compose f2 g1)
Are there others?
Saturday, 24 May, 2014
Edward Kmett said...
Sjoerd:
There are also
instance (Zap f g, Zap h i) => Pairing (Sum f h) (Product g i)
instance (Zap f g, Zap h i) => Pairing (Product g i) (Sum f h)
which aren't simply instances of the only Hask->Hask adjunction in disguise and which swaps sums for
products.
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 10 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
Older Post
Post a Comment
Links to this post
Create a Link
Home
Subscribe to: Post Comments (Atom)
Blog Archive
! 2014 (4)
! May (2)
Cofree meets Free
Types, and two approaches to problem solving
" April (1)
" February (1)
" 2013 (4)
" 2012 (8)
" 2011 (13)
" 2010 (20)
" 2009 (21)
" 2008 (35)
" 2007 (37)
" 2006 (92)
" 2005 (53)
Some Links
The Comonad.Reader
Rubrication
Richard Borcherds: Mathematics and physics
The n-Category Cafe
Ars Mathematica
About Me
Dan Piponi
Follow
1.8k
Blog: A Neighborhood of Infinity
But even that first 'intertwining' leads to whole families of such twistings, e.g. StateT vs. StoreT should give
rise to something like:
instance Pairing m w => Pairing (StateT m s) (StoreT w s)
and vice versa.
Saturday, 24 May, 2014
5/26/14, 5:39 PM A Neighborhood of Innity: Cofree meets Free
Page 11 of 11 http://blog.sigfpe.com/2014/05/cofree-meets-free.html
Code: Github
Twitter: sigfpe
Home page: www.sigfpe.com
View my complete profile

Vous aimerez peut-être aussi