
Hi, I was told on #haskell that I should bring this up here, to ask whether this is a bug in ghc6 or otherwise explain this to me. I’m trying to write the function "addd" which takes an arbitrary number of Integer arguments and returns the sum. This code works: -- Try 1 class More a where more ::Integer -> a instance (More a, Integral i) => More (i -> a) where more v1 v2 = more (v1 + toInteger v2) instance More Integer where more v = v addd :: More a => a addd = more 0 printI :: Integer -> IO () printI = print main = do printI $ addd printI $ addd 1 printI $ addd 1 2 printI $ addd 1 2 3 -- SNIP But when I try to use a concret type (Integer) instead of the (Integral i =>) condition (which should make the program more concrete, I’d say) and write the following instance: -- Try 2 (changed lines of code) instance More a => More (Integer -> a) where more v1 v2 = more (v1 + v2) -- SNIP I get this error: test.hs:4:0: Illegal instance declaration for `More (Integer -> a)' (All instance types must be of the form (T a1 ... an) where a1 ... an are distinct type *variables* Use -XFlexibleInstances if you want to disable this.) In the instance declaration for `More (Integer -> a)' Failed, modules loaded: none. Well, I add {-# LANGUAGE FlexibleInstances #-} and get this error for the line "printI $ addd 1" (and similar errors for the other following addd lines): test.hs:19:17: No instance for (More (t -> Integer)) arising from a use of `addd' at test.hs:19:17-22 Possible fix: add an instance declaration for (More (t -> Integer)) In the second argument of `($)', namely `addd 1' In the expression: printI $ addd 1 In a 'do' expression: printI $ addd 1 And this is the point where I’m lost and would like to ask for hints what this means. Thanks, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

'Integer -> a' is more concrete, less general than 'i -> a', so it matches fewer types. '1 :: Num a => a' is more general than 'Integer'. | No instance for (More (t -> Integer)) | arising from a use of `addd' at test.hs:19:17-22 if nothing forces the parameter (!) to be Integer, the more concrete instance won't match. try type-annotating the numeric literals. claus

Hi, Am Dienstag, den 01.04.2008, 17:53 +0100 schrieb Claus Reinke:
'Integer -> a' is more concrete, less general than 'i -> a', so it matches fewer types.
'1 :: Num a => a' is more general than 'Integer'.
| No instance for (More (t -> Integer)) | arising from a use of `addd' at test.hs:19:17-22
if nothing forces the parameter (!) to be Integer, the more concrete instance won't match. try type-annotating the numeric literals.
Indeed, printI $ addd (1::Int) (2::Int) (3::Int) does work. But I can’t follow your explanation completely. When I use the variant with Integer, ghc will not use the instance because (1::Num a => a) is too general. But why does it use the Integral i-Instance in the working variant? (1::Num a=> a) is also more general than (1::Integral i => i), isn’t it? Thanks, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

|But I can’t follow your explanation completely. When I use the variant |with Integer, ghc will not use the instance because (1::Num a => a) is |too general. | |But why does it use the Integral i-Instance in the working variant? |(1::Num a=> a) is also more general than (1::Integral i => i), isn’t it? because instance selection does not take instance contexts into account (a frequent source of feature requests;-): http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension... so, the match is against 'i', and the 'Integral i' is added to the constraints needing proof *after* that instance has been chosen. claus
participants (2)
-
Claus Reinke
-
Joachim Breitner