MPTC and type classes issue (polymorphic '+')

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/

input2 = [ InputDecs [ inp "emaLength" TyNumber (20 + 40) ] ]
(untested). Imho the simple, dumb, best fix for this is to give a explicit type to those values.
input2 = [ InputDecs [ inp "emaLength" TyNumber ((20::Integer) + (40::Integer)) ] ]
This is just one way to fix it. You could also try to improve your instances or enable -foverlapping-instances. But in my experience MPTC and overlapping instances, though powerful, can become very confusing, very quickly. Cheers pepe

Pepe, On Apr 7, 2007, at 1:31 PM, Pepe Iborra wrote:
input2 = [ InputDecs [ inp "emaLength" TyNumber ((20::Integer) + (40::Integer)) ] ]
Thank you for your suggestion! I'm trying to make my AST definition as succinct as possible, though, so I would really love to have 20 + 40. The issue is confined to a single module used during testing. Thanks, Joel -- http://wagerlabs.com/

The main problem is that you cannot assume Integral for the values 20 and 40. Those have types (Num a=>a). And without the Integral assumption, you cannot define your instance. So what I would do is to create a thin wrapper:
i = id :: Integer -> Integer
and write:
input2 = [ InputDecs [ inp "emaLength" TyNumber ((i 20) + (i 40)) ] ]
Sometimes the simplest solution is the best one Cheers pepe On 07/04/2007, at 14:35, Joel Reymont wrote:
Pepe,
On Apr 7, 2007, at 1:31 PM, Pepe Iborra wrote:
input2 = [ InputDecs [ inp "emaLength" TyNumber ((20::Integer) + (40::Integer)) ] ]
Thank you for your suggestion! I'm trying to make my AST definition as succinct as possible, though, so I would really love to have 20 + 40. The issue is confined to a single module used during testing.
Thanks, Joel

Pepe, On Apr 7, 2007, at 2:01 PM, Pepe Iborra wrote:
And without the Integral assumption, you cannot define your instance. So what I would do is to create a thin wrapper:
i = id :: Integer -> Integer
and write:
input2 = [ InputDecs [ inp "emaLength" TyNumber ((i 20) + (i 40)) ] ]
That's what I did but I'm driving to make it even simpler. I would like to add various permutations of Integer, Double and NumExpr, as well as String and StrExpr. This includes Integer/ Integer, Integer/Double, Double/NumExpr, etc. This is standalone code, also at http://hpaste.org/1291#a12 {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-} import Prelude hiding ( id, (+), (-), (/), (*), (>), GT, EQ, LT ) newtype VarIdent = VarIdent String instance Show VarIdent instance Eq VarIdent data NumExpr = Int Integer | Double Double | NumOp NumOp NumExpr NumExpr data StrExpr = Str String | StrOp StrOp StrExpr StrExpr data Expr = NumExpr NumExpr | StrExpr StrExpr data Type = TyNumber | TyString data NumOp = Plus | Minus -- ... data StrOp = StrPlus data Statement = Skip | InputDecs [InputDecl] data InputDecl = InputDecl VarIdent Type Expr class PlusClass a b c | a b -> c where (+) :: a -> b -> c -- instance PlusClass a b c => PlusClass b a 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) -- and the functions id = VarIdent inp x ty e = InputDecl (id x) ty e input2 = [ InputDecs [ inp "emaLength" TyNumber (20 + 40) ] ] -- http://wagerlabs.com/

On Apr 7, 2007, at 2:01 PM, Pepe Iborra wrote:
So what I would do is to create a thin wrapper:
i = id :: Integer -> Integer
and write:
input2 = [ InputDecs [ inp "emaLength" TyNumber ((i 20) + (i 40)) ] ]
I do it like this and it does save typing. It's not bad so I'll stick to it for now: id = VarIdent d = Double i = Int b = Bool s = Str d' = NumExpr . d i' = NumExpr . i b' = CondExpr . b s' = StrExpr . s n = NumExpr (+) a b = NumExpr (NumOp Plus a b) This is much less verbose than my OCaml version anyway. -- http://wagerlabs.com/

On Sat, Apr 07, 2007 at 01:07:48PM +0100, Joel Reymont wrote:
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))
Here is a large part of your problem - unsuprisingly enough, Integer is an instance of Integral.
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.
You can probably use -fallow-incoherent-instances for this. It has a scary name on purpose since it doesn't usually do what you think it should... My (very limited!) understanding of type checking algorithms says that in this case, the worst that can fail is an extra call to fromInteger :: Integer -> Integer. Big deal.
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.
Stefan

On Apr 7, 2007, at 4:16 PM, Stefan O'Rear wrote:
You can probably use -fallow-incoherent-instances for this. It has a scary name on purpose since it doesn't usually do what you think it should... My (very limited!) understanding of type checking algorithms says that in this case, the worst that can fail is an extra call to fromInteger :: Integer -> Integer. Big deal.
It only works until I add instance declarations for Fractional. Thanks, Joel -- http://wagerlabs.com/
participants (3)
-
Joel Reymont
-
Pepe Iborra
-
Stefan O'Rear