I am using the Writer
monad to keep track of an error ("collision") flag on arbitrary values (such as Int
). Once the flag is set it is "sticky" and attaches itself to all values produced as a result of any operation with the marked one.
Sometimes the collision flag is associated with individual values, sometimes I would like to associate with composite structures such as lists. Of course, once the collision flag is set for a whole list, it also makes sense to assume it is set for an individual element. So for a writer monad m
I need the two following operations:
sequence :: [m a] -> m [a]
unsequence :: m [a] -> [m a]
The first one is defined in the Prelude, while the second one has to be defined. Here is a good discussion of how it could be defined using comonads. A native comonad implementation does not preserve the state. Here is an example:
{-# LANGUAGE FlexibleInstances #-}
module Foo where
import Control.Monad.Writer
import Control.Comonad
unsequence :: (Comonad w, Monad m) => w [a] -> [m a]
unsequence = map return . extract
instance Monoid Bool where
mempty = False
mappend = (||)
type CM = Writer Bool
type CInt = CM Int
instance (Monoid w) => Comonad (Writer w) where
extract x = fst $ runWriter x
extend f wa = do { tell $ execWriter wa ; return (f wa)}
mkCollision :: t -> Writer Bool t
mkCollision x = do (tell True) ; return x
unsequence1 :: CM [Int] -> [CInt]
unsequence1 a = let (l,f) = runWriter a in
map (\x -> do { tell f ; return x}) l
el = mkCollision [1,2,3]
ex2:: [CInt]
ex2 = unsequence el
ex1 = unsequence1 el
The ex1
produces the correct value, while ex2
output is incorrectly not preserving collision flag:
*Foo> ex1
[WriterT (Identity (1,True)),WriterT (Identity (2,True)),WriterT (Identity (3,True))]
*Foo> ex2
[WriterT (Identity (1,False)),WriterT (Identity (2,False)),WriterT (Identity (3,False))]
*Foo>
In view of this I have 2 questions:
- Is it possible to define
unsequence
using monadic and comonadic operators, not specific to Writer
?
- Is there is a more elegant implementation of the
extend
function above, perhaps similar to this one?
Thanks!
The ex1
produces correct value, while ex2
output is incorrectly not preserving collision flag:
unsequence
(and, as a consequence, ex2
) doesn't work because it throws away the Writer
log.
unsequence :: (Comonad w, Monad m) => w [a] -> [m a]
unsequence = map return . extract
extract
for your Comonad
instance gives the result of the computation, discarding the log. return
adds a mempty
log to the bare results. That being so, the flags are cleared in ex2
.
unsequence1
, on the other hand, does what you want. That clearly doesn't have anything to do with Comonad
(your definition doesn't use its methods); rather, unsequence1
works because... it's actually sequence
! Under the hood, Writer
is just a pair of a result and a (monoidal) log. If you have a second look at unsequence1
with that in mind, you will note that (modulo irrelevant details) it does essentially the same thing than sequence
for pairs -- it annotates the values in the other functor with the log:
GHCi> sequence (3, [1..10])
[(3,1),(3,2),(3,3),(3,4),(3,5),(3,6),(3,7),(3,8),(3,9),(3,10)]
In fact, Writer
already has a Traversable
instance just like that, so you don't even need to define it:
GHCi> import Control.Monad.Writer
GHCi> import Data.Monoid -- 'Any' is your 'Bool' monoid.
GHCi> el = tell (Any True) >> return [1,2,3] :: Writer Any [Int]
GHCi> sequence el
[WriterT (Identity (1,Any {getAny = True})),WriterT (Identity (2,Any {getAny = True})),WriterT (Identity (3,Any {getAny = True}))]
It is worth mentioning that sequence
isn't an essentially monadic operation -- the Monad
constraint in sequence
is unnecessarily restrictive. The real deal is sequenceA
, which only requires an Applicative
constraint on the inner functor. (If the outer Functor
-- i.e. the one with the Traversable
instance -- is like Writer w
in that it always "holds" exactly one value, then you don't even need Applicative
, but that's another story.)
Is it possible to define 'unsequence' using monadic and comonadic operators, not specific to 'Writer'
As discussed above, you don't actually want unsequence
. There is a class called Distributive
that does provide unsequence
(under the name of distribute
); however, there is relatively little overlap between things with Distributive
instances and things with Traversable
ones, and in any case it doesn't essentially involve comonads.
Is there is a more elegant implementatoin of extend function above, perhaps similar to this one?
Your Comonad
instance is fine (it does follow the comonad laws), except that you don't actually need the Monoid
constraint in it. The pair comonad is usually known as Env
; see this answer for discussion of what it does.