Type Classes

Type Classes

When you first learned about types in Haskell, you learned about how to use parametric polymorphism to create functions that implement the same algorithm regardless of the type of value they are working on. Although parametric polymorphism is a powerful tool, you will often find that you need to provide different implementations of a function based on the input type, while still remaining polymorphic. Type classes are Haskell’s approach to providing this form of ad-hoc polymorphism.

You’ll learn how to write polymorphic functions that depend on a specific implementation for a given type. You’ll also learn how to create your own type classes, and to use a GHC language extension that lets you more explicitly tell the compiler how to decide which behavior to use for a polymorphic function call.

You’ll be able to create new type classes that describe the behavior of types, and implement the type classes for types that you define.

In the next several chapters you’ll learn about some key concepts in Haskell like how to make use of IO and how to use things like Monads and Functors. Understanding how these things work requires a good understanding of typeclasses.

Writing Typeclass Representing Emptiness

Imagine that we wanted to create a typeclass that represents things that can be “empty” for some definition of empty that will depend on the particular type. In this exercise we’ll call the typeclass Nullable and give it two functions:

  • isNull should return True if a value is “empty”
  • null should return an “empty” value
module Nullable where
import Prelude hiding (null)

class Nullable a where
  isNull :: a -> Bool
  null :: a

Create instances of this typeclass for:

  1. Any Maybe a where a is Nullable
  2. Any tuple, (a,b) where a and b are Nullable
  3. Any list type

Hints

Click to reveal

There’s more than one way to create an instance for Maybe a. You can pick whichever definition you like.

Click to reveal

Remember: for a type like Maybe a if you want to use null or isNull for the type a you’ll need to ensure that a has a Nullable instance.

Click to reveal

In the instance that you define for Maybe a you can ensure a has a Nullable instance like this:

instance Nullable a => Nullable (Maybe a) where
  -- the body of the instance goes here

Solution

Click to reveal

The first part of our exercise presents us with a problem that has more than one solution. We’re asked to write an instance of Nullable for a Maybe value. One obvious solution to this problem would be to treat Nothing as a null value, and a Just value as non-null:

instance Nullable (Maybe a) where
  isNull Nothing = True
  isNull _ = False

  null = Nothing

Technically this solution solves the question as asked. Although we don’t require that a be nullable, there’s nothing to stop the instance from working in cases where it is nullable. Still, this isn’t really in the spirit of the question, so let’s dig in a bit more. Let’s start by adding the constraint, then we can figure out what to do with it:

instance Nullable a => Nullable (Maybe a) where
  isNull Nothing = True
  isNull _ = False

  null = Nothing

Now that we’ve added the constraint, we can use isNull and null for a. One way we can take advantage of this is by being more permissive about what we consider a null value. Let’s take another pass at this implementation:

instance Nullable a => Nullable (Maybe a) where
  isNull Nothing = True
  isNull (Just a) = isNull a

  null = Nothing

This version of our instance lets us account for the fact that even if we have a Just value, it might be something that’s still empty.

Click to reveal

The next part of the exercise asks us to write a Nullable instance for a tuple. Unlike the Maybe instance we wrote earlier, tuple’s don’t have any default value that naturally maps to being empty. Instead, we’ll need to fall back to the definitions of both a and b. Let’s take a look:

instance (Nullable a, Nullable b) => Nullable (a,b) where
  isNull (a,b) = isNull a && isNull b
  null = (null, null)

In this example, we’re considering a tuple to be null if both elements of the tuple are null. This tells us both how to create a new null tuple, and how to test to see if an existing tuple is null.

Click to reveal

The final part of this exercise asks us to write an instance that will work for any list type. This problem is complementary to the instance we wrote for Maybe. Although we could have written an instance for Maybe a that didn’t require a to be nullable, we opted to add that requirement so that we could identify cases where we had a Just null value. For our list instance, we are asked to create a version that works for any a whether it’s Nullable or not. Let’s take a look:

instance Nullable [a] where
  isNull [] = True
  isNull _ = False

  null = []

