When I run the following code without the "import Data.Char" I get an error that digitToInt is not defined. When I put the import in I get a large number of errors that weren't there before.
Can some one explain this to me? How can I get this code to work?
--- Here is the code ---
module Expressionparser where
import Data.Char import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec.Expr import Text.ParserCombinators.Parsec.Token import Text.ParserCombinators.Parsec.Language
run :: Show a => Parser a -> String -> IO() run p input = case(parse p "" input) of Left err -> do { putStr "parse error at " ; print err } Right x -> print x
runLex :: Show a => Parser a -> String -> IO() runLex p = run (do{ whiteSpace lang ; x <- p ; eof ; return x } )
lang = makeTokenParser (haskellStyle{ reservedNames = ["return","total"]})
expr = buildExpressionParser table factor <?> "expression"
table = [ [op "*" (*) AssocLeft, op "/" div AssocLeft]
, [op "+" (+) AssocLeft, op "-" (-) AssocLeft] ]
where
op s f assoc = Infix (do{ symbol lang s; return f } <?> "operator") assoc
factor = parens lang expr <|> natural lang <?> "simple expression"
test1 = do{ n <- natural lang
; do{ symbol lang "+"
; m <- natural lang
; return (n+m) } <|> return n
}
-----------------------------------------------------------
price :: Parser Int -- this is the price in cents 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
receipt :: Parser Bool receipt = do{ ps <- many produkt ; p <- total ; return (sum ps == p) }
produkt = do{ symbol "return" ; p <- price ; semi ; return (-p) } <|> do{ identifier ; p <- price ; semi ; return p } <?> "produkt"
total = do{ p <- price ; symbol "total" ; return p }
--- end code ---
Here are the errors:
___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.2.2, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \____/\/ /_/\____/|_| Type :? for help.
Loading package base ... linking ... done.
Prelude> :l ~/expression-parser.hs Compiling Expressionparser ( /home/greg//expression-parser.hs, interpreted )
/home/greg//expression-parser.hs:59: Variable not in scope: `digitToInt' Failed, modules loaded: none. Prelude> :r Compiling Expressionparser ( /home/greg//expression-parser.hs, interpreted )
/home/greg//expression-parser.hs:51: 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)))'
/home/greg//expression-parser.hs:67: Couldn't match `GenParser tok st' against `(->) String' Expected type: GenParser tok st t Inferred type: String -> CharParser st1 String Probable cause: `symbol' is applied to too few arguments in the call (symbol "return") In a 'do' expression: symbol "return"
/home/greg//expression-parser.hs:80:
Couldn't match `GenParser Char ()' against `(->) String'
Expected type: GenParser Char () t
Inferred type: String -> CharParser st String
Probable cause: `symbol' is applied to too few arguments in the call
(symbol "total")
In a 'do' expression: symbol "total"
Failed, modules loaded: none.
Prelude>
-- +++++ Greg Wolff Our Lady Queen of Peace [EMAIL PROTECTED] Pray for us! _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe