On Mon, 26 Jul 2004 22:45:50 -0500, <[EMAIL PROTECTED]> wrote:

Hello,

I copied this example exactly from the page

http://www.cs.uu.nl/people/daan/download/parsec/parsec.html

-----begin-----
module Parser where
import Data.Char
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Char
import Text.ParserCombinators.Parsec.Token
price   = lexeme (do{ ds1 <- many1 digit
                    ; char '.'
                    ; ds2 <- count 2 digit
                    ; return (convert 0 (ds1 ++ ds2))
                    })
          <?> "price"
          where
            convert n []     = n
            convert n (d:ds) = convert (10*n + digitToInt d) ds
-----end-----

However attempting to compile it gives the error message

Test.hs:8:
    Couldn't match
        `GenParser tok st a'
        against
        `CharParser st1 a1 -> CharParser st1 a1'
        Expected type: GenParser tok st a
        Inferred type: CharParser st1 a1 -> CharParser st1 a1
    Probable cause: `lexeme' is applied to too few arguments in the call
        (lexeme (do
                   ds1 <- many1 digit
                   char '.'
                   ds2 <- count 2 digit
                   return (convert 0 (ds1 ++ ds2))))
    In the first argument of `(<?>)', namely
        `lexeme (do
                   ds1 <- many1 digit
                   char '.'
                   ds2 <- count 2 digit
                   return (convert 0 (ds1 ++ ds2)))'


lexeme is now a record accessor of TokenParser. The idea is that you define a language with a specific comment style, reserved names, operators and so on and then let Parsec do the hard work for you :-). Basicly: 1) use makeTokenParser with a language definition to define a TokenParser 2) give "price" the TokenParser as first argument and pass it to lexeme or whitespace or whatever there is in Text.ParserCombinators.Parsec.Token

Here a version that uses TokenParser:
mkTP :: TokenParser st
mkTP = makeTokenParser
      $ emptyDef { commentStart = "{-"
                  , commentEnd   = "-}"
                  , commentLine  = "--"
                  , nestedComments = True
                  , identStart = lower <|> char '_'
                  ...
                  }

price :: TokenParser () ->  Parser Double
price tp = do whiteSpace tp
              val <- float tp
              return val
ghci or hugs
$ parse (price mkTP) "" "1.23"
        Right 1.23
$ parse (price mkTP) "" " {-comment-} 1.23"
        Right 1.23

Okay my version of price doesn't check if there are exactly 2 digits after the point but it can handle comments ;-).

Hope it helped!

 Georg
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to