[Haskell-cafe] Parsers are monadic?

Jon Cast jcast at ou.edu
Sun Jul 1 15:36:14 EDT 2007


On Saturday 30 June 2007, Claus Reinke wrote:
> >The standard, naïve approach to monadic parsing is very nice, but
> >inefficient. So *please read* some material based on Hutton&Meijer
> >approach, but don't stay there, read something more modern,
>
> since we thereby seem to have left the phase of simple answers to
> simple questions;-) i'd like to raise a pet issue of mine. my own first
> combinator parsers (inspired by Wadler's "How to replace failure
> by a list of successes", but adapted to a call-by-value language)
> were based on continuations.
>
> ..
>
> ok, now everybody has had time to chime in with "monadic parsers
> are based on continuations" or "continuations are just one specific
> monad". so let me return to the particular issue i'm interested in:
> contrary to monadic parsers, those continuation-based parsers
> had *two* continuations, one for success, one for failure. and
> that seemed to be a very natural match for the problem.

<snip>

Two-continuations is a monad too, right?

newtype ContErrorT m alpha
  = ContErrorT { runContErrorT :: forall beta. (alpha -> m beta) ->
                                               (Exception -> m beta) ->
                                               m beta }
instance Monad m => ContErrorT m where
  return x = ContErrorT (\ k h -> k x)
  a >>= f
    = ContErrorT (\ k h -> runContErrorT a (\ x -> runContErrorT (f x) k h) h)
instance Monad m => MonadError Exception (ContError m) where
  throwError e = ContErroT ( \ k h -> h e)
  a `catchError` f
    = ContErrorT (\ k h -> runContErrorT a k (\ e -> runContErrorT (f e) k h))

Am I missing something really obvious here?

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs


More information about the Haskell-Cafe mailing list