[Haskell-cafe] Re: Parsers are monadic?

apfelmus apfelmus at quantentunnel.de
Mon Jul 2 10:31:34 EDT 2007


apfelmus wrote:
>   class DiMonad m where
>     returnR :: a -> m e a
>     bindR   :: m e a -> (a -> m e b)  -> m e b
> 
>     returnL :: e -> m e a
>     bindL   :: m e a -> (e -> m e' a) -> m e' a
>
>   type TwoCont e a = (e -> R) -> (a -> R) -> R
>
> A final question remains: does the dimonad abstraction cover the full
> power of TwoCont? I mean, it still seems like there's an operation
> missing that supplies new left and right continuations at once.

I think that this missing operation is

  bind2 :: m e a -> (e -> m e' a') -> (a -> m e' a') -> m e' a'

It executes the second or the third argument depending on whether the
first argument is a failure or a success.

First, bind2 can be defined for TwoCont

 bind2 m fe fa = \e' a' -> m (\e -> (fe e) e' a') (\a -> (fa a) e' a')

Apparently, bindL and bindR can be expressed with bind2

  bindL m f = bind2 m f returnR
  bindR m f = bind2 m returnL f

The question is whether bind2 can be expressed by bindL and bindR or
whether bind2 offers more than both. It turns out that bind2 can be
formulated from bindL and bindR alone

  fmapR f m = m `bindR` returnR . f
  bind2 m fe fa =
     ((Left `fmapR` m) `bindL` (\e -> Right `fmapR` fe e))
    `bindR`
     (\aa' -> case aa' of
         Left  a  -> fa a
         Right a' -> returnR a')

The definitions is rather cumbersome and we omit the proof that both
definitions for bind2 are the same for TwoConts. For a general proof,
we'd need an axiomatic characterization of dimonads and bind2.


Recast in the light of MonadError, bind2 gives rise to a combinator

  bind2 :: MonadError e m => m a -> (e -> m b) -> (a -> m b) -> m b

that executes either failure or success path. The important point is the
inequality

   bind2 m fe fa ≠ (m >>= fa) `catchError` fe

There's no equivalent to bind2 (with a better name, of course) in the
libraries at the moment.


The only function that does come near bind2 in the libraries is

   Control.Exception.try :: IO a -> IO (Either Exception a)

which can be used rather easily to implement bind2 of course.
Interestingly, the existence of  try  shows that there is a natural
isomorphism

   DiMonad m => m e a ≅ m () (Either e a)

so that dimonads do not add anything beyond what monads can already do.
(More precisely,  try  gives one direction. The other direction is
rather obvious.)

Regards,
apfelmus



More information about the Haskell-Cafe mailing list