Since we have no guarantee that a has a Nullable instance, we can’t consider its value when we’re thinking about what might constitute a null list. With only the shape of the list to consider, the only sensible choice is to make null and empty list. Thanks to pattern matching, we can write a version of isNull that doesn’t require an Eq instance for a.

Adding a Default Null Test

Add a new Eq constraint to the definition of Nullable:

class Eq a => Nullable a

With this change in place, create a default implementation of isNull.

Hints

Click to reveal

Remember that your default implementation can refer to other functions defined by the typeclass.

Click to reveal

With the Eq constraint, you can compare values of type a using (==).

Click to reveal

A value is null if it’s equal to null.

Solution

Click to reveal

This exercise asks us to add an Eq constraint to Nullable and use that to allow us to write a default definition of isNull. This is a pretty small change on it’s own:

class Eq a => Nullable a where
  isNull :: a -> Bool
  isNull = (== null)

  null :: a

Unfortunately, changing this definition of our class to add the extra constraint means that we also need to update most of our instances as well:

module EffectiveHaskell.Exercises.Chapter6.DefaultNull where
import Prelude hiding (null)

class Eq a => Nullable a where
  isNull :: a -> Bool
  isNull = (== null)
  null :: a

instance Nullable a => Nullable (Maybe a) where
  isNull Nothing = True
  isNull (Just a) = isNull a
  null = Nothing

instance (Nullable a, Nullable b) => Nullable (a,b) where
  isNull (a,b) = isNull a && isNull b
  null = (null, null)

instance Eq a => Nullable [a] where
  isNull [] = True
  isNull _ = False
  null = []

The extra constraint doesn’t impact how we’re writing our instances, but it does mean that we won’t be able to use the instances in some cases. For example, before adding the constraint we could use isNull to see whether or not we had an empty list of functions, but functions don’t have an Eq instance, so we won’t be able to do that anymore. In some cases the additional restriction would be fine, but it limits the ways that people can use our typeclasses, and doing so unnecessarily can make our code less reusable. Let’s look at a couple of other approaches we could have used that offer more flexibility.

Defaulting with a Helper

In this example, our motivation for adding an Eq constraint to the definition of Nullable was so that we could provide a default implementation of isNull. There’s a common alternative that gives us almost as much ease-of-use with a lot more flexibility: helper functions. Let’s start looking at how they work by creating a new function called isNullHelper:

isNullHelper :: (Eq a, Nullable a) => a -> Bool
isNullHelper = (== null)

This function puts the same constraints on a that we would have in the default isNull implementation we wrote, but it lives outside of the type class. That means that we can drop the constraint at the type class level, but make use of it for particular instances when it makes sense. Let’s look at a concrete example. First, we’ll return to our original definition of Nullable:

class Nullable a where
  isNull :: a -> Bool
  null :: a

Next, let’s take a look at how we might use our new helper function. We’ll start by revisiting our Nullable instance for [a]. In our original definition of isNull for lists, we didn’t look at the values inside of the list at all- only whether the list itself was empty. That makes the definition of isNull for lists a good candidate to use the isNullHelper function we’ve just added. Unfortunately, we can only test lists for equality if we can test the elements inside the lists for equality, so we’ll still need our Eq constraint:

instance Eq a => Nullable [a] where
  isNull = isNullHelper
  null = []

As you can see, although we no longer have a default definition for isNull, we’re able to use the helper function so that it’s very easy to write a new instance. This also gives us the flexibility to define instances that work differently and don’t need an equality constraint. For example, let’s take a look at the instance for Maybe:

instance Nullable a => Nullable (Maybe a) where
  isNull Nothing = True
  isNull (Just a) = isNull a
  null = Nothing

In this example we’re not actually testing for equality at all. If we do have a value, we defer to whatever definition of isNull is provided by a.

This approach gives us some flexibility around the constraints on instances of our typeclass, while still saving someone work in the common case that they can rely on equality testing. It’s not without drawbacks though. The main drawback is that someone using our module might be confused and try to call isNullHelper directly, even when it’s behavior would differ from the definition of isNull. That could be a source of bugs. There’s another option that we can use, but it requires that we add a new language extension.

