Polymorphic addition function with variable number of arguments?

Dear Haskellers, I'm trying to define a polymorphic "add" function which takes a variable number of arguments (instance of Num) and returns their sum. I don't want to specify the types of the arguments while calling the function, I just want to , at most, specify the return type (*it should infer that the return type is the type of the arguments*). class Add a b where add :: a -> b instance Num a => Add a a where add = id instance (Num a, Add a b) => Add (a -> b) where add x y = add (x + y) Can someone tell me why this is not working and propose a fix for this, if possible? Thanks in advance

Can someone tell me why this is not working
that "someone" is actually ghci: Prelude> instance (Num a, Add a b) => Add (a -> b) where add x y = add (x + y) <interactive>:8:30: Expecting one more argument to `Add (a -> b)' In the instance declaration for `Add (a -> b)'

I'm sorry this was a typo. Here's the correct one: {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} class Add a b where add :: a -> b instance Num a => Add a a where add = id instance (Num a, Add a b) => Add a (a -> b) where add x y = add (x + y) I'm trying to use the printf trick to achieve this. On Tue, Mar 13, 2012 at 9:30 PM, Johannes Waldmann < waldmann@imn.htwk-leipzig.de> wrote:
Can someone tell me why this is not working
that "someone" is actually ghci:
Prelude> instance (Num a, Add a b) => Add (a -> b) where add x y = add (x + y)
<interactive>:8:30: Expecting one more argument to `Add (a -> b)' In the instance declaration for `Add (a -> b)'
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The problem seems to be that numeric literals are polymorphic. With your code, this works: *Main> let x = 8 :: Int *Main> add x x x :: Int 24 *Main> add x x :: Int 16
participants (2)
-
Johannes Waldmann
-
Some One