Type signature inside an instance declaration

Kwanghoon Choi lazyswamp at gmail.com
Tue Dec 16 07:08:16 EST 2008


=======================================================================
module Test where
class Arg a where
  pr :: a -> String
instance Arg Int where
  pr _ = "i"
instance Arg Char where
  pr _ = "c"
instance Arg a => Arg [a] where
  pr _ = "[" ++ pr (undefined :: a) ++ "]"      -- the type variable 'a' is
interpreted as an unbound one.
  -- (1) pr :: [a] -> String
  -- (2) pr (_ :: [a]) = "[" ++ pr (undefined :: a) ++ "]"
=======================================================================

Dear All,

I got some problem when I try to compile the above program.

The problem is due to the presence of a type variable 'a' in the body of the
last instance declaration.
How could I refer to the type variable of Arg [a] in the instance
declaration?

I tried these options
   1) by giving an explicit declaration for pr
   2) by giving a type signature to the argument of pr with
-XPatternsSignatures

The first option gives me back an error :
    Misplaced type signature: pr :: [a] -> String
    The type signature must be given where `pr' is declared

The second option gives me an error:
    Test.hs:21:12: Not in scope: type variable `a'

Would anybody help me to understand this problem?

Thanks in advance.

Kwanghoon
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081216/563f748c/attachment-0001.htm


More information about the Glasgow-haskell-users mailing list