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
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to