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

Joel Reymont joelr1 at gmail.com
Sat Apr 7 09:05:47 EDT 2007


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/







More information about the Haskell-Cafe mailing list