Haskell/Advanced type classes

From Wikibooks, open books for an open world
Jump to navigation Jump to search

Type classes may seem innocuous, but research on the subject has resulted in several advancements and generalisations which make them a very powerful tool.

Multi-parameter type classes[edit | edit source]

Multi-parameter type classes are a generalisation of the single parameter type classes, and are supported by some Haskell implementations.

Suppose we wanted to create a 'Collection' type class that could be used with a variety of concrete data types, and supports two operations -- 'insert' for adding elements, and 'member' for testing membership. A first attempt might look like this:

Example: The Collection type class (wrong)

 class Collection c where
     insert :: c -> e -> c
     member :: c -> e -> Bool

 -- Make lists an instance of Collection:
 instance Collection [a] where
     -- insert :: [a] -> e -> [a]
     insert xs x = x:xs
     -- member :: [a] -> e -> Bool
     member = flip elem

This won't compile, however because the arguments to (:) must be of type [a] and a whereas we supply an e. The problem is that the 'e' type variable in the Collection operations comes from nowhere -- there is nothing in the type of an instance of Collection that will tell us what the 'e' actually is, so we can never define implementations of these methods. Multi-parameter type classes solve this by allowing us to put 'e' into the type of the class. Here is an example that compiles and can be used:

Example: The Collection type class (right)

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 class Eq e => Collection c e where
     insert :: c -> e -> c
     member :: c -> e -> Bool

 instance Eq a => Collection [a] a where
     insert = flip (:)
     member = flip elem

Functional dependencies[edit | edit source]

A problem with the above example is that, in this case, we have extra information that the compiler doesn't know, which can lead to false ambiguities and over-generalised function signatures. In this case, we can see intuitively that the type of the collection will always determine the type of the element it contains - so if c is [a], then e will be a. If c is Hashmap a, then e will be a. (The reverse is not true: many different collection types can hold the same element type, so knowing the element type was e.g. Int, would not tell you the collection type).

In order to tell the compiler this information, we add a functional dependency, changing the class declaration to

Example: A functional dependency

 {-# LANGUAGE FunctionalDependencies #-}
 class Eq e => Collection c e | c -> e where ...

A functional dependency is a constraint that we can place on type class parameters. Here, the extra | c -> e should be read 'c uniquely identifies e', meaning for a given c, there will only be one e. You can have more than one functional dependency in a class -- for example you could have c -> e, e -> c in the above case. And you can have more than two parameters in multi-parameter classes.

Examples[edit | edit source]

Matrices and vectors[edit | edit source]

Suppose you want to implement some code to perform simple linear algebra:

Example: The Vector and Matrix datatypes

 data Vector = Vector Int Int deriving (Eq, Show)
 data Matrix = Matrix Vector Vector deriving (Eq, Show)

You want these to behave as much like numbers as possible. So you might start by overloading Haskell's Num class:

Example: Instance declarations for Vector and Matrix

instance Num Vector where
  Vector a1 b1 + Vector a2 b2 = Vector (a1+a2) (b1+b2)
  Vector a1 b1 - Vector a2 b2 = Vector (a1-a2) (b1-b2)
  {- ... and so on ... -}

instance Num Matrix where
  Matrix a1 b1 + Matrix a2 b2 = Matrix (a1+a2) (b1+b2)
  Matrix a1 b1 - Matrix a2 b2 = Matrix (a1-a2) (b1-b2)
  {- ... and so on ... -}

The problem comes when you want to start multiplying quantities. You really need a multiplication function which overloads to different types:

Example: What we need

(*) :: Matrix -> Matrix -> Matrix
(*) :: Matrix -> Vector -> Vector
(*) :: Matrix -> Int -> Matrix
(*) :: Int -> Matrix -> Matrix
{- ... and so on ... -}

How do we specify a type class which allows all these possibilities?

We could try this:

Example: An ineffective attempt (too general)

class Mult a b c where
  (*) :: a -> b -> c

instance Mult Matrix Matrix Matrix where
  {- ... -}

instance Mult Matrix Vector Vector where
  {- ... -}

That, however, isn't really what we want. As it stands, even a simple expression like this has an ambiguous type unless you supply an additional type declaration on the intermediate expression:

Example: Ambiguities lead to more verbose code

m1, m2, m3 :: Matrix
(m1 * m2) * m3              -- type error; type of (m1*m2) is ambiguous
(m1 * m2) :: Matrix * m3    -- this is ok

After all, nothing is stopping someone from coming along later and adding another instance:

Example: A nonsensical instance of Mult

instance Mult Matrix Matrix (Maybe Char) where
  {- whatever -}

The problem is that c shouldn't really be a free type variable. When you know the types of the things that you're multiplying, the result type should be determined from that information alone.

You can express this by specifying a functional dependency:

Example: The correct definition of Mult

class Mult a b c | a b -> c where
  (*) :: a -> b -> c

This tells Haskell that c is uniquely determined from a and b.