[Haskell-cafe] About the parse error (possibly incorrect indentation)

xu zhang douyaxu at gmail.com
Thu Sep 17 20:17:22 EDT 2009


Hi, I am trying to get the function showMinProp to return String, but I
always get an error of parse error (possibly incorrect indentation)
Who can help with this? any idea?
Thank u in advance!

data Prop
  = Var String
  | Negation Prop
  | BinOp Op Prop Prop

data Op = And | Or | Implies | Equiv
               derived Eq

showOp :: Op -> String
showOp And      = "&"
showOp Or       = "|"
showOp Implies  = "=>"
showOp Equiv    = "<=>"

instance Show Op where show = showOp

precList = [(And,4),(Or,3),(Implies,2),(Equiv,1)]
showProp :: Prop -> String
showProp (Var s) = s
showProp (Negation p) = "~" ++ showProp p
showProp (BinOp op p q) = paren (showProp a p ++ space (showOp op) ++
showProp a q)

showMinProp :: Int -> Prop -> String
showMinProp preNo (BinOp op p q) =
       case op of
         And -> let a = 4
         Or  -> let a = 3
         Implies -> let a = 2
         Equiv   -> let a = 1
       if (a > preNo)
         then (showMinProp a p  ++ space (showOp op) ++ showMinProp a q)
         else paren (showMinProp a p ++ space (showOp op) ++ showMinProp a
q))

space s = " " ++ s ++ " "
paren s = "(" ++ s ++ ")"

instance Show Prop where show = showProp
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090917/06077285/attachment.html


More information about the Haskell-Cafe mailing list