Types can be thought of roughly as sets of values that bear similarities. Similarly, type classes (shown in blue below) are sets of types that bear similarities: every type in a particular class defines a common set of members — that is, functions or other values — with particular type signatures. And we’ll see that there are different kinds of types (shown in red).
Diagram based on this image from this wiki.
Consider the Eq
type class from the
Prelude
. There are two parts to the definition. First, a
list of members and type signatures that must be implemented by any type
a
to be added to the Eq
type class. Second, a
list of default implementations for members that are not provided
explicitly.
class Eq t where
-- type signatures for required members
(==) :: t -> t -> Bool
(/=) :: t -> t -> Bool
-- default implementations (used when not explicitly defined)
x == y = not (x /= y)
x /= y = not (x == y)
In this class, notice how (==)
and (/=)
are
defined mutually recursively. As long as one of the operations is
defined for a particular type (overriding the default definition), the
definition of the other “comes for free.”
In addition to the definition itself, there are two additional
components that are described informally, in comments or in the
documentation. First, because of the default implementations, the
minimal complete definition is either (==)
or
(/=)
; no need to provide both.
The second additional component is a set of (unchecked) laws that
each implementation is assumed to satisfy. For each type a
in Eq
, the law is:
∀ x
::
a
, y
::
a
. (x == y) == not (x /= y)
Notice that this law is respected by the default implementations, but can be broken by an explicit instance definition.
The Eq
class is defined in Prelude
. To test
out the class definition above, you’ll have to hide things; rather, you
can explicitly import Prelude
with very little. For
example, in a file Eq.hs
:
import Prelude (Bool(..), not)
...
The Bool(..)
entry imports the Bool
datatype and its data constructors (False
and
True
).
What are the types of the Eq
operations?
> :t (==)
> :t (/=)
Adding a type T
to a class C
requires an
instance declaration that implements the members of
C
, with types specialized to T
.
As a simple example, consider a hard-coded integer list type:
data IntList
= Nil
| Cons Int IntList
We can add IntList
to the Eq
class as
follows:
instance Eq IntList where
(==) :: IntList -> IntList -> Bool
Nil == Nil = True
Cons x xs == Cons y ys = x == y && xs == ys
_ == _ = False
Haskell allows infix operators to be defined using infix notation, as above. Equivalently with prefix notation:
instance Eq IntList where
(==) :: IntList -> IntList -> Bool
(==) Nil Nil = True
(==) (Cons x xs) (Cons y ys) = x == y && xs == ys
(==) _ _ = False
This function first checks that the data constructors match and, if
so, then recursively checks that the corresponding components are equal.
Notice that the call to (==)
in x == y
refers
to the implementation (provided by Haskell) for Int
s and
the call to (==)
in xs == ys
refers to the
implementation in the IntList
instance (that is, the
function currently being defined recursively).
We have seen how deriving
clauses can be used to
automatically generate instance declarations for certain classes. If we
had defined IntList
with the clause
deriving (Eq)
, the implementation above — checking that the
“boxes” are tagged with the same data constructors, and then checking
pairwise value equality among each of the data values inside the boxes —
is essentially what will get generated automatically. In situations
where the default implementation is not what we want, we can manually
declare the instance.
For a given type class, there can be at most one instance declaration for any particular type.
This design decision restricts some potentially useful programming patterns in exchange for automatically knowing where to find the implementation of any call to a type class member based on the types of its arguments.
Try adding a second Eq IntList
instance declaration,
either explicitly or by adding a deriving (Eq)
clause.
On a related note, you cannot hide existing instances. So, if you want to explicitly test an instance declaration that is already defined in the library, first try explicitly defining the class as noted above.
Consider a polymorphic list definition.
data List a
= Nil
| Cons a (List a)
instance Eq a => Eq (List a) where
(==) :: List a -> List a -> Bool
Nil == Nil = True
Cons x xs == Cons y ys = x == y && xs == ys
_ == _ = False
Note that our instance declaration requires a type class constraint,
to ensure that the underlying type a
is also part of
Eq
. The call to (==)
in xs == ys
refers to the implementation from the Eq a
instance. This
implementation can also be automatically derived via
deriving (Eq)
.
class Show a where
show :: a
...
> :t show
Automatically derived Show
instance for
List a
:
> Cons 1 (Cons 2 (Cons 3 Nil))
Cons 1 (Cons 2 (Cons 3 Nil))
We can make them look more like built-in lists.
instance Show a => Show (List a) where
show :: List a -> String
show Nil = "[]"
show (Cons x xs) = "(" ++ show x ++ " : " ++ show xs ++ ")"
> Cons 1 (Cons 2 (Cons 3 Nil))
(1 : (2 : (3 : [])))
class Read a where
read :: String -> a
...
The read
function is used to parse String
s
into values of some type.
Notice how the type variable a
is referred to only in
the output. Therefore, we can tell that the function will crash (rather
than return an error via Maybe
) when the there is no
meaningful a
value to return for the given input
String
. Furthermore, Haskell needs information from the
context in which read
is called to figure out which
instance declaration to use.
> read "1"
*** Exception: Prelude.read: no parse
> read "1" :: Int
1
> read "1" :: Integer
1
> read "1" :: Float
1.0
> read "1" :: Bool
*** Exception: Prelude.read: no parse
In reality, if you dig into the Prelude
you’ll see that Read
is actually defined with a member
readsPrec :: Int -> String -> [(a, String)]
and read
is a library function (outside of the
Read
class) defined in terms of the Read
members. This is a minor detail that we need not worry about for now. We
will see readsPrec
again when we program some parsers in
detail later on.
> :info Ord
class Eq a => Ord a where
(<=) :: a -> a -> Bool
...
Every type T
in Ord
must first be a member
of Eq
. Eq
is a superclass of Ord
;
Ord
is a subclass of Eq
.
There is a strong argument to be made that the arrow
=>
should have been written in the opposite
direction (i.e. <=
): the membership of a type
t
in Ord
implies that t
is in Eq
. Oh well, there’s no going back several decades in
Haskell history to revisit such syntactic choices.
> :info Num
> :info Int
> :info Floating
> :info Integral
Int
and Integer
have a common superclass
called Integral
.
> :info Enum
> [1..10]
> [1,2..10]
> [False .. True]
> [True .. False]
> :info Bounded
> minBound :: Int
> maxBound :: Int
> minBound :: Integer
> :t minBound
> minBound + 0
> (minBound :: Int) + (minBound :: 1)
> (minBound :: Int) + 1
> (minBound :: Int) + 2
> minBound + (2 :: Int)
Recall the foldr function from before…
foldr :: {- forall a b. -} (a -> b -> b) -> b -> [a] -> b
foldr f acc [] = acc
foldr f acc (x:xs) = f x (foldr f acc xs)
… which actually lives in the following class:
class Foldable t where
foldr :: (a -> b -> b) -> b -> t a -> b
foldl :: (b -> a -> b) -> b -> t a -> b
...
One minimal complete definition is foldr
. We will talk
about other members (much) later.
Lots of other data structures can be folded over, too. For example:
data BinaryTree a
= Empty
| Node a (BinaryTree a) (BinaryTree a)
deriving (Show)
instance Foldable BinaryTree where
foldr :: (a -> b -> b) -> b -> BinaryTree a -> b
foldr f acc Empty = acc
foldr f acc (Node x left right) =
foldr f (f x (foldr f acc right)) left
> :t length
length :: Foldable t => t a -> Int
> :t concat :: [[a]] -> [a]
> :t concat
concat :: Foldable t => t [a] -> [a]
> :t elem :: Eq a => (a -> [a] -> Bool)
> :t elem
elem :: (Foldable t, Eq a) => a -> t a -> Bool
> import Data.Foldable
> :t toList
Sometimes type error messages are exactly to the point:
> not "a"
...
Expected: Bool
Actual: String
...
But the presence of type classes complicates matters. For example:
> "a" + "b"
...
• No instance for (Num String) arising from a use of ‘+’
...
The message is a hedge: the expression could be well-typed
if only String
were an instance of Num
. In
this case, it is easy to diagnose the fact that we would not want to
make String
a Num
.
But sometimes, the super-general nature of constrained polymorphic type inference can hide logic errors. Consider the following definition (without a type annotation):
sum [] = 0
sum (x:xs) = x : sum xs
Think about, and then check, what type Haskell infers for
sum
, and compare it to the intended (typical) type
signature for sum
.
Recall the following:
class Eq t where
(==) :: t -> t -> Bool
(/=) :: t -> t -> Bool
class Foldable t where
foldr :: (a -> b -> b) -> b -> t a -> b
The types t
in Eq
are different types of
types than those in Foldable
. Notice how a
Foldable
type t
is referred to in type
signatures: t a
. It is a type that takes a type — in
particular, a
— an argument. This is a different kind of
type than those ranged over by a
and b
, which
are not applied to any type arguments. Yep, there are different kinds of
types!
The “type of a type” is called a kind in Haskell.
Proper types (or ground types or
monotypes) are described with kind *
(pronounced
“star”).
> :kind Int
> :k Int
> :k (Int, Int)
> :k Int -> Int
> :k Int -> Int -> Int
Type constructors (or type functions or *type operators) are described with arrow kinds.
> :k Maybe
> :k []
> :k (,)
> :k (,,)
> :k (->)
Polymorphic types, unconstrained or constrained, are proper types:
> :k a -> a
> <interactive>:1:1: error: Not in scope: type variable ‘a’
> :k forall a. a -> a
> :k forall a b. (a, b) -> a
> :k forall a. Num a -> a -> a
A “fully applied” type is a proper type or a type constructor applied to enough arguments to produce a proper type. Only proper types are “inhabited” by Haskell values.
Kinds do not have to be written in type class definitions, but it’s
helpful to think about them explicitly (like forall
quantifiers in polymorphic types). The KindSignatures
language extension, enabled by default in GHC2021
allows them to be written:
class Eq (t :: *) where
...
class Foldable (t :: * -> *) where
...
We do not need to worry about this much, but consider:
> :k Eq
Eq :: * -> Constraint
> :k Eq Int
Eq Int :: Constraint
Class Constraint
s are used to contrain polymorphic
types:
forall
a b …
.
(
Constraint_1, Constraint_2, …)
.
_t_1 -> … ->
_t_n
Improving and acting upon type error messages is an active area of research. With its focus on type classes — among other advanced features in Haskell — one particularly relevant paper is “Diagnosing Type Errors with Class”.
Imagine we wanted to define a datatype to hold three numbers, to be summed:
> data ThreeNums n = ThreeNums n n n
> sumThreeNums (ThreeNums x y z) = x + y + z
> :t sumThreeNums
sumThreeNums :: Num a => ThreeNums a -> a
There’s nothing stopping us from building non-numeric triples:
> ThreeNums () () ()
There is a deprecated language extension called DatatypeContexts
that allowed a datatype definition to come with a context of constraints
on its type variables, such as:
> data Num n => ThreeNums n = ThreeNums n n n
This feature has been removed…
> :set -XDatatypeContexts
...
-XDatatypeContexts is deprecated: It was widely considered a misfeature,
and has been removed from the Haskell language.
… because it turned out that datatype contexts were not sufficient to
forgo the constraints on sumThreeNums
; its type would still
be Num a => ThreeNums a -> a.
Interestingly, however, the recent paper “Partial Type Constructors (Or, Making Ad Hoc Datatypes Less Ad Hoc)” proposes a new design for datatype contexts that does make them useful, albeit at the cost of slightly changing the meaning of polymorphic types and their instantations.