Lecture 17 — 2015-11-04

Type classes

This lecture is written in literate Haskell; you can download the raw source.

What’s happening? We’ll do more weeks of serious Haskell training, and then… cool stuff! Topics will definitely include automatic random testing and parser combinators. We’ll choose between a few others: concurrency, lenses/bidirectional programming, applications of PL in networks, or other topics (like static analysis). I’ll put out a poll when the time comes.

For the upcoming HW08, it will come in two parts. The first part is up now; I’ll post to Piazza when the second part is available. It will be due on 2015-11-15.

Type classes

Type classes are groups of functions associated with a type. Each type can have a single instance for each type class.

What are they for? In general, type classes characterize common interfaces and behaviors. For example:

  • printing (Show)
  • parsing (Read)
  • equality (Eq)
  • ordering (Ord)
  • representability in memory/disk (Storable)

Type classes get a lot of use in Haskell. More complex type classes include:

  • enumerability (Enum)
  • boundedness (Bounded)
  • being a structure that has foldl and foldr (Foldable)

Type classes are very much like classes in object-oriented languages, but there are important differences. Java, C++, and Python use classes to group code and data together, but Haskell separates data definitions from class definitions. Traditional OO “objects” are instances of classes, but Haskell’s “objects” are just values, while “instances” are implementations of interfaces.

Running examples

We used three types as our running examples. TVL is a three-valued logic; List a is lists containing a; OneOfThree a b c is like Either a b but has a third option.

module Lec17 where

data TVL = Yes | No | Maybe

data List a =
    Nil
  | Cons a (List a)

data OneOfThree a b c =
    L a
  | M b
  | R c

The Show type class

Haskell declares Show as follows:

class Show a where
  show :: a -> String

Here are some instances that use it.

instance Show TVL where
  show Yes = "Yes"
  show No = "No"
  show Maybe = "Maybe"

instance (Show a) => Show (List a) where
  show Nil         = "Nil"
  show (Cons x xs) = show x ++ "," ++ show xs
  
instance (Show a, Show b, Show c) => Show (OneOfThree a b c) where
  show (L a) = "L " ++ show a
  show (M b) = "M " ++ show b
  show (R c) = "R " ++ show c

When we want to use a type class function, we have to add a constraint to our type, as below. Pay careful attention to the difference between => and ->.

decision :: Show a => a -> String
decision result = "The committee answer was: " ++ show result

The Eq and Ord type classes

The Eq type class is how we establish equality for Haskell types; the Ord type class is used for ordering. They are (effectively) defined as follows:

class Eq a where
  (==) : a -> a -> Bool
  (/=) : a -> a -> Bool
  a /= b = not (a == b)
                    
data Ordering = LT | EQ | GT

class Eq a => Ord a where
  compare :: a -> a -> Ordering

There are a few things to note here. First, note that Eq provides a default implementation for (/=), which just negates (==). We could have separately defined:

(/=) :: Eq a => a -> a -> Bool
a /= b = not (a == b)

The Haskell library designers included (/=) in the Eq type class with a default implementation, instead. Why? This way, someone can create an instance of Eq that defines a more efficient verison of (/=) if their data structure permits it.

The Ord type class has an Eq type class constraint. You can’t define an instance for Ord a unless there’s already an instance for Eq a.

As a first cut for TVL, we might write:

instance Eq TVL where
  No    == No    = True
  Maybe == Maybe = True
  Yes   == Yes   = True
  _     == _     = False

instance Ord TVL where
  compare No    No    = EQ
  compare Yes   Yes   = EQ
  compare Maybe Maybe = EQ
  compare No    _     = LT
  compare Maybe No    = GT
  compare _     Yes   = LT

We can do better though—there’s some redundancy here. If we define a single function for comparison, we can use it for both instances.

cmpTVL :: TVL -> TVL -> Ordering
cmpTVL No No = EQ
cmpTVL Maybe Maybe = EQ
cmpTVL Yes Yes = EQ
cmpTVL No _ = LT
cmpTVL Maybe No = GT
cmpTVL _ Yes = LT

instance Eq TVL where
  a == b = cmpTVL a b == EQ

instance Ord TVL where
  compare = cmpTVL

newtype and its uses

We’ve seen the data keyword, which introduces data structures that will exist at runtime. We’ve also seen the type keyword, which introduces a type synonym, a convenient shorthand for the type checker. The newtype keyword has features of both. Like type, it's just a hint for the type checker, and will have no influence on the runtime; likedata`, it has constructors… but only a single one.

The most common way to use a newtype is as follows:

newtype Reversed a = Reversed { reversedValue :: a }

Note that (a) it takes a parameter, a, (b) the constructor has the same name as the type, and (c) we’ve used record notation to define an accessor, reversedValue.

So we have a constructor Reversed :: a -> Reversed a, an accessor or deconstructor reversedValiue :: Reversed a -> a… why bother? Recall that each type class can only have a single implementation of a given type class. Reversed a and a are different type, so we can give them different implementations. For example, here’s an implementation that reverses the ordering:

instance Show a => Show (Reversed a) where
  show (Reversed a) = "Reversed " ++ show a ++ ""

instance Eq a => Eq (Reversed a) where
  (Reversed a) == (Reversed b) = a == b

instance Ord a => Ord (Reversed a) where
  compare (Reversed a) (Reversed b) = 
    case compare a b of
      LT -> GT
      EQ -> EQ
      GT -> LT

