[Haskell-cafe] Different choice operations in a continuation monad

Sebastian Fischer sebf at informatik.uni-kiel.de
Tue Jun 15 11:06:38 EDT 2010


Dear Café,

`MonadPlus` instances are usually required to satisfy certain laws,  
among them the monad laws and monoid laws for `mzero` and `mplus`.  
Additionally one may require that  (>>=f)  is a monoid morphism, that  
is:

     mzero         >>= f  =  mzero
     (a `mplus` b) >>= f  =  (a >>= f) `mplus` (b >>= f)

The list monad satisfies these additional laws, the `Maybe`-Monad does  
not satisfy the second, distributive, law:

     ghci> (return False `mplus` return True) >>= guard :: [()]
     [()]
     ghci> (return False `mplus` return True) >>= guard :: Maybe ()
     Nothing

Instead of the distributive law, the `Maybe` monad satisfies a  
different law:

     return x `mplus` a  =  return x

that is, `return` annihilates the `Maybe`-Monad regarding `mplus`.  
This "cancellation law" is incompatible with the distributive law  
because (together with other laws) it implies that the result of the  
above example expression is `Nothing` whereas the distributive law  
implies that it is `Just ()`.

We can lift the `Maybe` type into a continuation monad:

  > newtype CMaybe r a = CMaybe ((a -> Maybe r) -> Maybe r)
  >
  > instance Monad (CMaybe r) where
  >   return x        = CMaybe (\k -> k x)
  >   CMaybe ca >>= f = CMaybe (\k -> ca (\x -> let CMaybe cb = f x in  
cb k))
  >
  > instance MonadPlus (CMaybe r) where
  >   mzero                       = CMaybe (\_ -> mzero)
  >   CMaybe ca `mplus` CMaybe cb = CMaybe (\k -> ca k `mplus` cb k)

Unlike the `Maybe`-monad, the `CMaybe`-monad satisfies the  
distributive law, not the cancellation law.

Can you define an associative operation

     orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a

with identity `mzero` that satisfies the cancellation law?

Cheers,
Sebastian



-- 
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)





More information about the Haskell-Cafe mailing list