[Haskell-cafe] Parsing with Proof

muad muad.dib.space at gmail.com
Wed Apr 1 19:59:10 EDT 2009


Hi Martijn and Wouter,

Based on the parser combinators paper, I put a monad together,

> data Parser s t = Parser ([s] -> [(t, [s])])
> 
> pFail = Parser (const [])
> pReturn a = Parser (\inp -> [(a, inp)])
> pSymbol s = Parser (\inp -> case inp of x:xs | x == s -> [(s,xs)] ; _ ->
> [])
> pChoice (Parser m) (Parser n) = Parser (\inp -> m inp ++ n inp)
> pBind :: Parser s a -> (a -> Parser s b) -> Parser s b
> pBind (Parser m) f = Parser (x m f) where
>  x :: ([s] -> [(a, [s])]) -> (a -> Parser s b) -> [s] -> [(b, [s])]
>  x m f inp = concatMap (y f) (m inp)
>  y f (a,s) = case f a of Parser g -> g s
> 
> instance Monad (Parser s) where return = pReturn ; (>>=) = pBind
> instance MonadPlus (Parser s) where mzero = pFail ; mplus = pChoice
> 
> runParser (Parser f) inp = f inp

and wrote the parser using that:

> left = pSymbol '('
> right = pSymbol ')'
> 
> parens = wrappend `mplus` empty where
>  empty = return Empty
>  wrappend = do left ; p <- parens ; right ; q <- parens ; return (Wrap p &
> q) where
>   m & Empty = m
>   m & n = Append m n

I really like the approach Wouter used for the State monad and I hope to
follow that idea for this, I am not sure how to do it yet but I will
scribble and see where it goes. Thanks very much for the advice!

-- 
View this message in context: http://www.nabble.com/Parsing-with-Proof-tp22814576p22835016.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list