Chapter 6: Typeclasses

6.1 Typeclasses

In this chapter we will

  • examine the typeclasses Eq, Ord, Enum and Show;

  • learn about type-defaulting typeclasses and typeclass inheritance;

  • look at some common but often implicit functions that create side effects.

6.2 What are typeclasses?

Type classes provide a way to introduce overloaded operations.

The main idea of a type class is to define a set of overloaded names that work for many types. Names can be either expressions, like minBound, or functions, like (+). Overloaded names have different term-level implementations for each type.

You define a type class in two parts, one part contains the overloaded names, and the other part supplies type-specific implementations of each name.

Class declarations

The class declaration introduces a new type class.

This consists of a header with the type class name, a body of overloaded expression names, and associated type signatures for each name in the body. You can also include fixity declarations here, for names that represent infix functions.

Syntactically, class declarations have the general form:

class constraints => Classname typevars where { class_method_names_and_type_signatures }

The constraints part here can be used to specify a superclass.

Here’s an example that defines a simplified version of the type class Num, which introduces the overloaded functions (+) and negate:

class Num a where
  (+)    :: a -> a -> a
  negate :: a -> a

This declaration may be read “a type a is an instance of the class Num if there are class methods (+) and negate, of the given types, defined on it.”

Instance declarations

An instance declaration defines the term-level implementation of each overloaded operation — called class methods — for the specified type.

The general form of an instance declaration is:

instance constraints => Classname Typename typevars where { class_method_definitions }

Here we implement Num for the concrete types Int and Float:

instance Num Int where
  x + y       =  addInt x y
  negate x    =  negateInt x

instance Num Float where
  x + y       =  addFloat x y
  negate x    =  negateFloat x

The first declaration above may be read “Int is an instance of the class Num as witnessed by these definitions (i.e. class methods) for (+) and negate.”

Type membership

A type is a member of a type class if it has a instance declaration which defines all minimally required methods of the class declaration.

How can we query which classes a type is a member of?

One way is to search for it on hoogle, which extracts documentation from the source code.

But what if you don’t have access to hoogle or the source code?

You can find membership information from the output of :info TypeName, like this:

·∾ :info Float
data Float = GHC.Types.F# GHC.Prim.Float# -- Defined in ‘GHC.Types’
instance Eq Float           -- Defined in ‘GHC.Classes’
instance Ord Float          -- Defined in ‘GHC.Classes’
instance Enum Float         -- Defined in ‘GHC.Float’
instance Floating Float     -- Defined in ‘GHC.Float’
instance Fractional Float   -- Defined in ‘GHC.Float’
instance Num Float          -- Defined in ‘GHC.Float’
instance Real Float         -- Defined in ‘GHC.Float’
instance RealFloat Float    -- Defined in ‘GHC.Float’
instance RealFrac Float     -- Defined in ‘GHC.Float’
instance Show Float         -- Defined in ‘GHC.Float’
instance Read Float         -- Defined in ‘GHC.Read’

The instance Num Float line shows us that there is an instance for Num. Because of this instance, Float is a member of Num.

Minimally required methods

Wait, there’s something new here. What is a minimally required class method? How can you tell which class methods are required?

Look no further than :info TypeClassName. (I’m showing the actual output for Num here, not the example version of Num that we used above.)

·∾ :info Num
class Num a where
  (+) :: a -> a -> a
  (-) :: a -> a -> a
  (*) :: a -> a -> a
  negate :: a -> a
  abs :: a -> a
  signum :: a -> a
  fromInteger :: Integer -> a
  {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}
        -- Defined in ‘GHC.Num’
instance Num Word     -- Defined in ‘GHC.Num’
instance Num Integer  -- Defined in ‘GHC.Num’
instance Num Int      -- Defined in ‘GHC.Num’
instance Num Float    -- Defined in ‘GHC.Float’
instance Num Double   -- Defined in ‘GHC.Float’

Syntax for specifying minimally required class methods

The {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-} syntax here is an example of a minimal pragma.

