[Haskell-cafe] MPTC and type classes issue (polymorphic '+')

Joel Reymont joelr1 at gmail.com
Sat Apr 7 08:07:48 EDT 2007


Folks,

I'm trying to save time when typing in my ASTs so I thought I would  
create a Plus class like this (I do hide the one from Prelude)

class PlusClass a b c | a b -> c where
     (+) :: a -> b -> c

{-
instance (Integral a, Integral b) => PlusClass a b Expr where
     a + b = NumExpr (NumOp Plus (Int (fromIntegral a)) (Int  
(fromIntegral b)))

instance Integral a => PlusClass a Double Expr where
     a + b = NumExpr (NumOp Plus (Int (fromIntegral a)) (Double b))
-}

instance PlusClass Integer Integer Expr where
     a + b = NumExpr (NumOp Plus (Int a) (Int b))

instance PlusClass Double Integer Expr where
     a + b = NumExpr (NumOp Plus (Double a) (Int b))

instance PlusClass NumExpr NumExpr Expr where
     a + b = NumExpr (NumOp Plus a b)

instance PlusClass Integer NumExpr Expr where
     a + b = NumExpr (NumOp Plus (Int a) b)

instance PlusClass  NumExpr Integer Expr where
     a + b = NumExpr (NumOp Plus a (Int b))

instance PlusClass String String Expr where
     a + b = StrExpr (StrOp StrPlus (Str a) (Str b))

NumExpr and StrExpr return Expr whereas Int, Double return NumExpr  
and Str returns StrExpr.

This is all so that I could type in

input2 =
     [ InputDecs [ inp "emaLength" TyNumber (20 + 40) ] ]

Still, I get the following error

Easy/Test/ParserAST.hs:76:44:
     No instance for (PlusClass t t1 Expr)
       arising from use of `+' at Easy/Test/ParserAST.hs:76:44-50
     Possible fix: add an instance declaration for (PlusClass t t1 Expr)
     In the third argument of `inp', namely `(20 + 40)'
     In the expression: inp "emaLength" TyNumber (20 + 40)
     In the first argument of `InputDecs', namely
	`[inp "emaLength" TyNumber (20 + 40)]'

and get an overlapped instances error if I uncomment the top portion.

Any suggestions on how to resolve this?

	Thanks, Joel

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list