incorrect MonadPlus law "v >> mzero = mzero"?

Hi, this law apparently fails for a MonadPlus instance that has more than one possible failure value. Consider: runIdentity . runErrorT $ ((ErrorT . Identity $ Left "failure") >> mzero :: ErrorT String Identity ()) evaluates to `Left "failure"`, which isn't equal to ErrorT's mzero `Left ""`. This isn't just the case of ErrorT, it fails for any MonadPlus with multiple failure values. For example lift (tell "foo") >> mzero :: MaybeT (Writer String) () is again distinct from mzero. Actually, no monad transformer with a MonadPlus instance can satisfy the law, because the first part in front of `>> mzero` can introduce side effects in the underlying monad. I'm not sure what should be the proper solution. Perhaps to change the laws to: return x >> mzero = mzero (v >> mzero) >>= f = (v >> mzero)` That is, if an expression ends with `mzero`, it behaves like `mzero`. Petr

On Wed, Jan 29, 2014 at 8:57 AM, Petr Pudlák
I'm not sure what should be the proper solution. Perhaps to change the laws to:
return x >> mzero = mzero (v >> mzero) >>= f = (v >> mzero)`
That is, if an expression ends with `mzero`, it behaves like `mzero`.
As others've mentioned, these come for free from being a monad together with (mzero >>= f) = mzero. The rules I'd expect MonadPlus to obey are: mzero >>= f = mzero (x `mplus` y) >> mzero = (x >> mzero) `mplus` (y >> mzero) x `mplus` (y `mplus` z) = (x `mplus` y) `mplus` z x `mplus` mzero = x mzero `mplus` y = y The last three simply state that (mplus,mzero) forms a monoid. The first two laws indicate that the (>>) notion of "multiplication" distributes over the mplus notion of "addition", but only from the right side. These laws together with the associativity of (>>) mean that MonadPlus forms a right-seminearring (or right-nearsemiring, if you prefer). If we additionally require that mplus is commutative, then its an commutative right-seminearring. Seminearrings show up naturally all over the place, especially in linguistic contexts (i.e., parsing and generation of "strings"). I know Edward Kmett has talked about them before, and other algebraically minded folks are probably familiar with them too. They're one of my favorites and not too much more difficult to work with than semirings. ObTangent: For the algebraically minded, we have that S is a semiring just in case (1) S is a right-seminearring (2) S is a left-seminearring (just flip the directionality of the first two laws above) (3) the addition of S is commutative (4) there exists an identity element for multiplication -- Live well, ~wren

On Wed, Feb 5, 2014 at 7:59 PM, wren ng thornton
The rules I'd expect MonadPlus to obey are:
mzero >>= f = mzero
(x `mplus` y) >> mzero = (x >> mzero) `mplus` (y >> mzero)
Er, sorry, that should've been: (x `mplus` y) >> z = (x >> z) `mplus` (y >> z) from which the above instance follows trivially. -- Live well, ~wren

On Wed, Feb 5, 2014 at 5:01 PM, wren ng thornton
On Wed, Feb 5, 2014 at 7:59 PM, wren ng thornton
wrote: The rules I'd expect MonadPlus to obey are:
mzero >>= f = mzero
(x `mplus` y) >> mzero = (x >> mzero) `mplus` (y >> mzero)
Er, sorry, that should've been:
(x `mplus` y) >> z = (x >> z) `mplus` (y >> z)
from which the above instance follows trivially.
I don't think this is correct. consider the original instance with x /= mzero. Then we have left side (x `mplus` y) >> mzero x >> mzero -- by def. of mplus right side (x >> mzero) `mplus` (y >> mzero) mzero'x `mplus` (y >> mzero) -- mzero'x is a zero with x's effects, this reduction comes from the monad laws (y >> mzero) -- by mplus Or concretely,
let x = lift (print "x!") :: MaybeT IO () let y = lift (print "y!") :: MaybeT IO () runMaybeT $ (x `mplus` y) >> mzero
"x!" Nothing
runMaybeT $ (x >> mzero) `mplus` (y >> mzero)
"x!" "y!" Nothing John

