[Haskell-cafe] Re: what is inverse of mzero and return?

Jorge Adriano Aires jadrian at mat.uc.pt
Sun Jan 23 10:41:12 EST 2005


> > One common example is using MonadPlus for some backtracking algorithm,
> > then instantiatiating it to Maybe or List instance depending on wether
> > you just want one solution or all of them.
>
> Backtracking only works with the first kind, even if you're only
> interested in the first solution. This must hold:
>
>   (mplus a b) >>= c = mplus (a >>= c) (b >>= c)

Not really. If the recursive call is something like "msum 
[all_possible_paths]", then you are backtracking. The difference is that by 
using Maybe you'll stop as soon as you succeed, and with list you will find 
all possible paths. 

I don't have a small, self-contained, example at hand so I'll use one by 
Carsten Schultz that I once saw posted in comp.lang.functional. Hope he 
doesn't mind. 

http://groups-beta.google.com/group/comp.lang.functional/msg/d7ac1fe1684ef840
-- -------------------------------------------------------------------
-- knapsack problem 

module Subset2 where
import Control.Monad

sss :: MonadPlus m => Int -> [Int] -> m [Int]
sss n [] | n>0 = mzero
sss n (x:xs) = 
    case compare n x 
    of LT -> mzero
       EQ -> return [x]
       GT -> liftM (x:) (sss (n-x) xs) `mplus` sss n xs
-- -------------------------------------------------------------------
sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: [[Int]]
[[3,8,14,15],[3,9,13,15],[8,13,19],[8,15,17],[9,14,17]]

sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: Maybe [Int]
Just [3,8,14,15]


> > [*] For instance, I've missed Maybe being an instance of MonadError.
> You could define your own instance, of course.

Yes of course, and I did ;)  But I think it should be provided nontheless, and 
I even find the fact that it isn't is playing a big part in all this 
confusion. Since there is no MonadError instance for Maybe, we end up using 
its MonadPlus instance, which just happens to be the same. But it cannot be 
generalized, for other types.

Lets forget about lists, think (Either e). It's usual to move from (Maybe a) 
to (Either e a) to consider more than one kind of error. But, there is no 
natural instance of MonadPlus for (Either e a). What would mzero be? 

Yet, the "Maybe like, mplus operation" makes perfect sense in (Either e) or 
any other MonadError, though. You don't need Monoids at all, what you need is 
the concept of error. Just define it as:

skipError x y = catchError x (\_->y)

J.A.


More information about the Haskell-Cafe mailing list