[Haskell-cafe] Associative prefix operators in Parsec
Christian Maeder
Christian.Maeder at dfki.de
Thu Mar 8 09:57:29 CET 2012
The simplest solution is to parse the prefixes yourself and do not put
it into the table.
(Doing the infixes "&" and "|" by hand is no big deal, too, and possibly
easier then figuring out the capabilities of buildExpressionParser)
Cheers C.
Am 07.03.2012 13:08, schrieb Troels Henriksen:
> Consider a simple language of logical expressions:
>
>> import Control.Applicative
>> import Text.Parsec hiding ((<|>), many)
>> import Text.Parsec.String
>> import Text.Parsec.Expr
>>
>> data Expr = Truth
>> | Falsity
>> | And Expr Expr
>> | Or Expr Expr
>> | Not Expr
>> deriving (Show, Eq)
>
> I define a simple expression parser using Parsec:
>
>> expr :: Parser Expr
>> expr = buildExpressionParser table (lexeme term)
>> <?> "expression"
>>
>> term :: Parser Expr
>> term = between (lexeme (char '(')) (lexeme (char ')')) expr
>> <|> bool
>> <?> "simple expression"
>>
>> bool :: Parser Expr
>> bool = lexeme (string "true" *> pure Truth)
>> <|> lexeme (string "false" *> pure Falsity)
>>
>> lexeme :: Parser a -> Parser a
>> lexeme p = p<* spaces
>>
>> table = [ [prefix "!" Not ]
>> , [binary "&" And AssocLeft ]
>> , [binary "|" Or AssocLeft ]
>> ]
>>
>> binary name fun assoc = Infix (do{ lexeme (string name); return fun }) assoc
>> prefix name fun = Prefix (do{ lexeme (string name); return fun })
>
> Now this doesn't work:
>
>> test1 = parseTest expr "!!true"
>
> But this does:
>
>> test2 = parseTest expr "!(!true)"
>
> I have studied the code for buildExpressionParser, and I know why this
> happens (prefix operators are treated as nonassociative), but it seems
> like one would often want right-associative prefix operators (so test1
> would work). Is there a common workaround or solution for this problem?
> I assume the nonassociativity in Parsec is by design and not a bug.
>
More information about the Haskell-Cafe
mailing list