Using DefaultSignatures

The DefaultSignatures extension gives us another way to solve the problem. In this chapter you saw how this extension allows you to add a default value to a typeclass that has narrower constraints than the type defined by the class. In this case, we can use the extension to provide a default implementation of isNull only when the Nullable value has an Eq instance. Let’s take a look:

{-# LANGUAGE DefaultSignatures #-}
module EffectiveHaskell.Exercises.Chapter6.DefaultSignaturesNull where
import Prelude hiding (null)

class Nullable a where
  isNull :: a -> Bool

  default isNull :: Eq a => a -> Bool
  isNull = (== null)
  null :: a

With DefaultSignatures enabled we’re able to add a default definition of isNull that works by comparing the input value to null, just like isNullHelper from our earlier example. Like our other examples, we can still create instances that provide a definition of isNull. If the type we’re defining a Nullable instance for doesn’t have an instance of Eq we’re required to provide on:

instance (Nullable a, Nullable b) => Nullable (a,b) where
  isNull (a,b) = isNull a && isNull b
  null = (null, null)

If, on the other hand, we do have an Eq constraint then we’re free to provide our own definition of isNull:

instance (Eq a, Nullable a) => Nullable (Maybe a) where
  isNull Nothing = True
  isNull (Just a) = isNull a
  null = Nothing

Alternatively, we can use the default version:

instance Eq a => Nullable [a] where
  null = []

In the last exercise you saw that we were able to avoid having an Eq instance when we defined isNull for lists thanks to pattern matching. To use the default instance, we need to add it. This is a good example of the tradeoffs that you’ll want to think about when defining default instances. Ideally, if you’re using DefaultSignatures to add constraints to the default implementation of a function, you’ll be adding common constraints that well come “for free” for at least some implementations.

Deriving Nullable

In the first exercise in this chapter you should have created an instance of Nullable for Maybe and list values. There are a few ways that you could have approached writing these instances, but let’s look at some reasonable definitions you might have used:

module DerivingNullable where
import Prelude hiding (null)
import qualified Prelude (null)

class Nullable a where
  isNull :: a -> Bool
  null :: a

instance Nullable [a] where
  isNull = Prelude.null
  null = []

instance Nullable (Maybe a) where
  isNull Nothing = True
  isNull _ = False
  null = Nothing

These instances use a fairly intuitive definition of what should be considered null: empty lists are null, as are Nothing values. What if we have an optional list though?

λ isNull Nothing
True
λ isNull []
True
λ isNull (Just [])
False

In this case it’s not clear whether Just [] should be considered a null value or not, it depends entirely on the program we are writing. You can even imagine that we might want different behavior in different parts of the same program.

In this exercise, try to create an API so that a user can make use of deriving via to create Nullable instances of their own types. A user should be able to decide whether Just [] should be considered a null value or not by selecting which type they derive their instance from.

Hints

Click to reveal

If you’re having trouble imagining how an API like this might be used, imagine that you’re working with some text data that will be provided by user and you need to decide whether a user provided a value or not. In some cases, an empty string might be a valid input when the user doesn’t have anything more meaningful to input. In other cases, you might want to ensure that they’ve provided some actual data.

For example, imagine that you wanted to define two types: OptionalString and OptionalNonEmptyString. You might start by defining them like this:

newtype OptionalString = OptionalString { getString :: Maybe String }
  deriving stock (Eq, Show)

newtype OptionalNonEmptyString = OptionalNonEmptyString { getNonEmptyString :: Maybe String }
  deriving stock (Eq, Show)

Instead of writing instances manually, think about how you could provide a way for users to use deriving via with these types.

Click to reveal

You’ll need to create a newtype for each of the behaviors you want to make available with deriving via, along with a Nullable instance for each.

Click to reveal

Trying creating two types with Nullable instances. First, create a type named BasicNullable that should have isNull return True only if there’s a missing value. Next, create one called TransitiveNullable with a definition of isNull that will return also true if the inner value is null.

Solution

Click to reveal

We’ll start our solution by creating a new module and re-defining Nullable. We’ll go ahead and add the DerivingVia extension too, since we’re planning to use it later in this exercise:

{-# LANGUAGE DerivingVia #-}
module EffectiveHaskell.Exercises.Chapter6.DerivingNullable where
import Prelude hiding (null)

class Nullable a where
  isNull :: a -> Bool
  null :: a

Next, let’s define some types that represent the different “templates” that we might want to use with deriving via to get our behaviors. If you looked at the hints earlier, you’ll know that we’re going to create two types: BasicNullable and TransitiveNullable. Let’s start with BasicNullable first.

We want our BasicNullable type to represent optional values that are only considered null if they are truly missing a value. Let’s start by creating the type. We’ll also add a Show instance to make things easier when we want to test the code in ghci later:

newtype BasicNullable a = BasicNullable (Maybe a)
  deriving stock Show

We also need to create a Nullable instance for BasicNullable. For this basic definition of Nullable, we’ll consider a Nothing value to be null, and anything else will be non-null:

instance Nullable (BasicNullable a) where
  isNull (BasicNullable Nothing) = True
  isNull _ = False
  null = BasicNullable Nothing

Next, let’s do the same thing for TransitiveNullable. Unlike BasicNullable, this instance will only consider something non-null if it contains a non-null value:

newtype TransitiveNullable a = TransitiveNullable (Maybe a)
  deriving stock Show

instance Nullable a => Nullable (TransitiveNullable a) where
  isNull (TransitiveNullable Nothing) = True
  isNull (TransitiveNullable (Just a)) = isNull a
  null = TransitiveNullable Nothing

Even though we created BasicNullable an TransitiveNullable so that we could use them with deriving via, they are still valid ordinary types and we can test their behavior in ghci. Let’s run a few tests to make sure everything’s working as we expect. Let’s start by testing out the isNull instance of BasicNullable:

λ isNull $ BasicNullable Nothing
True

λ isNull $ BasicNullable (Just "hello")
False

We can see from these examples that isNull appears to be working for the obvious cases, but we should still test that isNull correctly returns False when we have Just some empty value. One way we can test this is to nest some BasicNullable values:

λ isNull $ BasicNullable (Just $ BasicNullable Nothing)
False

This is a little weird though. Let’s add an instance of Nullable for lists so that we have some values to test with:

instance Nullable [a] where
  isNull [] = True
  isNull _ = False
  null = []

Using these two instances, we can see that while [] is null, BasicNullable (Just []) continues to be treated as non-null:

λ isNull []
True

λ isNull [1,2,3]
False

λ isNull $ BasicNullable (Just [])
False

Now that we’ve figured out BasicNullable let’s move on to TransitiveNullable. Just like before, we’ll start by creating a new type:

newtype TransitiveNullable a = TransitiveNullable (Maybe a)
  deriving stock Show

We’ll also create a new instance of Nullable. Unlike our earlier instance, we’ll need to make sure that whatever type we’re holding is also Nullable since we’ll need to check to see if the values we’re working with are null or not:

instance Nullable a => Nullable (TransitiveNullable a) where
  isNull (TransitiveNullable Nothing) = True
  isNull (TransitiveNullable (Just a)) = isNull a
  null = TransitiveNullable Nothing

Like before, we can load this up into ghci to test it:

λ isNull $ TransitiveNullable (Just "hello")
False

Unfortunately, if we try to test the empty case of TransitiveNullable the same way we tested BasicNullable we’ll get an error:

λ isNull $ TransitiveNullable Nothing
<interactive>:20:1: error:
    • Ambiguous type variable ‘a0’ arising from a use of ‘isNull’
      prevents the constraint ‘(Nullable a0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘a0’ should be.
      These potential instances exist:
        instance Nullable (BasicNullable a)
          -- Defined at EffectiveHaskell/Exercises/Chapter6/DerivingNullable.hs:12:10
        instance Nullable OptionalNonEmptyString
          -- Defined at EffectiveHaskell/Exercises/Chapter6/DerivingNullable.hs:35:12
        instance Nullable OptionalString
          -- Defined at EffectiveHaskell/Exercises/Chapter6/DerivingNullable.hs:31:12
        ...plus two others
        (use -fprint-potential-instances to see them all)
    • In the first argument of ‘($)’, namely ‘isNull’
      In the expression: isNull $ TransitiveNullable Nothing
      In an equation for ‘it’: it = isNull $ TransitiveNullable Nothing

The problem here is the definition of Nullable we defined for TransitiveNullable a relies on the definition of Nullable for a. When we use a value like Just "hello" the compiler can infer the type of a must be String. When we use Nothing we’re not giving the compiler enough information to figure out what a should be, so it can’t pick a Nullable instance. We can help it out by adding a visible type application to TransitiveNullable to tell it what type to use for a:

λ isNull $ TransitiveNullable @String Nothing
True

Alternatively, you can add a type annotation to Nothing:

λ isNull $ TransitiveNullable (Nothing :: Maybe String)
True

Now that we’ve covered both obviously null and obviously non-null cases, let’s take a look at an example where TransitiveNullable and BasicNullable should differ: A value that contains an empty list. Let’s test them side-by-side:

λ isNull $ TransitiveNullable (Just [])
True

λ isNull $ BasicNullable (Just [])
False

As expected, the TransitiveNullable instance considers an empty list to be null, while the BasicNullable instance doesn’t.

Now that we’ve created two different types that have our desired Nullable behaviors, how can we use them with deriving via? To start with, let’s imagine that we’re dealing with some text data. As a specific example, imagine that you’re processing some data submited by a user, and you want to ensure that you’re getting valid data. In some cases, you might have data that could be empty, while in other cases you want to ensure that there’s actual data. For example, a user signing up for a service might be required to enter a password, but the “how did you hear about us” field could be left empty.

We’ll represent these two types of data with the types OptionalString and OptionalNonEmptyString:

newtype OptionalString = OptionalString { getString :: Maybe String }
  deriving stock Show

newtype OptionalNonEmptyString = OptionalNonEmptyString { getNonEmptyString :: Maybe String }
  deriving stock Show

You can imagine that we could write Nullable instances for these two types that are identical to the BasicNullable and TransitiveNullable types we just created, but thanks to deriving via we don’t need to. Instead, we can add the DerivingVia extension, and use it to select an instance:

newtype OptionalString = OptionalString { getString :: Maybe String }
  deriving stock Show
  deriving Nullable via BasicNullable String

newtype OptionalNonEmptyString = OptionalNonEmptyString { getNonEmptyString :: Maybe String }
  deriving stock Show
  deriving Nullable via TransitiveNullable String

Let’s load this code up into ghci and check that it behaves like we’d expect. Starting with OptionalString:

λ isNull $ OptionalString (Just "hello")
False

λ isNull $ OptionalString (Just "")
False

λ isNull $ OptionalString Nothing
True

As you can see, since we derived the Nullable instance for OptionalString from BasicNullable, the behavior is the same. Next, let’s look at OptionalNonEmptyString:

λ isNull $ OptionalNonEmptyString (Just "hello")
False

λ isNull $ OptionalNonEmptyString (Just "")
True

λ isNull $ OptionalNonEmptyString Nothing
True

Success! It appears that OptionalNonEmptyString is now using the same behavior as TransitiveNullable.

You might have noticed that, in practice, using deriving via in this case didn’t buy us much- it seems as though we’ve actually done more work by creating the generic types and then deriving our instances from them instead of creating instances for OptionalString and OptionalNonEmptyString directly. In this case it’s true, but as soon as we need a second, third, or fourth type that would have the same boilerplate implementation of a type class, then we’ll have saved ourselves some effort. Realistically, it’s not always clear when you’ll want to reuse some definition of a typeclass, so you might find that instead of creating the generic reusable types to start with, you recognize that you have the same definition in multiple places and instead factor those out into a common definition that you can use with deriving via.