[Haskell-cafe] Re: Lazy Parsing

S.Doaitse Swierstra doaitse at swierstra.net
Sun May 31 16:06:06 EDT 2009


Dear Gunther,


I am providing my solution, on which one can of course specialise in  
making sure that a valid date is parsed, which would be a bit more  
cumbersome; how should e.g. error correction be done. I prefer to test  
afterwards in such situations.

Best,
Doaitse



module Guenther where
import Text.ParserCombinators.UU.Parsing
import Text.ParserCombinators.UU.BasicInstances
import Text.ParserCombinators.UU.Examples hiding (main)
import Control.Applicative hiding ((<*), (*>), (<$))

{- The first decision we have to make is what kind of input we are  
providing. The simplest case is just to assume simple characters,  
hence for our input type we will use the standard provided stream of  
Characters: Str Char, so we use the type of our parsers to be the type  
used  in the Examples module; since we do not know whether we wil be  
using the parsers in a monadic mode too we stay on the safe side ans  
use the type P_m -}

type GP a = P_m (Str Char) a  -- GP stands for GuenterParser

{- Once we know that our input contains characters, but that in our  
output we what to have integer values, we start out by building a  
parser for a single integer , for which we use the function pNatural  
form the examples-}

pDate = (,,) <$> pNatural <* pDot <*> pNatural <* pDot <*>  
(pNatural ::GP Int)
pDot  = pSym '.'
{-
main = do print (test pDate "3.4.1900")
           print (test pDate "3 4 1900")
           print (test pDate "..1900")-}

-- end of Module Guenther

By playing with insertion and deletion costs (e.g. by building a more  
picky pNatural) one can control the error recovery. Another option to  
get better error recovery would be to define a specialised instance of  
Provides which removes spaces. You might even temporarily pSwitch to  
the use of this state


>
> Period.
>
> I do not even manage to write a parser for even a mere digit or a  
> simple character. I have read the tutorial from a to a to z and from  
> z to a and there were a few words I recognized.
>
> I mean I'd like to be able to turn "12.05.2009" into something like  
> (12, 5, 2009) and got no clue what the code would have to look like.  
> I do know almost every variation what the code must not look like :).
>
> I am guessing here that when one does define a parsing function,  
> since all the parser combinators aren't function but methods, one  
> *must* also provide a type signature so that the compiler knows the  
> actual *instance* method?
>
>
> Günther
>


More information about the Haskell-Cafe mailing list