Pragmas are not a built-in language feature, but a facility provided by GHC. Minimal pragmas were introduced in GHC version 7.10, and are treated as a comments by earlier versions. You can find the docs on minimal here.

Minimal pragmas include a boolean expression that determine which class method definitions are required for membership.

Within these expressions the stroke | indicates a logical OR, and the comma , represents logical AND.

So, for membership in Num, either (-) or negate are required, but not both. Additionally (+), (*), abs, signum, and fromInteger are all required.

Default class methods

So, if some class methods are not required for membership, then what happens if you leave them undefined?

Either they won’t work (because they don’t exist), or more interestingly, there may be a default implementation of the method provided by the type class.

These default methods are usually created by composing the minimally required methods together in some way. (Though there are other possibilities.)

How do you supply your own default methods for a type class?

You include their term-level definition directly in the class declaration, like so:

class (Units a) => PID a where
  extendedGCD :: a -> a -> (a,a,a)
  extendedGCD = extendedEuclid divMod
  gcd :: a -> a -> a
  gcd x y = let (g,_,_) = extendedGCD x y in g

Derivable type classes

What’s better than not having to write class methods? Not having to write entire instance declarations!

Many of the default classes provide generic instances that can be derived automatically.

To do this you can add a deriving clause after a data declaration which will generate the instances.

For example, here’s a custom list type:

data List a = Cons a (List a) | Nil deriving (Eq, Ord, Show)

Haskell has just written the instances for Eq, Ord, and Show for you. But how do they work?

What Eq and Show does here is pretty obvious. Show turns any data constructor into a string, and the methods within Eq will compare the names of the data constructors.

How about Ord? There are a number of ways we could determine how things are ordered. The default implementation takes a simple approach.

When using a derived Ord instance, data constructors are considered to have a higher ordinal value the further right they are in the data declaration. So in this case Nil is ordered after Cons. Given our List definition above, for example:

·∾ (Cons 3 (Nil)) < Nil
True

Deriving does not work universally, however. So, how can you determine which type classes can be derived, and which cannot?

Here’s what #haskell had to say:

<justsomeguy> How can I determine which type classes can be derived,
              and which cannot? Do I just have to know, or can I
              query them somehow?

<dolio>       justsomeguy: They're listed in the Haskell
              report, and GHC has some extras turned on by extensions.

<dsal>        justsomeguy: I often just assume I can't derive
              classes and write them, but I've found GHC's been able
              to do some pretty fantastic deriving at times. There's
              lots of magic when you're ready for it.

<dsal>        Is there a particular class you want derived?

<justsomeguy> dsal: I can't think of a particular example
              right now; I was just reading about type classes in the
              book I'm learning from, and it piqued my interest.

<dsal>        justsomeguy: Very often, there's only one way to do
              it, so it makes sense that it can be derived.

The language report says:

Derived instances are possible only for classes known to the compiler: those defined in either the Prelude or a standard library.

The only classes in the Prelude for which derived instances are allowed are Eq, Ord, Enum, Bounded, Show, and Read

You will get a static error if you try to derive a type class that doesn’t support it. So I guess another way to figure it out is just to try to derive and see if you get an error.

Common type classes

Here are a few type classes you should know about. You’ll definitely encounter these, as they’re pretty common used.

Eq

Things that can be compared for equality. Can be derived – data constructor names are compared.

Ord

Things that can be ordered. Can be derived. It inherits from Eq. This gives you the standard relational operators.

Enum

Things that can be enumerated.

Show

Things that can be rendered into strings. Can be derived.

Read

This type class parses things into strings. Don’t use it.

Bounded

Introduces the methods minBound and maxBound, which define the minimal and maximal elements of the type. Can be derived – the first and last data constructors are used as bounds. For derivation, every constructor must be nullary or the type must have only one constructor.

6.3 Back to Bool

As you’ve just read, type classes have a hierarchy of sorts.

All Fractional numbers implement Num. All members of Ord must be members of Eq. All members of Enum must be members of Ord.

Num --> Fractional

Eq --> Ord --> Enum

6.4 Eq

Tests for equality are implemented with a type class called Eq.

