[Haskell-cafe] Polymorphic addition function with variable number of arguments?
Some One
haskellie at gmail.com
Tue Mar 13 20:49:26 CET 2012
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 at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120313/4b51a851/attachment.htm>
More information about the Haskell-Cafe
mailing list