ghc fails to find the right instance

Joachim Breitner mail at joachim-breitner.de
Tue Apr 1 12:30:43 EDT 2008


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 at joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nomeata at debian.org
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Dies ist ein digital signierter Nachrichtenteil
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20080401/ba855517/attachment.bin


More information about the Glasgow-haskell-users mailing list