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
unsequenceusing monadic and comonadic operators, not specific toWriter? - Is there is a more elegant implementation of the
extendfunction above, perhaps similar to this one?
Thanks!
unsequence(and, as a consequence,ex2) doesn't work because it throws away theWriterlog.extractfor yourComonadinstance gives the result of the computation, discarding the log.returnadds amemptylog to the bare results. That being so, the flags are cleared inex2.unsequence1, on the other hand, does what you want. That clearly doesn't have anything to do withComonad(your definition doesn't use its methods); rather,unsequence1works because... it's actuallysequence! Under the hood,Writeris just a pair of a result and a (monoidal) log. If you have a second look atunsequence1with that in mind, you will note that (modulo irrelevant details) it does essentially the same thing thansequencefor pairs -- it annotates the values in the other functor with the log:In fact,
Writeralready has aTraversableinstance just like that, so you don't even need to define it:It is worth mentioning that
sequenceisn't an essentially monadic operation -- theMonadconstraint insequenceis unnecessarily restrictive. The real deal issequenceA, which only requires anApplicativeconstraint on the inner functor. (If the outerFunctor-- i.e. the one with theTraversableinstance -- is likeWriter win that it always "holds" exactly one value, then you don't even needApplicative, but that's another story.)As discussed above, you don't actually want
unsequence. There is a class calledDistributivethat does provideunsequence(under the name ofdistribute); however, there is relatively little overlap between things withDistributiveinstances and things withTraversableones, and in any case it doesn't essentially involve comonads.Your
Comonadinstance is fine (it does follow the comonad laws), except that you don't actually need theMonoidconstraint in it. The pair comonad is usually known asEnv; see this answer for discussion of what it does.