[Haskell-cafe] parsec2 vs. parsec3... again

Maciej Piechotka uzytkownik2 at gmail.com
Fri Dec 24 13:36:08 CET 2010


On Thu, 2010-12-23 at 18:38 +0200, Michael Snoyman wrote:
> On Thu, Dec 23, 2010 at 6:21 PM, Johan Tibell <johan.tibell at gmail.com> wrote:
> > On Thu, Dec 23, 2010 at 3:03 PM, Felipe Almeida Lessa
> > <felipe.lessa at gmail.com> wrote:
> >> Michael Snoyman wants attoparsec-text as well [1].
> >>
> >> [1] http://docs.yesodweb.com/blog/wishlist/
> >
> > It's on my Christmas wishlist too.
> >
> > Johan
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> 
> Since I'm sure everyone is thinking it at this point, I'll just say
> it: we're all hoping Bryan O'Sullivan saves the day again and writes
> this package. He wrote both attoparsec *and* text, so if he writes
> attoparsec-text, it will just be double the awesomeness. So Bryan,
> please do tell: how many beers (or any other consumable) will it take
> to get you to write it? I'll start up the collection fund, and throw
> in a six pack ;).
> 
> Michael

I may be wrong but the attoparsec/attoparsec-text would be operating on
the same principles. Maybe using typeclass like Data.ListLike would be
solution?

I'd not quite sure how much would it slow down but it should be
possible.

More as proof of concept reimplementation of string parser (for real
life probably needs INLINE and SPECIALISE):

> import Control.Applicative
> import Control.Monad
> import Data.Monoid
> import Data.ListLike as LL
> 
> data Result i r
>     = Fail !i [String] String
>     | Partial (i -> Result i r)
>     | Done !i r
> 
> newtype Parser i a
>     = Parser { runParser :: forall r. S i
>                          -> Failure i   r
>                          -> Success i a r
>                          -> Result  i   r }
> 
> type Failure i   r = S i -> [String] -> String -> Result i r
> type Success i a r = S i -> a -> Result i r
> 
> data More = Complete | Incomplete deriving (Eq, Show)
> 
> instance Monoid More where
>     mempty  = Incomplete
>     mappend Complete _        = Complete
>     mappend _        Complete = Complete
>     mappend _        _        = Incomplete
> 
> data S i = S { input :: !i, _added :: !i, more :: !More }
> 
> instance Functor (Parser i) where
>     fmap p m = Parser (\st0 f k -> runParser m st0 f (\s a -> k s (p
a)))
> 
> instance Applicative (Parser i) where
>     pure x = Parser (\st0 _ ks -> ks st0 x)
>     (<*>) = ap
> 
> instance Monad (Parser i) where
>     return = pure
>     m >>= g
>         = Parser (\st0 kf ks -> runParser m st0 kf (\s a -> runParser
(g a) s kf ks))
>     fail err = Parser (\st0 kf _ -> kf st0 [] err)
> 
> string :: (Eq full, LL.ListLike full item) => full -> Parser full full
> string s = takeWith (LL.length s) (== s)
> 
> takeWith :: (LL.ListLike full item) => Int -> (full -> Bool) -> Parser
full full
> takeWith n p = do
>     ensure n
>     s <- get
>     let (h, t) = LL.splitAt n s
>     if p h then put t >> return h else fail "takeWith"
> 
> ensure :: (LL.ListLike full item) => Int -> Parser full ()
> ensure n
>     = Parser $ \st0@(S s0 _a0 _c0) kf ks ->
>         if LL.length s0 >= n
>         then ks st0 ()
>         else runParser (demandInput >> ensure n) st0 kf ks
> 
> prompt :: LL.ListLike i ii
>        => S i -> (S i -> Result i r) -> (S i -> Result i r) -> Result
i r
> prompt (S s0 a0 _) kf ks
>     = Partial $ \s ->
>         if LL.null s
>         then kf $! S s0 a0 Complete
>         else ks $! S (s0 `mappend` s) (a0 `mappend` s) Incomplete
> 
> demandInput :: (LL.ListLike full item) => Parser full ()
> demandInput
>     = Parser $ \st0 kf ks ->
>         if more st0 == Complete
>         then kf st0 ["demandInput"] "not enough bytes"
>         else prompt st0 (\st -> kf st ["demandInput"] "not enough
bytes") (`ks` ())
> 
> get :: Parser full full
> get = Parser (\st0 _ ks -> ks st0 (input st0))
> 
> put :: full -> Parser full ()
> put s = Parser (\(S _ a0 c0) _ ks -> ks (S s a0 c0) ())

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20101224/2408bc9e/attachment.pgp>


More information about the Haskell-Cafe mailing list