Is there a generic way to detect "mzero"?

Hi, I was writing a code trying to use MonadPlus to detect some error cases (representing missing values etc. in pure code). With the Maybe monad, I can do this: can0 :: (a -> Maybe b) -> a -> Bool can0 f x = case f x of Nothing -> False Just x -> True And I got the expected result: *Main> can0 (\x -> Just x) 1 True But, when I try to generalize this using MonadPlus, as follows: can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True I got a warning: __testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main. And the result is also not as intended (see also can0): *Main> can (\x -> Just x) 1 False Can anyone help to explain why this wouldn't work or if there is a workaround to use Monadplus and mzero (or Monad and fail) to achieve this? Thanks in advance for your help Ting

can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main. The problem here is that when you match on "f x", your first match is an identifier that matches anything at all, and binds it to mzero. I think what you're looking for is
can f x = case f x of x' | x' == mzero -> False _ -> True Jeff

On 26 March 2012 21:11, Jeff Shaw
can :: (MonadPlus m) => (a -> m b) -> a -> Bool
can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main.
The problem here is that when you match on "f x", your first match is an identifier that matches anything at all, and binds it to mzero. I think what you're looking for is
can f x = case f x of x' | x' == mzero -> False _ -> True
can f x = f x /= mzero

Jeff,
I don't think your code works in general, since it is not guaranteed that
x' == mzero is allowed unless (m b) is an instance of Eq. I'm unsure if you
are able to test for mzero in general.
Harry
On Mon, Mar 26, 2012 at 3:11 PM, Jeff Shaw
can :: (MonadPlus m) => (a -> m b) -> a -> Bool
can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main.
The problem here is that when you match on "f x", your first match is an identifier that matches anything at all, and binds it to mzero. I think what you're looking for is
can f x = case f x of x' | x' == mzero -> False _ -> True
Jeff
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

