You may like my parser transformer then (based on the efficent
backtracking parser paper, I believe by Ralf Heinze - uses endofunctor
and continuation passing - Its a long time since I tested it but I think
it holds its own against Parsec, without requiring the extra return types).
-- parser.hs: Copyright (C)2001,2002 Keean Schupke.
--
-- Polymorphic monadic consumer based parser.
module Lib.Monad.ParserT(ParserT(..)) where
import Control.Monad hiding (guard)
import Control.Monad.Error
import Lib.Monad.MonadT
import Lib.Monad.MonadState
import Lib.Monad.MonadParser
import Lib.Monad.MonadControl
import Lib.Arrow.Runnable
------------------------------------------------------------------------------
-- An continuation passing endomorphic parser
type Cps a r = (a -> r) -> r
type Endo r = r -> r
newtype ParserT r tok m a = PT (Cps a ([tok] -> Endo (m r)))
instance Monad m => Functor (ParserT r tok m) where
fmap g (PT m) = PT $ \k -> m (\a s f -> k (g a) s f)
instance Monad m => Monad (ParserT r tok m) where
{-# INLINE return #-}
return a = PT $ \k -> k a
{-# INLINE (>>=) #-}
(PT m) >>= f = PT $ \k -> m (\a -> (\(PT x) -> x) (f a) k)
instance Monad m => MonadPlus (ParserT r tok m) where
{-# INLINE mzero #-}
mzero = PT $ \_ _ f -> f
{-# INLINE mplus #-}
mplus (PT m) (PT n) = PT $ \k s -> m k s . n k s
instance MonadPlus m => MonadT (ParserT r tok) m where
{-# INLINE up #-}
up m = PT $ \k s f -> (m >>= \a -> k a s mzero) `mplus` f
{-# INLINE down #-}
down = undefined
instance (MonadPlus m,MonadT (ParserT r tok) m,Runnable ([tok] -> m
([tok],r)) ([tok] -> n ([tok],r)))
=> Runnable (ParserT ([tok],r) tok m r) ([tok] -> n
([tok],r)) where
run = run . (\(PT m) t -> m (\a t' f -> return (t',a) `mplus` f)
t mzero)
instance (MonadPlus m,MonadT (ParserT r tok) m)
=> Runnable (ParserT ([tok],r) tok m r) ([tok] -> m
([tok],r)) where
run = (\(PT m) t -> m (\a t' f -> return (t',a) `mplus` f) t mzero)
instance Monad m => MonadState [tok] (ParserT r tok m) where
{-# INLINE update #-}
update st = PT $ \k s -> k s ((st s) `asTypeOf` s)
setState st = PT $ \k _ -> k () st
getState = PT $ \k s -> k s s
instance Monad m => MonadParser tok (ParserT r tok m) where
{-# INLINE item #-}
item = PT $ \k s -> case s of
[] -> id
(a:x) -> k a x
instance (MonadPlus (t m),MonadParser tok m,MonadT t m) => MonadParser
tok (t m) where
item = up item
instance Monad m => MonadControl (ParserT r tok m) where
{-# INLINE once #-}
once (PT m) = PT $ \k s f -> m (\a s' _ -> k a s' f) s f
Regards,
Keean.
John Goerzen wrote:
On 2005-09-16, Andrew Pimlott <[EMAIL PROTECTED]> wrote:
On Thu, Sep 15, 2005 at 06:11:58PM -0700, Andrew Pimlott wrote:
I don't see why this would be more error-prone than any other approach.
Hmm... I take that back. I don't know anything about the IMAP protocol,
but after imagining for a few moments what it might be like, I can see
how it could be more difficult than my example.
The user state of the parser might help you...
Hmm, can you elaborate on that?
Basically, I *really* want to get away frmo having to use hGetContents.
It is just not at all friendly for an interactive netwrk protocol. If I
were just streaming a large file from an FTP server, it would be fine,
but even using it to begin with involves using Handles in a nonstandard
way (since there must be a separate Handle for writing, since
hGetContents sents the Handle to be half-closed) that is apparently not
well-supported.
-- John
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe