Type signature inside an instance declaration

======================================================================= 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

"Kwanghoon Choi"
===================================================================== instance Arg a => Arg [a] where pr _ = "[" ++ pr (undefined :: a) ++ "]" =====================================================================
You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'. pr xs = "[" ++ pr (undefined `asTypeOf` x) ++ "]" where (x:_) = xs or pr ~(x:_) = "[" ++ pr (undefined `asTypeOf` x) ++ "]" Regards, Malcolm

Hi
You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.
pr xs = "[" ++ pr (undefined `asTypeOf` x) ++ "]" where (x:_) = xs
I prefer: pr xs = "[" ++ pr (undefined `asTypeOf` head x) ++ "]" Or even more simply: pr xs = "[" ++ pr (head x) ++ "]" I do believe there is some GHC extension that can be turned on to refer to variables like you did, but its not standard Haskell. Thanks Neil

{-# LANGUAGE ScopedTypeVariables #-}
2008/12/16 Neil Mitchell
Hi
You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.
pr xs = "[" ++ pr (undefined `asTypeOf` x) ++ "]" where (x:_) = xs
I prefer:
pr xs = "[" ++ pr (undefined `asTypeOf` head x) ++ "]"
Or even more simply:
pr xs = "[" ++ pr (head x) ++ "]"
I do believe there is some GHC extension that can be turned on to refer to variables like you did, but its not standard Haskell.
Thanks
Neil _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Push the envelope. Watch it bend.

Many thanks for your helps.
Kwanghoon
On Tue, Dec 16, 2008 at 11:22 PM, Thomas Schilling
{-# LANGUAGE ScopedTypeVariables #-}
2008/12/16 Neil Mitchell
: Hi
You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.
pr xs = "[" ++ pr (undefined `asTypeOf` x) ++ "]" where (x:_) = xs
I prefer:
pr xs = "[" ++ pr (undefined `asTypeOf` head x) ++ "]"
Or even more simply:
pr xs = "[" ++ pr (head x) ++ "]"
I do believe there is some GHC extension that can be turned on to refer to variables like you did, but its not standard Haskell.
Thanks
Neil _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Push the envelope. Watch it bend. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (4)
-
Kwanghoon Choi
-
Malcolm Wallace
-
Neil Mitchell
-
Thomas Schilling