[Haskell-beginners] Question regarding to type classes

Daniel Fischer daniel.is.fischer at googlemail.com
Sat Sep 24 19:52:49 CEST 2011


On Saturday 24 September 2011, 19:21:17, Johannes Engels wrote:
> Dear list members,
> 
> as an exercise, I tried to define a type class for structures with
> ordered key values. The key values could be numbers, but also strings.
> For instance, I intend to define an address list containing records with
> names as key values. So far, my type class definition contains a
> function "key", which should extract the key values from the structures,
> and a function which compares the key values. So I tried:
> 
> class StructsWithOrderedKeys a where
> -- no default definition for key
>     key :: (Ord b) => a -> b

This does not mean what I think you intend.
This type signature means that key can produce any type belonging to Ord, 
whatever the caller desires.
So, I need a String, key can produce it, Bool? too, from the same value, 
Integer? yes, also that...

> 
>     (<?) :: a -> a -> Bool
>     x <? y = (key x) < (key y)
> 
> Here I get the following error message from GHCI:
> 
> "Ambiguous type variable 'b' in the constraint:
> 'Ord b' arising from a use of 'key' ...
> Probable fix: add a type signature that fixes these type variable(s)"
> 
> Could anybody explain what ambiguity arises here? As the arguments of
> (<?) are of the same type, I expected also the results (key x) and (key
> y) to be of the same type, which should be by the type constraint for
> "key" an instance of Ord. Why I am not allowed to use "key" in the
> definition of (<?) ?

Because, as said above, key's type says it can produce values of different 
types from the same argument, so the compiler can't know which type to 
pick, should it produce

  x <? y = (key x :: Integer) < key y

or

  x <? y = (key x :: String) < key y

or ...

So the type at which to do the comparison is ambiguous.

What you probably intended is that for every type s which is an instance of 
StructsWithOrderedKeys, there is a type k, belonging to Ord, such that the 
function key produces values of type k from values of type s.

You can achieve that by using multiparameter type classes (with functional 
dependencies) or associated types.

With associated types, it would be

==========
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
module Structs where


class (Ord (Key a)) => StructsWithOrderedKeys a where
  type Key a
  key ::a -> Key a
  (<?) :: a -> a -> Bool
  x <? y = key x < key y

data Pair = P { pkey :: String, pval :: Int } deriving Show

instance StructsWithOrderedKeys Pair where
  type Key Pair = String
  key = pkey
==========

and with multiparameter type classes

==========
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Structs where

-- The "| a -> b" is the functional dependency saying that a
-- uniquely determines b
class (Ord b) => StructsWithOrderedKeys a b | a -> b where
  key :: a -> b
  (<?) :: a -> a -> Bool
  x <? y = key x < key y

data Pair = P { pkey :: String, pval :: Int } deriving Show

instance StructsWithOrderedKeys Pair String where
  key = pkey
=========

Use what you prefer, some things are easier to express using FunDeps, 
others using associated types.
Generally, FunDeps were there first, but people tend to rather use type 
families nowadays.



More information about the Beginners mailing list