Hello Paul,

As far as I can see you're calling the parens accessor function of the TokenParser record instead of supplying a parser. Here is a working example grammar I made for my bachelor paper a while ago:

module ExpressionsWithLexer where
import Text.ParserCombinators.Parsec.Expr
import Text.ParserCombinators.Parsec
import qualified Text.ParserCombinators.Parsec.Token as P
import Text.ParserCombinators.Parsec.Language


{-
Leftassociative: +, -, *, /
Rightassociative: ^
Priority 1: +,-
Priority 2: *, /
Priority 3: ^

expr   ::= factor (op factor)*
factor ::= number | '(' expr ')'

op     ::= '+' | '-' | '*' | '/' | '^'

number ::= ('0' | '1' | ... | '9')+
-}

lexer :: P.TokenParser ()
lexer = P.makeTokenParser
        (emptyDef
        { reservedOpNames = ["*","/","+","-", "^"]
        })

whiteSpace= P.whiteSpace lexer
natural = P.natural lexer
parens = P.parens lexer
reservedOp = P.reservedOp lexer

gram   = do  whiteSpace
             x <- expr
             eof
             return x

expr :: Parser Integer
expr = buildExpressionParser table factor
       <?> "expression"

-- Earlier in the list means a higher priority
table = [[op "^" (^) AssocRight]
        ,[op "*" (*) AssocLeft, op "/" div AssocLeft]
        ,[op "+" (+) AssocLeft, op "-" (-) AssocLeft]
        ]
       where op s f assoc = Infix (do{ reservedOp s; return f} <?> "operator") assoc
                           

factor = natural
         <|>
         (parens expr
          <?> "factor")

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

exampleRun = run gram "(10 ^3 - (1 + 3))"


This grammar parses the EBNF like grammar included in the source.

As you can see parens is an accessor function of the TokenParser record. A TokenParser record is thus produced by calling makeTokenParser and supplying that function with a language definition. I used the emptyDef (empty definition) as an argument for the makeTokenParser and only updated the operatornames. After constructing a TokenParser parsers such as parens are accessed by their accessor functions. For ease of use you can use a qualified import for the token parser module and define the parens parser and other parsers at toplevel like I did.

I only tested this with Parsec 2.1.0.1 but the idea should be the same. You can read some more explanations and examples in my bachelor paper if you'd like[1][2].

Good luck,

Bas van Gijzel

(server is currently down :( )
[1] Comparing Parser Construction Techniques: http://referaat.cs.utwente.nl/new/papers.php?confid=12
[2] Parser Code: http://fmt.cs.utwente.nl/~michaelw/projects/vgijzel/ParserCode.zip

On Sat, Jul 11, 2009 at 00:27, Paul Sujkov <psujkov@gmail.com> wrote:
Hi haskellers,

I'm trying to use buildExpressionParser parser generator from ParsecExpr module of Parsec (http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#ParsecExpr). It works well, except for the "parens" token parser (http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#parens). This code (sample from Expressions part of the manual) typechecks fine:

expr    :: Parser Integer
expr    = buildExpressionParser table factor
        <?> "expression"

table   = [[op "*" (*) AssocLeft, op "/" div AssocLeft]
          ,[op "+" (+) AssocLeft, op "-" (-) AssocLeft]
          ]         
        where
          op s f assoc
             = Infix (do{ string s; return f}) assoc


factor  = do{ char '('
            ; x <- expr
            ; char ')'
            ; return x
            }
        <|> number
        <?> "simple expression"

but if I try to use parens:

factor  = parens expr
        <|> number
        <?> "simple expression"

it fails to typecheck:

Couldn't match expected type `GenTokenParser s u m'
           against inferred type `Parser Integer'
    In the first argument of `parens', namely `expr'
    In the first argument of `(<|>)', namely `parens expr'
    In the first argument of `(<?>)', namely `parens expr <|> number'
Failed, modules loaded: none.

the type of expr infers to GenParser Char () Integer, and the expected type for the parens is GenTokenParser s u m (however, manual introduces it with the type CharParser st a expected)

It seems pretty weird for me, as there are numerous examples of using parens with the buildExpressionParser (e.g. http://blog.moertel.com/articles/2005/08/27/power-parsing-with-haskell-and-parsec) and nobody comments such an error. I know I'm missing something very simple here, maybe someone could help me with it? Thanks in advace

I'm using GHC 6.10.1 and Parsec 3.0.0

--
Regards, Paul Sujkov

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe