[Haskell-beginners] MultiParamTypeClasses confusion

Derek McLoughlin derek.mcloughlin at gmail.com
Mon Mar 10 12:59:04 UTC 2014


Hi,

In Chapter 6 of "Beginning Haskell" by Apress there's a couple of
classes introduced for vectors and things that can be vectorized (not
related to Data.Vector)

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

class Vector v where
    distance :: v -> v -> Double

instance Vector (Double, Double) where
    distance (a,b) (c,d) = sqrt $ (c - a) * (c - a) + (d - b) * (d - b)

class Vectorizable e v where
    toVector :: e -> v

instance Vectorizable (Double, Double) (Double, Double) where
    toVector = id

x = 1.0 :: Double
y = 10.0 :: Double

While I understand how to use the "distance" function:

ghci> distance (x, x) (y, y)
12.727922061357855

... and I can see how "toVector" is used in their code

ghci> distance (x, x) $ toVector (y, y)
12.727922061357855

I don't understand why this doesn't work:

ghci> let z = toVector (y, y)
interactive>:32:9:
    No instance for (Vectorizable (Double, Double) v0)
      arising from a use of `toVector'
    The type variable `v0' is ambiguous
    Possible fix: add a type signature that fixes these type variable(s)
    Note: there is a potential instance available:
      instance Vectorizable (Double, Double) (Double, Double)
        -- Defined at vector.hs:13:10
    Possible fix:
      add an instance declaration for (Vectorizable (Double, Double) v0)
    In the expression: toVector (y, y)
    In an equation for `z': z = toVector (y, y)

It seems odd that "toVector" works when used as an argument to
"distance" but not when used in a let expression.

Can anyone explain?

Derek.


More information about the Beginners mailing list