On Wed, Feb 5, 2014 at 8:38 PM, John Lato
On Wed, Feb 5, 2014 at 5:01 PM, wren ng thornton
wrote: On Wed, Feb 5, 2014 at 7:59 PM, wren ng thornton
wrote: The rules I'd expect MonadPlus to obey are:
mzero >>= f = mzero
(x `mplus` y) >> mzero = (x >> mzero) `mplus` (y >> mzero)
Er, sorry, that should've been:
(x `mplus` y) >> z = (x >> z) `mplus` (y >> z)
from which the above instance follows trivially.
I don't think this is correct. [...] Or concretely,
let x = lift (print "x!") :: MaybeT IO () let y = lift (print "y!") :: MaybeT IO () runMaybeT $ (x `mplus` y) >> mzero
"x!" Nothing
runMaybeT $ (x >> mzero) `mplus` (y >> mzero)
"x!" "y!" Nothing
Well, notably, the Maybe part of things does agree. It's the transformer part which breaks things. However, this is something that could be "fixed" by changing the implementation of mplus for MaybeT. In particular, if we have it fully execute both arguments, but then discard the results of latter ones whenever earlier ones have succeeded. That is, mplus x y = MaybeT $ do v <- runMaybeT x w <- runMaybeT y case v of Nothing -> return w Just _ -> return v This "fix" ensures that the law is obeyed regardless of the underlying monad. However, it's not necessarily the instance we want. So the question is: for monad transformers, what --explicitly, concretely-- do we want? Do we consider the current MaybeT instance sacrosanct? What about the other popular instances? I still think the above laws are the most sensible ones. I discuss a bit about why I believe that in this blog post I just posted[1]. The only alternative I see is to drop every law about how mplus interacts with bind, which isn't a solution quite so much as giving up. [1] http://winterkoninkje.dreamwidth.org/90905.html -- Live well, ~wren

On Wed, Feb 5, 2014 at 9:32 PM, wren ng thornton
I still think the above laws are the most sensible ones. I discuss a bit about why I believe that in this blog post I just posted[1]. The only alternative I see is to drop every law about how mplus interacts with bind, which isn't a solution quite so much as giving up.
I had commented in that post about how the generalization of the distributivity law could possibly lead to problems, but didn't really explore it. I just now posted an addendum showing that (for Maybe/MaybeT) it is indeed the generalization itself which causes the problems; and that, if we use the *exact* distributivity law from seminearrings[2] rather than the generalized version, then the problem goes away (for Maybe). I still submit that this is the right law to have, following the same overall justification as before. The generalized law is nice, but I wouldn't be too sad about using the non-generalized law instead. Any IO/STM examples which break the non-generalized law? [2] That is, mzero >>= f = mzero -- this one is still generalized (x `mplus` y) >> z = (x >> z) `mplus` (y >> z) -- no longer generalized (x `mplus` y) `mplus` z = x `mplus` (y `mplus` z) x `mplus` mzero = x mzero `mplus` y = y -- Live well, ~wren

On Wed, Feb 5, 2014 at 6:32 PM, wren ng thornton
On Wed, Feb 5, 2014 at 8:38 PM, John Lato
wrote: On Wed, Feb 5, 2014 at 5:01 PM, wren ng thornton < winterkoninkje@gmail.com> wrote:
On Wed, Feb 5, 2014 at 7:59 PM, wren ng thornton
wrote: The rules I'd expect MonadPlus to obey are:
mzero >>= f = mzero
(x `mplus` y) >> mzero = (x >> mzero) `mplus` (y >> mzero)
Er, sorry, that should've been:
(x `mplus` y) >> z = (x >> z) `mplus` (y >> z)
from which the above instance follows trivially.
I don't think this is correct. [...] Or concretely,
let x = lift (print "x!") :: MaybeT IO () let y = lift (print "y!") :: MaybeT IO () runMaybeT $ (x `mplus` y) >> mzero
"x!" Nothing
runMaybeT $ (x >> mzero) `mplus` (y >> mzero)
"x!" "y!" Nothing
Well, notably, the Maybe part of things does agree. It's the transformer part which breaks things. However, this is something that could be "fixed" by changing the implementation of mplus for MaybeT. In particular, if we have it fully execute both arguments, but then discard the results of latter ones whenever earlier ones have succeeded. That is,
mplus x y = MaybeT $ do v <- runMaybeT x w <- runMaybeT y case v of Nothing -> return w Just _ -> return v
This "fix" ensures that the law is obeyed regardless of the underlying monad. However, it's not necessarily the instance we want. So the question is: for monad transformers, what --explicitly, concretely-- do we want? Do we consider the current MaybeT instance sacrosanct? What about the other popular instances?
That instance would mean that x `mplus` y /= x, when y assumes certain zeros. This property is more important to me than the other, at least as far as MaybeT is concerned. YMMV. Personally, I'm ok with treating all zeros as equal so far as the laws are concerned. Any particular instance with multiple zeros should document how they're propagated at mplus though. Of course, if we treat zeros as equivalent, then (v >> mzero = mzero) holds ;) John
I still think the above laws are the most sensible ones. I discuss a bit about why I believe that in this blog post I just posted[1]. The only alternative I see is to drop every law about how mplus interacts with bind, which isn't a solution quite so much as giving up.
[1] http://winterkoninkje.dreamwidth.org/90905.html
-- Live well, ~wren
participants (3)
-
John Lato
-
Petr Pudlák
-
wren ng thornton