Add laws to Alternative

Twan van Laarhoven twanvl at gmail.com
Fri Nov 1 13:08:31 UTC 2013


On 01/11/13 12:44, Nathan van Doorn wrote:
> Firstly, I don't see how IO is relevant here, it has neither a MonadPlus
> instance nor an Alternative instance.

You are right. I thought it was an instance with mzero=fail "foo" and 
mplus=catch. But I was apparently mistaken. Objection withdrawn.

> Secondly, the MonadPlus laws are documented in Control.Monad to be:
>
>     mzero >>= f = mzero
>     v >> mzero = mzero

I missed them, because they are written in the documentation of mzero rather 
than the documentation of the class where I expected them.

> Thirdly, the monoid laws are already documented. (<|>) must be "An associative
> binary operation", and empty "The identity of <|>". These are exactly the monoid
> laws. Perhaps they should be made more explicit, but that is a different issue.

Missed this as well.

> Fourthly, [] fulfils neither the left-distribution law or the left-catch law,
> and I doubt many people would be happy to lose []'s MonadPlus instance.

List does satisfy left distribution:

λ> (,) <$> ([1,2] <|> [3]) <*> [4,5]
[(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]
λ> (,) <$> [1,2] <*> [4,5] <|> (,) <$> [3] <*> [4,5]
[(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]
λ> quickCheck (\x y z -> ((,) <$> (x <|> y :: [Int]) <*> (z :: [Int]))
                       == (((,) <$> x <*> z) <|> ((,) <$> y <*> z)))
+++ OK, passed 100 tests.

See also http://www.haskell.org/haskellwiki/MonadPlus. Then law which it doesn't 
is right distribution.

Consider Maybe. it does satisfies left catch but not left distribution for 
MonadPlus. Since
   mplus (Just False >>= guard) (Just True >>= guard) = Just ()
while
   mplus (Just False) (Just True) >>= guard = Nothing

But for Alternative, you can't have the failure of the second argument of (<*>) 
depend on the first. So Maybe *does* satisfy left distribution for Alternative. 
IMO that makes it a good candidate law.


Twan

> I believe I have addressed all your issues. If I've missed something, please
> point it out to me.
>
> Nathan.
>
>
> On 1 November 2013 12:09, Twan van Laarhoven <twanvl at gmail.com
> <mailto:twanvl at gmail.com>> wrote:
>
>     On 01/11/13 11:42, Nathan van Doorn wrote:
>
>         Proposal: add the following laws to the documentation of
>         Control.Applicative.__Alternative:
>
>            * empty <*> a = empty
>            * f <*> empty = empty
>
>      > These laws correspond to the laws given in MonadPlus- if you take mzero =
>      > empty and ap = (<*>), the ones in MonadPlus imply these- and I don't think
>      > this proposal should be too controversial.
>
>     As far as I can see, the documentation for MonadPlus does not specify these
>     laws anywhere [1,2].
>
>     Consider the IO monad. These laws claim that
>
>          launchMissiles *> fail "empty" = fail "empty"
>
>     This is clearly *not* true.
>
>     --
>
>     If we add laws, I think we should first consider the much more reasonable
>     monoid laws
>
>          identity
>            empty <|> a = a
>            a <|> empty = a
>          associativity:
>            (a <|> b) <|> c = a <|> (b <|> c)
>
>     In the MonadPlus world, the controversial part is the choice between
>
>          left distribution
>            (f <|> g) <*> a = (f <*> a) <|> (g <*> a)
>
>     or
>
>          left catch
>            pure a <|> b = pure a
>
>     Your proposal would be
>
>          left zero
>
>            empty <*> a = empty
>          right zero
>
>            f <*> empty = empty
>
>     And as mentioned above, right zero is problematic. The fmap version should
>     be okay though
>
>           map zero
>            f <$> empty = empty
>
>
>     Twan
>
>     [1]
>     http://hackage.haskell.org/__package/base-4.6.0.1/docs/__Control-Monad.html#t:MonadPlus
>     <http://hackage.haskell.org/package/base-4.6.0.1/docs/Control-Monad.html#t:MonadPlus>
>     [2] http://www.haskell.org/__haskellwiki/MonadPlus
>     <http://www.haskell.org/haskellwiki/MonadPlus>
>     _________________________________________________
>     Libraries mailing list
>     Libraries at haskell.org <mailto:Libraries at haskell.org>
>     http://www.haskell.org/__mailman/listinfo/libraries
>     <http://www.haskell.org/mailman/listinfo/libraries>
>
>



More information about the Libraries mailing list