On 26 March 2012 20:33, Ting Lei
can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True
In the first pattern `mzero' is just a variable and matches anything, as does `_'. So, naturally, both patterns overlap. I don't see any way to write this without requiring `Eq m'.

On Mon, Mar 26, 2012 at 1:33 PM, Ting Lei
Hi,
I was writing a code trying to use MonadPlus to detect some error cases (representing missing values etc. in pure code). With the Maybe monad, I can do this:
can0 :: (a -> Maybe b) -> a -> Bool can0 f x = case f x of Nothing -> False Just x -> True
And I got the expected result:
*Main> can0 (\x -> Just x) 1 True
But, when I try to generalize this using MonadPlus, as follows:
can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main.
Well, you can sort of do it with only MonadPlus - but it really depends on your choice of Monad whether or not it does anything like what you want: can :: (MonadPlus m) => (a -> m ()) -> a -> m Bool can f x = (f x >> return True) <|> return false For 'Maybe' this works great, but for something like 'List' I couldn't even tell you what it would do without reasoning through it. So you might be better off with the suggestion from Tobias using Eq Antoine

On Mon, Mar 26, 2012 at 21:24, Antoine Latter
On Mon, Mar 26, 2012 at 1:33 PM, Ting Lei
wrote: Hi,
I was writing a code trying to use MonadPlus to detect some error cases (representing missing values etc. in pure code). With the Maybe monad, I can do this:
can0 :: (a -> Maybe b) -> a -> Bool can0 f x = case f x of Nothing -> False Just x -> True
And I got the expected result:
*Main> can0 (\x -> Just x) 1 True
But, when I try to generalize this using MonadPlus, as follows:
can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main.
Well, you can sort of do it with only MonadPlus - but it really depends on your choice of Monad whether or not it does anything like what you want:
can :: (MonadPlus m) => (a -> m ()) -> a -> m Bool can f x = (f x >> return True) <|> return false
For 'Maybe' this works great, but for something like 'List' I couldn't even tell you what it would do without reasoning through it.
So you might be better off with the suggestion from Tobias using Eq
Well, if you accept the following MonadPlus laws: mzero >>= f == mzero mzero `mplus` m == m Then you can say that for a well-behaving MonadPlus, mzero will return (only) False in that function. However, I don't think it's guaranteed that a non-mzero value will give (only) True. In fact, the list monad will always return the final False. Erik

Hi Antoine and Tobias (and everyone else), Thanks a lot for your answers. They are really helpful Can you please show me how to use the (Eq m) constraint to do this? Also, my general question (probably novice-level) is that in monadic programming, you can convert not necessarily monadic codes into monadic ones. I know for many cases, it is impossible to do the reverse conversion, e.g. you can't make a function involving real IO operations into a pure code. In other cases, for example, I may need to using things like Nothing as the "null" value as in other programming languages, just to represent a special "missing" value outside the regular type. Is mzero a reasonable replacement for this or is there any reasonable (abstract) approximation in Haskell for doing this? (Like "null", I need the ability to detect it.) Thanks, Ting
From: aslatter@gmail.com Date: Mon, 26 Mar 2012 14:24:09 -0500 Subject: Re: [Haskell-cafe] Is there a generic way to detect "mzero"? To: tinlyx@hotmail.com CC: haskell-cafe@haskell.org
On Mon, Mar 26, 2012 at 1:33 PM, Ting Lei
wrote: Hi,
I was writing a code trying to use MonadPlus to detect some error cases (representing missing values etc. in pure code). With the Maybe monad, I can do this:
can0 :: (a -> Maybe b) -> a -> Bool can0 f x = case f x of Nothing -> False Just x -> True
And I got the expected result:
*Main> can0 (\x -> Just x) 1 True
But, when I try to generalize this using MonadPlus, as follows:
can :: (MonadPlus m) => (a -> m b) -> a -> Bool can f x = case f x of mzero -> False _ -> True
I got a warning:
__testError.hs:31:11: Warning: Pattern match(es) are overlapped In a case alternative: _ -> ... Ok, modules loaded: Main.
Well, you can sort of do it with only MonadPlus - but it really depends on your choice of Monad whether or not it does anything like what you want:
can :: (MonadPlus m) => (a -> m ()) -> a -> m Bool can f x = (f x >> return True) <|> return false
For 'Maybe' this works great, but for something like 'List' I couldn't even tell you what it would do without reasoning through it.
So you might be better off with the suggestion from Tobias using Eq
Antoine

On Mon, Mar 26, 2012 at 4:25 PM, Ting Lei
Hi Antoine and Tobias (and everyone else),
Thanks a lot for your answers. They are really helpful
Can you please show me how to use the (Eq m) constraint to do this?
Also, my general question (probably novice-level) is that in monadic programming, you can convert not necessarily monadic codes into monadic ones. I know for many cases, it is impossible to do the reverse conversion, e.g. you can't make a function involving real IO operations into a pure code. In other cases, for example, I may need to using things like Nothing as the "null" value as in other programming languages, just to represent a special "missing" value outside the regular type. Is mzero a reasonable replacement for this or is there any reasonable (abstract) approximation in Haskell for doing this? (Like "null", I need the ability to detect it.)
I think using 'Maybe' (with Nothing) is perfect for this - this function should come in handy: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Maybe.... Antoine

On Tue, Mar 27, 2012 at 11:03 AM, Antoine Latter
On Mon, Mar 26, 2012 at 4:25 PM, Ting Lei
wrote: Hi Antoine and Tobias (and everyone else),
Thanks a lot for your answers. They are really helpful
Can you please show me how to use the (Eq m) constraint to do this?
Also, my general question (probably novice-level) is that in monadic programming, you can convert not necessarily monadic codes into monadic ones. I know for many cases, it is impossible to do the reverse conversion, e.g. you can't make a function involving real IO operations into a pure code. In other cases, for example, I may need to using things like Nothing as the "null" value as in other programming languages, just to represent a special "missing" value outside the regular type. Is mzero a reasonable replacement for this or is there any reasonable (abstract) approximation in Haskell for doing this? (Like "null", I need the ability to detect it.)
I think using 'Maybe' (with Nothing) is perfect for this - this function should come in handy:
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Maybe....
Ting, It's often not good style to check Nothing explicitly, rather, it's better to use monads to thread it through automatically. If you have many functions that return a Maybe, then you can chain them together using do syntax: frobnicate = do foo <- function1 bar <- function2 foo return (bar + 1) If any of the functions in the chain return Nothing, then the monad will short circuit and the whole expression will result in Nothing. The <- acts like an automatic null check. Chris
Antoine
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

* Ting Lei
I was writing a code trying to use MonadPlus to detect some error cases (representing missing values etc. in pure code).
You are probably looking for the MonadError class. There's also the MonadLogic class (which allows to literally detect mzero), but if you simply need to catch errors, it is not as appropriate as MonadError. -- Roman I. Cheplyaka :: http://ro-che.info/
participants (9)
-
Antoine Latter
-
Chris Wong
-
dag.odenhall@gmail.com
-
Erik Hesselink
-
Harry Terkelsen
-
Jeff Shaw
-
Roman Cheplyaka
-
Ting Lei
-
Tobias Brandt