Some languages bake equality into every object in the language. Since some datatypes don’t have a sensible notion of equality, Haskell doesn’t do this.

(Which languages do that? What are some examples of datatypes that don’t have a sensible notion of equality?)

Eq provides these methods:

·∾ :info Eq
class Eq a where
  (==) :: a -> a -> Bool
  (/=) :: a -> a -> Bool
  {-# MINIMAL (==) | (/=) #-}
        -- Defined in ‘GHC.Classes’
...

…over many types. Run :info Eq yourself to see the full output.

6.5 Writing type class instances

Here is an very simple example of an Eq instance for a custom datatype:

data Trivial = Trivial'

instance Eq Trivial where
  Trivial' == Trivial' = True

There is a single quote at the end of the data constructor to disambiguate it from the type constructor.

A more interesting example:

data DayOfWeek = Mon | Tue | Wed | Thu | Fri | Sat | Sun
data Date = Date DayOfWeek Int

instance Eq DayOfWeek where
  (==) Mon Mon = True
  (==) Tue Tue = True
  (==) Wed Wed = True
  (==) Thu Thu = True
  (==) Fri Fri = True
  (==) Sat Sat = True
  (==) Sun Sun = True
  (==) _   _   = False -- <-- This catch-all line is important!

instance Eq Date where
  (==) (Date weekday dayOfMonth) (Date weekday' dayOfMonth') =
       weekday == weekday' && dayOfMonth == dayOfMonth'

Note that the constructors won’t print in GHCi unless you define an instance of Show for them.

6.5.2 Partial functions

A partial function is a function which doesn’t terminate and yield a value for all given inputs. Conversely a total function terminates and is always defined for all inputs.

We should take care to avoid partial functions, since they can blow up at runtime. But it seems like it would be easy to overlook an input. So then, how can we ensure all our functions are total?

One way is to match unconditionally and then write some logic to deal with those inputs safely. (By, say, returning an identity value for that type.) Otherwise, you may want to use a wrapper type like Maybe to indicate the possibility of failure explicitly. Yet another possibility is to use a type with a smaller cardinality, and define cases for all possible inputs.

GHC flags can help you realize when functions are partial. If we turn on -Wall, we’ll get an error message if a function has cases left undefined. The error will even tell you which inputs your function needs cases for.

Certain historical parts of Prelude are full of partial functions. What about those?

Honestly that seems hard. Diehl has more to say on the matter.

To me it seems that Haskell has bad defaults in this area. I don’t think I’ll have the wherewithal to avoid them. Using an alternative prelude kind of sucks, too. Hopefully there is some tooling or a language extension to deal with this.

6.5.3 Sometimes we need to ask for more

Sometimes, in order to write our operations, we may need to use functions from other type classes. To make them visible, you can add a constraint to the instance declaration, like so:

--      constraint
--       vvvvvvv
instance Eq a => Eq (Identity a) where
  (==) (Identity v) (Identity v') = v == v'
--                                  ^^^^^^^
--                        needed for this comparison

6.5.4 Exercises: Eq Instances

A terminal recording, because why not?

Write the Eq instance for the datatype provided.

  1. data TisAnInteger = TisAn Integer (not a typo):

    instance Eq TisAnInteger where
       TisAn a == TisAn a' = a == a'
    
  2. data TwoIntegers = Two Integer Integer:

    instance Eq TwoIntegers where
       Two a a' == Two b b' = (a, a') == (b, b')
    
  3. data StringOrInt = TisAnInt Int | TisAString String:

    instance Eq StringOrInt where
        TisAnInt a   == TisAnInt a'    = a == a'
        TisAString b == TisAString b'  = b == b'
        TisAString _ == TisAnInt _     = False
        TisAnInt _   == TisAString _   = False
    
  4. data Pair a = Pair a a:

    instance (Eq a) => Eq (Pair a) where
        (==) (Pair a a') (Pair b b') = a == b && a' == b'
    
  5. data Tuple a b = Tuple a b:

    instance (Eq a, Eq b) => Eq (Tuple a b) where
        Tuple a b == Tuple a' b'  =  a == a' && b == b'
    
  6. data Which a = ThisOne a | ThatOne a:

    instance (Eq a) => Eq (Which a) where
        (==) (ThisOne a) (ThatOne a') = a == a'
    
  7. data EitherOr a b = Hello a | Goodbye b:

    instance (Eq a, Eq b) => Eq (EitherOr a b) where
      Hello a == Hello a' = a == a'
      Goodbye b == Goodbye b' == b == b'
      Hello _ == Goodbye _ = False
      Goodbye _ == Hello _ = False
    

6.6 Num

Num provides (+), (*), (-), negate, abs, signum and fromInteger. You can read the docs on Num here.

abs: return the absolute value.

signum: for positive numbers return 1, for negative numbers return -1, for zero return 0.

6.6.1 Integral

Integral provides quot, rem, div, mod, quotRem, divMod, toInteger. Docs on Integral are here

Descendant type classes can’t override methods of their ancestor type classes. Type classes respect their ancestors.

6.6.2 Exercises: Tuple Experiment

Query the types of divMod and quotRem. Make a guess as to what they do, and then test it in the repl.

Here is one possible implementation:

·∾ divMod'  = \x y -> (x `div` y, x `mod` y)

·∾ quotRem' = \x y -> (x `quot` y, x `quot` y)

I feel like I’m cheating since I’ve read the source code for these functions when taking notes for chapter 4.

6.6.3 Fractional

Fractional numbers, supporting real division. Fractional provides (/), recip, and fromRational. Docs for Fractional are here.

Here’s an example of how to use recip:

·∾ recip 3.4
0.29411764705882354

·∾ recip (3 / 4 :: Rational)
4 % 3

·∾ import Data.Ratio (%)
·∾ recip (3 % 4)
4 % 3

6.7 Type-defaulting type classes?

In some cases, there may be no clear concrete type for a constrained polymorphic type variable to resolve to. There may be multiple types that satisfy the class constraints. This type variable is said to be of an ambiguous type.

To prevent this situation, some type classes provide a default type to resolve expressions to.

In the expression 1 / 2, there are multiple types that could satisfy the Fractional class constraint that (/) creates.

But the result is of type Double, because somewhere in the source code for Prelude the default Fractional Double default declaration is provided.

You can use a different concrete type that has an instance of Fractional by providing a type annotation:

·∾ 1 / 2
0.5

·∾ 1 / 2 :: Float
0.5

·∾ 1 / 2 :: Double
0.5

·∾ 1 / 2 :: Rational
1 % 2

Here are some good defaults to be aware of:

default   Num          Integer
default   Real         Integer
default   Enum         Integer
default   Integral     Integer
default   Fractional   Double
default   RealFrac     Double
default   Floating     Double
default   RealFloat    Double

Types can be made more specific, but not more general or polymorphic.

6.8 Ord

Ord provides compare, (<), (>=), (>), (<=), max, and min. Docs for Ord.

Compare was a new one to me:

·∾ compare 3 3
EQ

·∾ compare 3 4
LT

·∾ compare 3 2
GT

Any time we ask GHCi to print a return value in our terminal, we are indirectly invoking print.

6.8.1 Ord instances

A few things to keep in mind about writing Ord instances; It’s wise to ensure that your Ord instances agree with your Eq instances. Also you want to define a sensible total order. (wtf?) You ensure this in part by covering all cases and not writing partial instances.

6.8.3 Exercises: Will They Work?

Look at the following code examples and try to decide if they will work, what result they will return if they do, and why or why not. Be sure to test them in your repl once you’ve decided on your answer.

  1. Example:

    max (length [1,2,3]) (length [8,9,10,11,12])
    

    Prediction: The answer should be 5 :: Int.

    Proof:

    ·∾ max (length [1..3]) (length [8..12])
    5
    ·∾ :type it
    it :: Int
    
  2. Example:

    compare (3 * 4) (3 * 5)
    

    Prediction: Ok, the result must be an Ordering (one of LT, EQ, GT), and (3*4) is less than (3*5), so the answer must be LT.

    Proof:

    ·∾ compare (3*4) (3*5)
    LT
    
  3. Example:

    compare "Julie" True
    

    Prediction: How can you meaningfully compare a String and a Bool? This must result in a type error. Let’s see.

    Proof:

    ·∾ compare "Julie" True
    <interactive>:31:17: error:
        • Couldn't match expected type ‘[Char]’ with actual type ‘Bool’
        • In the second argument of ‘compare’, namely ‘True’
          In the expression: compare "Julie" True
          In an equation for ‘it’: it = compare "Julie" True
    
  4. Examples:

    (5 + 3) > (3 + 6)
    

    Prediction: Eight is not greater than nine – False.

    Proof:

    ·∾ 5+3 > 3+6
    False
    

6.9 Enum

Enum provides succ, pred, toEnum, fromEnum, enumFrom, enumFromThen, enumFromTo, enumFromThenTo. Docs for Enum hereeeee mothafuckaaaa.

There’s a toEnum?

·∾ toEnum 8 :: Char
'\b'

·∾ fromEnum 'c'
99

6.10 Show

Show is not a serialization format. Docs for Show. A minimal implementation only requires show or showsPrec.

What the hell is showsPrec?

·∾ :type showsPrec
showsPrec :: Show a => Int -> a -> ShowS

·∾ :info ShowS
type ShowS = String -> String

·∾ showsPrec 8 "this" "that"
"\"this\"that"

6.14 Chapter Exercises

6.14.1 Multiple choice

  1. The Eq class

    1. includes all types in Haskell

    2. is the same as the Ord class

    3. makes equality tests possible

      ·∾ :doc Eq
       The 'Eq' class defines equality ('==') and inequality ('/=').
      
    4. only includes numeric types

  2. The type class Ord

    1. allows any two values to be compared

    2. is a subclass of Eq

      ·∾ :info Ord
      class Eq a => Ord a where
      
    3. is a superclass of Eq

    4. has no instance for Bool

  3. Suppose the type class Ord has an operator >. What is the type of >?

    1. Ord a => a -> a -> Bool

      ·∾ :type (>)
      (>) :: Ord a => a -> a -> Bool
      
    2. Ord a => Int -> Bool

    3. Ord a => a -> Char

    4. Ord a => Char -> [Char]

  4. In x = divMod 16 12

    1. the type of x is Integer

    2. the value of x is undecidable

    3. the type of x is a tuple

      ·∾ divMod 16 12
      (1,4)
      ·∾ :type it
      it :: Integral a => (a, a)
      
    4. x is equal to 12 / 16

  5. The type class Integral includes

    1. Int and Integer numbers

      ·∾ :info Integral
      class (Real a, Enum a) => Integral a where
                        . . .
      instance Integral Word     -- Defined in ‘GHC.Real’
      instance Integral Integer  -- Defined in ‘GHC.Real’
      instance Integral Int      -- Defined in ‘GHC.Real’
      
    2. integral, real, and fractional numbers

    3. Schrodinger’s cat

    4. only positive numbers

6.14.2 Does it typecheck?

First, a terminal recording.

  1. Does the following code typecheck?

    data Person = Person Bool
    
    printPerson :: Person -> IO ()
    printPerson person = putStrLn (show person)
    

    If not, why not?

    My prediction is that this won’t typecheck since Person doesn’t have an instance of Show.

    ·∾ :load One.hs
    [1 of 1] Compiling Main             ( One.hs, interpreted )
    
    One.hs:4:32: error:
        • No instance for (Show Person) arising from a use of ‘show’
        • In the first argument of ‘putStrLn’, namely ‘(show person)’
          In the expression: putStrLn (show person)
          In an equation for ‘printPerson’:
              printPerson person = putStrLn (show person)
      |
    4 | printPerson person = putStrLn (show person)
      |                                ^^^^^^^^^^^
    Failed, no modules loaded.
    
  2. Does the following typecheck?

    data Mood = Blah | Woot deriving Show
    
    settleDown x = if x == Woot then Blah else x
    

    If not, why not?

    The settleDown function uses (==) within its definition but Mood doesn’t have an instance of Eq, so this shouldn’t compile.

    ·∾ :load Two.hs
    [1 of 1] Compiling Main             ( Two.hs, interpreted )
    
    Two.hs:3:19: error:
        • No instance for (Eq Mood) arising from a use of ‘==’
        • In the expression: x == Woot
          In the expression: if x == Woot then Blah else x
          In an equation for ‘settleDown’:
              settleDown x = if x == Woot then Blah else x
      |
    3 | settleDown x = if x == Woot then Blah else x
      |                   ^^^^^^^^^
    Failed, no modules loaded.
    
  3. If you were able to get settleDown to typecheck:

    So, I just added deriving Eq to Mood in the module Two, and saved it as TwoV2.hs.

    data Mood = Blah | Woot deriving (Show, Eq)
    
    settleDown x = if x == Woot then Blah else x
    

    Now it typechecks.

    ·∾ :load TwoV2.hs
    [1 of 1] Compiling Main             ( TwoV2.hs, interpreted )
    Ok, one module loaded.
    
  1. What values are acceptable inputs to that function?

    The acceptable inputs to settleDown are Blah or Woot (members of Mood):

    ·∾ settleDown Blah
    Blah
    ·∾ settleDown Woot
    Blah
    
  2. What will happen if you try to run settleDown 9? Why?

    Running settleDown 9 should throw a type error… let’s try it:

    ·∾ settleDown 9
    <interactive>:19:12: error:
        • No instance for (Num Mood) arising from the literal ‘9’
        • In the first argument of ‘settleDown’, namely ‘9’
          In the expression: settleDown 9
          In an equation for ‘it’: it = settleDown 9
    
  3. What will happen if you try to run Blah > Woot? Why?

    Mood doesn’t support Num, and numeric literals are of type Num a => a by default, so unning Blah > Woot won’t work, since (>) comes from Ord.

    ·∾ Blah > Woot
    <interactive>:23:1: error:
        • No instance for (Ord Mood) arising from a use of ‘>’
        • In the expression: Blah > Woot
          In an equation for ‘it’: it = Blah > Woot
    

    This means Mood would need to derive Ord for that to work.

    ·∾ data Mood = Blah | Woot deriving (Eq, Ord, Show)
    

    Now it works.

    ·∾ Blah > Woot
    False
    
    ·∾ Blah < Woot
    True
    
  1. Does the following typecheck?

    type Subject = String
    type Verb    = String
    type Object  = String
    
    data Sentence = Sentence Subject Verb Object deriving (Eq, Show)
    
    s1 = Sentence "dogs" "drool"
    s2 = Sentence "Julie" "loves" "dogs"
    

    If not, why not?

    My guess was that it wouldn’t type check since Sentence isn’t fully applied in s1, but I was wrong. It just returns a partially applied function!

    ·∾ :load Four.hs
    [1 of 1] Compiling Main             ( Four.hs, interpreted )
    Ok, one module loaded.
    
    ·∾ :type s1
    s1 :: Object -> Sentence
    

    That was a silly mistake.

    Of course if we try to use it, we can’t show the resulting function:

    ·∾ s1
    <interactive>:36:1: error:
        • No instance for (Show (Object -> Sentence))
            arising from a use of ‘print’
            (maybe you haven't applied a function to enough arguments?)
        • In a stmt of an interactive GHCi command: print it
    

6.14.3 Given a datatype declaration, what can we do?

Given the following datatype definitions:

data Rocks = Rocks String deriving (Eq, Show)
data Yeah = Yeah Bool deriving (Eq, Show)
data Papu = Papu Rocks Yeah deriving (Eq, Show)

Which of the following will typecheck? For the ones that don’t typecheck, why don’t they?

  1. phew = Papu "chases" True

    This won’t type check, because it’s written incorrectly. The Papu data constructor requires arguments of types Rocks and Yeah, but is getting String and Bool arguments, instead. If I try, I get an error like this:

    ·∾ phew = Papu "chases" True
    <interactive>:2:13: error:
        • Couldn't match expected type ‘Rocks’ with actual type ‘[Char]’
        • In the first argument of ‘Papu’, namely ‘"chases"’
          In the expression: Papu "chases" True
          In an equation for ‘phew’: phew = Papu "chases" True
    <interactive>:2:22: error:
        • Couldn't match expected type ‘Yeah’ with actual type ‘Bool’
        • In the second argument of ‘Papu’, namely ‘True’
          In the expression: Papu "chases" True
          In an equation for ‘phew’: phew = Papu "chases" True
    

    But if I rewrite it to Papu (Rocks "chases") (Yeah True) and evaluate it, it works:

    ·∾ phew = Papu (Rocks "chases") (Yeah True)
    ·∾ phew
    Papu (Rocks "chases") (Yeah True)
    
  2. truth = Papu (Rocks "chomskydoz") (Yeah True) This typechecks!

  3. equalityForall :: Papu -> Papu -> Bool; equalityForall p p' = p == p' This also typechecks!

  4. comparePapus :: Papu -> Papu -> Bool; comparePapus p p' = p > p'

    This won’t work since Papu (as well as Rocks and Yeah) don’t have an instance of Ord, which provides (>):

    ·∾ :{
     ⋮ comparePapus :: Papu -> Papu -> Bool
     ⋮ comparePapus p p' = p > p'
     ⋮ :}
    <interactive>:5:21: error:
        • No instance for (Ord Papu) arising from a use of ‘>’
        • In the expression: p > p'
          In an equation for ‘comparePapus’: comparePapus p p' = p > p'
    

6.14.4 Match the types

Can you substitute the second type for the first? Test all your answers.

The book asks me to create files for each of these, load them, and then change the type. That’s a lot of unneeded saving and loading, though, so I decided to do everything in the repl, instead. If you don’t want to suffer through my typos, I suggest you download the *.cast file, and run asciinema cat on it to view the entire contents at once.

6.14.5 Type-Kwon-Do Two: Electric Typealoo

The idea with these exercises is that you’ll derive the implementation from the type information.

  1. chk :: Eq b => (a -> b) -> a -> b -> Bool
    chk f a b = (f  a) == b
    
    --   +-----------------------------------------------------+
    --   |                                                     |
    --   v                                                     |
    -- (==) :: Eq b =>                b   ->    b   ->   Bool  |
    --                                ^    ^    ^    ^    ^    |
    --                                |    |    |    |    |    |
    --                        +-------+    |    |    |    |    |
    --                       /             |    |    |    |    |
    --                      v              v    v    v    v    |
    -- chk :: Eq b => (a -> b)   ->   a   ->    b   ->   Bool  |
    --                ^^^^^^^^        ^                        |
    --                    |           |                        |
    --                    |           |                        |
    --                    +  +--------+                        |
    --                   /  /                                  |
    --                  /  /                                   |
    --                 v  v                                    |
    -- chk f a b =    (f  a) == b                              |
    --                        ^                                |
    --                        |                                |
    --                        +--------------------------------+
    
  2. arith  :: Num b => (a -> b) -> Integer -> a -> b
    arith f i a = (f  a) + (fromInteger i)
    
    --  +-------------------------------------------------+
    --  |                                                 |
    --  v                                                 |
    -- (+)    :: Num a =>   a      ->    a     ->     a   |
    --                      ^       ^    ^      ^     ^   |
    --                       \      |     \      \    |   |
    --                        \     |      +---+  \   |   |
    --                         \    |           \  \  |   |
    --                          v   v            v  v v   |
    -- arith  :: Num b => (a -> b) -> Integer -> a -> b   |
    --                     ^  ^          ^     ^          |
    --                     |  |          |     |          |
    --                     +  +          |     |          |
    --                      \/           +-----------+    |
    --                      /\                 |     |    |
    --                     v  v                v     v    |
    -- arith f i a =      (f  a)    +   (fromInteger i)   |
    --                              ^                     |
    --                              |                     |
    --                              +---------------------+