Reversing the ordering is useful: this way sorting functions don’t need parameters to indicate direction, but can just follow the ordering of the type class.

Here’s another variation, where we suppress printing of values. This way we can print values but controllably hide the parts that might be too big or awkward to print on our console.

newtype Hidden a = Hidden { unhide :: a }

instance Show (Hidden a) where
  show _ = "Hidden _"

instance Eq a => Eq (Hidden a) where
  (Hidden a) == (Hidden b) = a == b

instance Ord a => Ord (Hidden a) where
  compare (Hidden a) (Hidden b) = compare a b

Kinds

Just as types classify terms, kinds classify types. Haskell has two kinds:

k ::= * | * -> *

First, *, pronounced “star”, is the kind of complete types, which classify terms. Int has kind *, as does Bool. The types [Int] and Maybe Bool have kind *, too. The types [] (read “list”) or Maybe have kind * -> *: they’re type constructors. There are no terms with the type [] or Maybe… terms only ever have types of kind *.

But: if you give [] a type, then you will have a complete type, as in [Int].

Next, the type of functions (->) has the kind * -> * -> *. If you give (->) two type parameters a and b, you will have a function type, a -> b. If you give it just one parameter, you will have a type constructor (a ->) of kind * -> *. It is unfortunately somewhat confusing that -> means two different things here: it’s both the function type and the ‘arrow’ kind. Rough stuff.

The type Mu we saw last week is even stranger:

newtype Mu f = Fold { unFold :: f (Mu f) }

Here, f has kind * -> *, and Mu f has kind *. So Mu itself has kind (* -> *) -> *. That is, Mu is a higher-kinded type: a type constructor that takes another type constructor.

Just as :t in GHCi will tell you the type of a term, :k will tell you the type of a kind. For example:

GHCi, version 7.10.2: http://www.haskell.org/ghc/  :? for help
Prelude> :k []
[] :: * -> *
Prelude>

Why do we care about kinds? In the next few classes, we’ll be looking at non-* kinded types in order to talk about groups of behavior. The next bit will be a first foray into types with interesting kinds.

Interface-like typeclasses

Finally, we looked at type classes that characterize behavior. The Listlike type class characterizes type constructors of kind * -> * that behave like lists.

class Listlike f where
  nil :: f a

  cons :: a -> f a -> f a

Note that f must have kind * -> *, because we apply it to the type parameter a, which must have kind *. Why? Because cons has type a -> f a -> f a, and (->) has kind * -> * -> * and is applied to a.

  openCons :: f a -> Maybe (a,f a)

  hd :: f a -> Maybe a
  hd l = 
    case openCons l of 
      Nothing -> Nothing
      Just (x,_) -> Just x

  tl :: f a -> Maybe (f a)
  tl l = 
    case openCons l of 
      Nothing -> Nothing
      Just (_,xs) -> Just xs

  isNil :: f a -> Bool
  isNil l =
    case openCons l of
      Nothing -> True
      Just _ -> False

  foldRight :: (a -> b -> b) -> b -> f a -> b

  foldLeft :: (b -> a -> b) -> b -> f a -> b

  each :: (a -> b) -> f a -> f b
  each f = foldRight (cons . f) nil

  append :: f a -> f a -> f a
  append xs ys = foldRight cons ys xs

We can show that the list type constructor, [], which has kind * -> *, is an instance of the Listlike class. On an intuitive level, this should be no surprise: lists are indeed listlike.

instance Listlike [] where
  nil = []
  cons = (:)

  openCons [] = Nothing
  openCons (x:xs) = Just (x,xs)

  tl [] = Nothing
  tl (_:xs) = Just xs

  isNil = null
  foldRight = foldr
  foldLeft = foldl
  -- just take each and append as the usual

We also defined a union-tree as an alternate list representation.

data UnionTree a =
    Empty
  | Singleton a
  | Union { left :: (UnionTree a), right :: (UnionTree a) }
  deriving Show

instance Listlike UnionTree where
  nil = Empty

  cons x Empty = Singleton x
  cons x xs = Union (Singleton x) xs

  openCons Empty = Nothing
  openCons (Singleton a) = Just (a,Empty)
  openCons (Union l r)   = 
    case openCons l of
      Nothing -> openCons r
      Just (x,l') -> Just (x,Union l' r)

  isNil Empty = True
  isNil (Singleton _) = False
  isNil (Union l r) = isNil l && isNil r

  foldRight f v l =
    case openCons l of  
      Nothing -> v
      Just (x,xs) -> f x (foldRight f v xs)

  foldLeft f v l =
    case openCons l of
      Nothing -> v
      Just (x,xs) -> foldLeft f (f v x) xs

  each f Empty = Empty
  each f (Singleton a) = Singleton $ f a
  each f (Union l r) = Union (each f l) (each f r)

  append = Union

Note that we overload append to use a much more efficient implementation—O(1) compared to O(n)!

asList :: Listlike f => f a -> [a]
asList = foldRight (:) []

concat :: Listlike f => f (f a) -> f a
concat = foldRight append nil

Equality for functions on finite domains

Finally, we defined a notion of equality for function on finite domains.

instance (Eq a, Bounded a, Enum a, Eq b) => Eq (a -> b) where
  f1 == f2 = 
    let checkAt x = f1 x == f2 x in
    and $ map checkAt $ enumFromTo minBound maxBound

Haskell could do this in its standard library, but doesn’t… why not? Why might this be a bad idea?