Typeclasses
maxInt :: Int -> Int -> Int
maxInt x y = if x > y then x else ymaxChar :: Char -> Char -> Char
maxChar x y = if x > y then x else yWhy not just? π€
max :: a -> a -> a
max x y = if x > y then x else yπ©βπ¬ The above type signature of max implies that the function can work with any type. But we don't know anything about the type!
Compare:
take :: Int -> [a] -> [a]π Parametric polymorphism β same behavior for different types.
π Ad-hoc polymorphism β different behavior for different types.
Examples
π Parametric
π€Έ Ad-hoc
  βββ "class" keyword
  β
  β      βββ Typeclass name
  β      β
  β      β    βββ Type variable
  β      β    β
  β      β    β   βββ "where" keyword     
class Display a where
    display :: a -> String
      β          β
      β          ββ method type signature
      β
  method nameclass Display a where
    display :: a -> Stringinstance Display Bool where
    display False = "false"
    display True  = "true"greet :: Display a => a -> String
greet val = "Hello, " ++ display valdisplayBoth :: (Display a, Display b) => a -> b -> String
displayBoth a b = display a ++ " and " ++ display binstance Display Char where
    display c = [c]ghci> :t greet
greet :: Display a => a -> String
ghci> :t display
display :: Display a => a -> String
ghci> greet 'A'
"Hello, A"
ghci> displayBoth 'x' True
"x and true"data
class
instance
What is stored inside?
What we can do with this?
How we implement this behavior for that data?
class Display a where
    {-# MINIMAL display #-}
    display :: a -> String
    
    displayList :: [a] -> String
    displayList l =
        "[" ++ intercalate ", " (map display l) ++ "]"π More performant methods
π¦ Different behaviour
π Big typeclasses
π° Small typeclasses
π Smaller possibility of error
π¦ Easier to write instances
displayList :: Display a => [a] -> Stringπ¦ΈββοΈ Typeclasses take power, not grant.
ghci> displayList [True, False, True]
"[true, false, true]"
ghci> displayList "Hello!"
"[H, e, l, l, o, !]"ghci> displayList [True, 'X']
<interactive>:31:20: error:
    β’ Couldn't match expected type βBoolβ with actual type βCharβ
    β’ In the expression: 'X'How to read Haskell code?
π« displayList takes a list of values that can be converted to String.
π displayList takes a list of values of the same type and this type can be converted to String.
{-# LANGUAGE InstanceSigs #-}
module Display where
class Display a where
    display :: a -> String
    
instance Display Char where
    display :: Char -> String  -- π needed for this
    display c = [c]βΉοΈ GHC has features not enabled by default. Use {-# LANGUAGE #-} pragma at the top of your file to enable them.
Eq β check for equality
Ord β compare
Show β convert to String
Read β parse from String
Bounded β has minimal and maximal value
Enum β is an enumeration
Num β a number (addition, multiplication, subtraction, etc.)
ghci> :info Bounded
type Bounded :: * -> Constraint
class Bounded a where
  minBound :: a
  maxBound :: a
  {-# MINIMAL minBound, maxBound #-}
  	-- Defined in βGHC.Enumβ
instance Bounded Word -- Defined in βGHC.Enumβ
instance Bounded Int -- Defined in βGHC.Enumβ
...class Eq a where
    {-# MINIMAL (==) | (/=) #-}
    
    (==), (/=) :: a -> a -> Bool
    
    x /= y = not (x == y)
    x == y = not (x /= y)ghci> :t (==)
(==) :: Eq a => a -> a -> Bool
ghci> 'x' == 'F'
False
ghci> [1..5] /= reverse [5, 4, 3, 2, 1]
False
ghci> "" == []
Trueclass (Eq a) => Ord a where
    {-# MINIMAL compare | (<=) #-}
    compare              :: a -> a -> Ordering
    (<), (<=), (>), (>=) :: a -> a -> Bool
    max, min             :: a -> a -> a
    compare x y = if x == y then EQ
                  else if x <= y then LT
                  else GT
    ...data Ordering
    = LT  -- ^ Less
    | EQ  -- ^ Equal
    | GT  -- ^ Greatersort   :: Ord a => [a] -> [a]
sortBy :: (a -> a -> Ordering) -> [a] -> [a]class Num a where
    (+), (-), (*)       :: a -> a -> a
    negate              :: a -> a
    abs                 :: a -> a
    signum              :: a -> a
    fromInteger         :: Integer -> a
    x - y               = x + negate y
    negate x            = 0 - xghci> :t 42
42 :: Num p => pghci> 42
42π¬ Syntax sugar everywhere
ghci> fromInteger (42 :: Integer)
42ghci> check x y = x + y < x * yghci> :t check
check :: (Ord a, Num a) => a -> a -> Booldata Color
    = Red
    | Green
    | Blue
    deriving (Eq, Ord, Show, Read, Enum, Bounded, Ix)βοΈ GHC can automatically generate instances for you*
data Bit
    = Zero
    | One
    deriving (Num)<interactive>:5:15: error:
    β’ Can't make a derived instance of βNum Bitβ:
        βNumβ is not a stock derivable class (Eq, Show, etc.)
        Try enabling DeriveAnyClass
    β’ In the data declaration for βBitβ{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Size = Size
    { unSize :: Int
    } deriving ( Show
               , Read
               , Eq
               , Ord
               , Enum
               , Bounded
               , Ix
               , Num
               , Integral
               , Real
               , Bits
               , FiniteBits
               )βοΈ For newtype, you can derive any typeclass of the original type
class Semigroup a where
    (<>) :: a -> a -> aβοΈ Typeclass for smashing things together
Equivalent typeclass
class Appendable a where
    append :: a -> a -> ainstance Semigroup [a] where
    (<>) = (++)βΉοΈ Standard instances
π©βπ¬ But with laws! Associativity:
instance Semigroup Bool where
    (<>) = ??? -- && or || , which one to choose ????newtype Any = Any { getAny :: Bool }
newtype All = All { getAll :: Bool }βοΈ newtypes help implement different behaviour for the same type
instance Semigroup Any where
    Any x <> Any y = Any (x || y)instance Semigroup All where
    All x <> All y = All (x && y)ghci> Any False <> Any True
Any {getAny = True}
ghci> All False <> All True
All {getAll = False}
ghci> Any False <> All True
<interactive>:4:14: error:
    β’ Couldn't match expected type βAnyβ with actual type βAllβ
    β’ In the second argument of β(<>)β, namely βAll Trueβnewtype Any =
    Any { getAny :: Bool }newtype All =
    All { getAll :: Bool }newtype Sum a =
    Sum { getSum :: a }newtype Product a =
    Product { getProduct :: a }newtype First a =
    First { getFirst :: a }newtype Last a =
    Last { getLast :: a }Ordering
Maybe a
[a]
(a, b)
...Booleans with ||
Booleans with &&
Numbers with +
Numbers with *
Anything with taking first
Anything with taking last
newtype Sub a = Sub { getSub :: a }
instance Num a => Semigroup (Sub a) where
    Sub x <> Sub y = Sub (x - y)π’ Numbers with subtraction (-)
π« Associativity doesn't hold!
class Semigroup a => Monoid a where
    mempty :: aβοΈ Smashing with a neutral element
instance Monoid [a] where
    mempty = []Standard instances
π©βπ¬ Laws again!
instance Monoid Any where
    mempty = Any FalseRight identity
Left identity
instance Monoid All where
    mempty = All Trueinstance Num a => Monoid (Sum a) where
    mempty = Sum 0instance Num a => Monoid (Product a) where
    mempty = Product 1newtype First a = First { getFirst :: a }βοΈ Not every data type has a neutral element for <>
instance Semigroup (First a) where
    a <> _ = ainstance Monoid (First a) where
    mempty = ???We need: mempty <> x β‘ x
base has two First data types
newtype First a =
    First { getFirst :: a }newtype First a =
    First { getFirst :: Maybe a }Data.Semigroup
Data.Monoid
π Kind β a type of a type.
ghci> :k Int
Int :: *
ghci> :k String
String :: *ghci> :k Maybe
Maybe :: * -> *
ghci> :k []
[] :: * -> *
ghci> :k Either
Either :: * -> * -> *
ghci> :k (->)
(->) :: * -> * -> *π Types like Maybe, Either, etc. are called type constructors.
π©βπ¬ The following type signature doesn't compile because the function arrow expects two types of kind * but Maybe is * -> *
maybeToList :: Maybe -> [a]interactive>:8:16: error:
    β’ Expecting one more argument to βMaybeβ
      Expected a type, but βMaybeβ has kind β* -> *β
π©βπ¬ In some sense, type constructors are like functions: they take arguments (other types) to become complete types. They can also be partially applied!
ghci> :k Either
Either :: * -> * -> *
ghci> :k Either Int
Either Int :: * -> *
ghci> :k Either Int String
Either Int String :: *π©βπ¬ Haskell allows polymorphism over type constructors
βΉοΈ A typeclass for creating singleton "containers" from values
class Singleton f where
    singleton :: a -> f aFrom the above typeclass definition we deduce the following facts:
instance Singleton Maybe where
    singleton :: a -> Maybe a
    singleton x = Just xinstance Singleton [] where
    singleton :: a -> [a]
    singleton x = [x]ghci> singleton 3 :: Maybe Int
Just 3
ghci> singleton 3 :: [Int]
[3]ghci> :t singleton 
singleton :: Singleton f => a -> f aβΉοΈ Mapping values inside context f
class Functor f where
    fmap :: (a -> b) -> f a -> f binstance Functor Maybe      where ...
instance Functor []         where ...
instance Functor (Either e) where ...βΉοΈ fmap is a generalization of map
ghci> :t map
map :: (a -> b) -> [a] -> [b]
ghci> :t fmap
fmap :: Functor f => (a -> b) -> f a -> f bghci> fmap (+ 5) (Just 7)
Just 12
ghci> fmap not [True, False, True]
[False,True,False]
ghci> fmap (drop 8) (Right [0 .. 10])
Right [8,9,10]
ghci> fmap (drop 8) (Left "Hello, Haskell!")
Left "Hello, Haskell!"βΉοΈ Identity function
π Correct Maybe instance
id :: a -> a
id x = xinstance Functor Maybe where
    fmap :: (a -> b) -> Maybe a -> Maybe b
    fmap _ Nothing  = Nothing
    fmap f (Just x) = Just (f x)Functor law 1: IdentityΒ
Functor law 2: Composition
π Incorrect Maybe instance
instance Functor Maybe where
    fmap :: (a -> b) -> Maybe a -> Maybe b
    fmap f m = NothingFolds for lists
         "step" function
               β
          ββββββΌβββββ
foldr :: (a -> b -> b) -> b -> [a] -> b
                          β     β     β
                          β     β     ββ final result
        initial value  ββββ     β
                                β
                         list of valuesghci> foldr (+) 0 [1 .. 5]
15
ghci> foldr (*) 3 [2, 4]
24Folds can be used to express almost everything you need!
Sum of elements
Length
Pair of length and sum (to get average)
The first element (aka head)
Index of the first zero
List of all elements
List of every second element
...
π©βπ¬ However, this doesn't mean that you always must use a fold. Sometimes, an explicit recursive function is easier to read.
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr _ z [] = z
foldr f z (x : xs) = f x (foldr f z xs)foldr f z [1,2,3] == f 1 (f 2 (f 3 z)) foldr (+) 0 [1, 2, 3]
1  :  2  :  3  : []
1  + (2  + (3  + 0))π©βπ¬ foldr f z replaces every list constructor (:) with f and [] with z
π©βπ¬ Use foldr when the function is lazy on the second argument
ghci> foldr (&&) True (repeat False)
False
ghci> foldr (\x _ -> Just x) Nothing [1 .. ]
Just 1foldl :: (b -> a -> b) -> b -> [a] -> b
foldl _ z [] = z
foldl f z (x : xs) = foldl f (f z x) xsfoldl f z [1,2,3] == f (f (f z 1) 2) 3foldl (+) 0 [1, 2, 3]
        1  :  2   :  3  : []
((0  +  1) +  2)  +  3β οΈΒ foldl always leaks memory due to its nature
π©βπ¬ foldl' is a strict version of foldl
ghci> foldl' (\acc x -> x + acc) 0 [1 .. 10]
55
ghci> foldl' (\acc _ -> acc + 1) 0 [1 .. 10]
10foldr  :: (a -> b -> b) -> b -> [a] -> b
foldl' :: (b -> a -> b) -> b -> [a] -> b
π©βπ¬Β Haskell has many folds. Choose between foldrΒ / foldl'
ghci> foldr (-) 0 [1..5]
30 - (1 - (2 - (3 - (4 - 5))))ghci> foldl' (-) 0 [1..5]
-15((((0 - 1) - 2) - 3) - 4) - 5βΉοΈ Folding any structure t that contains elements
class Foldable t where
    foldr :: (a -> b -> b) -> b -> t a -> b    foldMap :: Monoid m => (a -> m) -> t a -> m
    
    ... and 15 more methods ...ghci> :t foldr
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
ghci> :t sum
sum :: (Foldable t, Num a) => t a -> a
ghci> :t concat
concat :: Foldable t => t [a] -> [a]π Now the standard Haskell library makes sense!
ghci> foldr (-) 10 (Just 3)
-7π¦₯ Laziness can lead to space leaks
sum :: [Int] -> Int
sum = go 0
  where
    go :: Int -> [Int] -> Int
    go acc []       = acc
    go acc (x : xs) = go (acc + x) xssum [3, 1, 2]
  = go 0 [3, 1, 2]
  = go (0 + 3) [1, 2]
  = go ((0 + 3) + 1) [2]
  = go (((0 + 3) + 1) + 2) []
  = ((0 + 3) + 1) + 2
  = (3 + 1) + 2
  = 4 + 2
  = 6ππ Debugging in Haskell: Equational Reasoning
π₯ You can force evaluation of lazy computations* with bangs !
{-# LANGUAGE BangPatterns #-}
sum :: [Int] -> Int
sum = go 0
  where
    go :: Int -> [Int] -> Int
    go !acc []       = acc
    go !acc (x : xs) = go (acc + x) xssum [3, 1, 2]
  = go 0 [3, 1, 2]
  = go 3 [1, 2]
  = go 4 [2]
  = go 6 []
  = 6π° No more space leaks!
* to some degree