[Haskell-cafe] Re: Lazy Parsing
Stephen Tetley
stephen.tetley at gmail.com
Sun May 31 06:55:19 EDT 2009
Hi Günther
The code below should work for your simple example, provided it hasn't
lost formatting when I pasted it in to the email.
I was a bit surprised that there is no pSatisfy in this library, but
there are parsers for digits, lower case, upper case letters etc. in
the Examples module that would otherwise be achieved with pSatisfy.
Best wishes
Stephen
{-# LANGUAGE FlexibleContexts #-}
module Demo1 where
import Text.ParserCombinators.UU.Examples
import Text.ParserCombinators.UU.Parsing
-- here's a simple character '@' parser
pAtSym :: Symbol p Char Char => p Char
pAtSym = pSym '@'
test_simple_char = test pAtSym "@"
test_simple_char2 = test pAtSym "@@@@@"
-- pDigit is supplied in Text.ParserCombinators.UU.Examples
test_any_digit = test pDigit "6"
-- pNatural is supplied in Text.ParserCombinators.UU.Examples
-- It looks like the most likely candidate to parse a
-- sequence of digits...
test_natural = test pNatural "1234"
-- ... and it is!
-- parse a date "12.05.2009" as a triple (Int,Int,Int)
pDateTriple :: (Symbol p (Char,Char) Char, Applicative p, ExtApplicative p st,
Provides st Char Char)
=> p (Int,Int,Int)
pDateTriple = (,,) <$> pNatural <* pDot <*> pNatural <* pDot <*> pNatural
pDot :: (Symbol p Char Char, Applicative p) => p [Char]
pDot = lift <$> pSym '.'
test_date = test pDateTriple "12.05.2009"
More information about the Haskell-Cafe
mailing list