
Hello Cafe, I am trying to write a parser for propositional logic[1]. It's working fine for every input except equivalence ( <=> ). *Main> calculator "a=>b" Imp (Lit 'a') (Lit 'b') *Main> calculator "a<=b" Red (Lit 'a') (Lit 'b') *Main> calculator "a<=>b" *** Exception: failed to parse I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= ) and next character is '>' so it is parse error . If I remove both implication and reduction then equivalence is working fine. *Main> calculator "a<=>b" Eqi (Lit 'a') (Lit 'b') Could some please tell me how to solve this problem. I also tried fixity declaration but got this error LogicPraser.hs:12:10: The fixity signature for `<=>' lacks an accompanying binding -Mukesh Tiwari [1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html {-# LANGUAGE NoMonomorphismRestriction #-} import Text.Parsec.Token import Text.Parsec.Prim import Text.Parsec.Char import Text.Parsec.Expr import Text.Parsec.Combinator import Text.Parsec.Language import Control.Applicative hiding ( ( <|> ) , many ) import Data.Maybe ( fromJust ) --infixl 9 <=> data LExpr = Lit Char | Not LExpr | And LExpr LExpr | Or LExpr LExpr | Imp LExpr LExpr -- (=>) | Red LExpr LExpr -- ( <= ) | Eqi LExpr LExpr -- ( <=> ) deriving Show exprCal = buildExpressionParser table atom table = [ [ Prefix ( Not <$ string "~" ) ] , [ Infix ( And <$ string "&" ) AssocLeft ] , [ Infix ( Or <$ string "|" ) AssocLeft ] , [ Infix ( Imp <$ string "=>" ) AssocLeft , Infix ( Red <$ string "<=" ) AssocLeft , Infix ( Eqi <$ string "<=>" ) AssocLeft ] ] atom = char '(' *> exprCal <* char ')' <|> ( Lit <$> letter ) calculator :: String -> LExpr calculator expr = case parse exprCal "" expr of Left msg -> error "failed to parse" Right ( val ) -> val ~