
Hello. I am new to Haskell and I am going through "Haskell: The craft of functional programming". I am trying to grasp haskell's classes and instances, so here is slightly modified code from the book: class Show a => Visible a where toString :: a -> String toString = show size :: a -> Int size = length . show instance Visible a => Visible [a] where toString = concat . map toString size = foldl (+) 0 . map size vSort :: (Visible a, Ord a) => [a] -> String vSort = toString . List.sort s = vSort [1..3] Unfortunetly in ghc it gives the following type error: Ambiguous type variable `a' in the constraints: `Visible a' arising from use of `vSort' at d:/tmp.hs:83:4-8 `Enum a' arising from the arithmetic sequence `1 .. 3' at d:/tmp.hs:83:10-15 `Num a' arising from the literal `3' at d:/tmp.hs:83:14 `Ord a' arising from use of `vSort' at d:/tmp.hs:83:4-8 Probable fix: add a type signature that fixes these type variable(s) Failed, modules loaded: none. As you can see, Visible is nothing more than an adapter to the Show class. How I got thing so far, [1..3] :: (Num a, Enum a) => [a], has a Show instance so does class Num (which 'subclasses' Show). Therefore, I can't see any reason why toString function can't call show from those instances. Can someone please enlighten my (still) C++ thinking head? -- Slavomir Kaslev

Err, sorry for the meaningless mail subject. Should be 'Newbie class problem' or something like that. -- Slavomir Kaslev

Am Donnerstag, 2. November 2006 00:06 schrieb Slavomir Kaslev:
Hello.
I am new to Haskell and I am going through "Haskell: The craft of functional programming". I am trying to grasp haskell's classes and instances, so here is slightly modified code from the book:
class Show a => Visible a where toString :: a -> String toString = show size :: a -> Int size = length . show
instance Visible a => Visible [a] where toString = concat . map toString size = foldl (+) 0 . map size
vSort :: (Visible a, Ord a) => [a] -> String vSort = toString . List.sort ^^^^^^^ my ghc complained that List.sort is not in scope, did you import Data.List as List?
s = vSort [1..3]
Unfortunetly in ghc it gives the following type error: Ambiguous type variable `a' in the constraints: `Visible a' arising from use of `vSort' at d:/tmp.hs:83:4-8 `Enum a' arising from the arithmetic sequence `1 .. 3' at d:/tmp.hs:83:10-15 `Num a' arising from the literal `3' at d:/tmp.hs:83:14 `Ord a' arising from use of `vSort' at d:/tmp.hs:83:4-8 Probable fix: add a type signature that fixes these type variable(s) Failed, modules loaded: none.
As you can see, Visible is nothing more than an adapter to the Show class. How I got thing so far, [1..3] :: (Num a, Enum a) => [a], has a Show instance so does class Num (which 'subclasses' Show). Therefore, I can't see any reason why toString function can't call show from those instances.
First problem: class Visible has no instances yet, so even if you disambiguate the type by writing e.g. s = vSort [1 :: Int .. 3], you'll get an error message: Visible.hs:20:4: No instance for (Visible Int) arising from use of `vSort' at Visible.hs:20:4-8 Probable fix: add an instance declaration for (Visible Int) In the definition of `s': s = vSort ([1 :: Int .. 3]) And the second problem: The typechecker has no means of determining which type 1 should have. By virtue of the fact that numeric literals are overloaded in Haskell, it has type Num a => a. The use of enumFromTo adds the Enum a constraint and vSort adds Ord and Visible, however there may be many types satisfying these constraints and ghc says it's up to you to select one. And even if there is only one instance of Visible declared, ghc (nor, as far as I know, any other Haskell implementation) won't select that because there might, somewhere in a long-forgotten directory, lie a module dormant in which another instance satisfying all constraints is declared. To sum up: instance selection is left to the user, the compiler does only type _inference_. Often that determines which instance fits, but sometimes you have to give an expression type signature to tell the compiler what to choose.
Can someone please enlighten my (still) C++ thinking head?
Cheers, Daniel

Hello Slavomir, Thursday, November 2, 2006, 2:06:05 AM, you wrote:
Can someone please enlighten my (still) C++ thinking head?
you is not alone :))) look into http://haskell.org/haskellwiki/OOP_vs_type_classes -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (3)
-
Bulat Ziganshin
-
Daniel Fischer
-
Slavomir Kaslev