data Lecture 3 = type

               | class

               | instance

Custom types

Why it's not enough to have only basic types?

userFullId :: (Int, String, String) -> String
userFullId (uid, login, name) = show uid ++ ":" ++ login
ghci> userFullId (3, "pumpkin", "Ivan")
"3:pumpkin"

Problems?

type BinaryIntFunction = Int -> Int -> Int
type String            = [Char]
type FilePath          = String
type TripleList a      = [(a, a, a)]
type SwapPair a b      = (a, b) -> (b, a)

Type aliases

userFullId :: User -> String
userFullId (uid, login, name) = show uid ++ ":" ++ login
type User = (Int, String, String)

Still have problems :(

ADT's

Product types

\mathrm{PT} = T_1 \times T_2 \times \ldots \times T_n

C++

struct user {
    int uid;
    string login;
    string pass;
};
user = int \times string \times string
type User = (Int, String, String)

Haskell

Sum types

\mathrm{ST} = T_1 + T_2 + \ldots + T_n

Hard to find analogues in other non-functional languages. Haskell examples are on the following slides.

\mathrm{ADT} ::= \mathrm{PrimitiveType} \mid \mathrm{ADT} + \mathrm{ADT} \mid \mathrm{ADT} \times \mathrm{ADT}
\mathrm{PrimitiveType} ::= \mathrm{Int} \mid \mathrm{Char} \mid \mathrm{Double} \mid ...

ADT

ADT in Haskell (1 / 6, enums)

data TrafficLight = Red | Yellow | Green | Blue
-- pattern matching with types
lightName :: TrafficLight -> String
lightName Red    = "red"
lightName Yellow = "yellow"
lightName Green  = "green"
lightName Blue   = "magenta"
ghci> map lightName [Yellow, Red, Blue, Yellow]
["yellow","red","magenta","yellow"]

GHC can warn you if you don't cover all cases in pattern-matching. So compile programs with -Wall!

ADT in Haskell (2.1/6, structures)

data User = MkUser Int String String

Custom data type declaration: User

      ┌─ type name
      │
      │       ┌─ constructor name (or constructor tag)
      │       │
data User = MkUser Int String String
 │                  │    │      │
 │                  └────┴──────┴── types of fields
 │
 └ "data" keyword

Closer look at data type definition

ADT in Haskell (2.2/6, structures)

data User = MkUser Int String String
getUid :: User -> Int
getUid (MkUser uid _ _) = uid    -- pattern should be in ()

getName :: User -> String
getName (MkUser _ name _) = name
ghci> import Data.List (nub)
ghci> let users = [ MkUser 2 "Ivan" "123"
                  , MkUser 1 "Mark" "1"
                  , MkUser 3 "Ivan" "xxx"
                  ]
ghci> nub $ map getName users  -- unique names
["Ivan","Mark"]

How to create values of type User?

Constructors are just ordinary functions! Only start with uppercase.

ghci> :t MkUser
MkUser :: Int -> String -> String -> User

ADT in Haskell (3 / 6, parametric)

data Point2D a = Point2D a a  -- constructor name can be the same as type name
pointToList :: Point2D a -> [a]
pointToList (Point2D x y) = [x, y]
ghci> pointToList (Point2D 5 10)
[5, 10] 
ghci> doublePoint (Point2D 'a' 'b')
Point2D ('a', 'b') ('a', 'b') 
ghci> maxCoord (Point2D 5 10)
10
ghci> distFromZero (Point2D 5 10)
11.180339887498949
doublePoint :: Point2D a -> Point2D (a, a)
doublePoint (Point2D x y) = Point2D (x, y) (x, y) 
maxCoord :: Point2D Int -> Int
maxCoord (Point2D x y) = max x y
distFromZero :: Point2D Double -> Double
distFromZero (Point2D x y) = sqrt (x^2 + y^2)
ghci> :t Point2D  -- remeber, constructors are just functions
Point2D :: a -> a -> Point2D a

ADT in Haskell (4 / 6, sum)

data IntResult = Success Int 
               | Failure String
safeDiv :: Int -> Int -> IntResult
safeDiv _ 0 = Failure "division by zero"
safeDiv x y = Success $ x `div` y
ghci> showResult $ safeDiv 7 2
"Result: 3"
ghci> showResult $ safeDiv 7 0
"Error: division by zero"

Integer result or failure

showResult :: IntResult -> String
showResult (Success n) = "Result: " ++ show n
showResult (Failure e) = "Error:  " ++ e
ghci> :t Success 
Success :: Int -> IntResult
ghci> :t Failure 
Failure :: String -> IntResult

ADT in Haskell (5 / 6, param sum)

data Vector a = Vector2D a a | Vector3D a a a
packVector :: Vector a -> [a]
packVector (Vector2D x y)   = [x, y]
packVector (Vector3D x y z) = [x, y, z]
vecLen :: Vector Double -> Double
vecLen = sqrt . sum . map (^2) . packVector
ghci> maximum $ map vecLen [Vector3D 1.1 2.2 4.5, Vector2D 3 4]
5.12835256198

Simple geom primitives

ghci> sortOn vecLen [Vector3D 1.1 2.2 4.5, Vector2D 3 4]
[Vector2D 3.0 4.0, Vector3D 1.1 2.2 4.5]

Constructors are still functions

ghci> :t Vector2D
Vector2D :: a -> a -> Vector a
ghci> :t Vector3D
Vector3D :: a -> a -> a -> Vector a

ADT in Haskell (5.5 / 6, Maybe)

data Maybe a = Nothing | Just a  -- implemented in Prelude

Possible failure (value in box)

maybeSecond :: [a] -> Maybe a
maybeSecond (_:x:_) = Just x
maybeSecond _       = Nothing
ghci> :t Nothing
Nothing :: Maybe a
ghci> :t Just
Just :: a -> Maybe a

ADT in Haskell (5.75 / 6, Either)

data Either a b = Left a | Right b  -- implemented in Prelude

Possible parametric failure with error result

eitherSecond :: [a] -> Either String a
eitherSecond []      = Left "list is empty"
eitherSecond [_]     = Left "list has only single element"
eitherSecond (_:x:_) = Right x
ghci> :t Left
Left :: a -> Either a b
ghci> :t Right
Right :: b -> Either a b

ADT in Haskell (6 / 6, recursive)

data List a = Nil | Cons a (List a)
myList :: List Int
myList = Cons 2 (Cons 1 (Cons 3 Nil))
myMap :: (a -> b) -> List a -> List b
myMap _        Nil  = Nil
myMap f (Cons x xs) = Cons (f x) (myMap f xs) 
ghci> myMap (`div` 2) myList
Cons 1 (Cons 0 (Cons 1 Nil))

Real lists are more convenient

data [] a = [] | a : [a]
ghci> :t Nil
Nil :: List a
ghci> :t Cons
Cons :: a -> List a -> List a

Record Syntax

data User = User 
    { uid      :: Int
    , login    :: String
    , password :: String 
    }
data User = User Int String String

uid :: User -> Int
uid (User i _ _) = i

login :: User -> String
login (User _ l _) = l

password :: User -> String
password (User _ _ p) = p
ivan :: User
ivan = User { login    = "Ivan"
            , password = "123" 
            , uid      = 1
            }
isIvan :: User -> Bool
isIvan user = login user == "Ivan"

Record definition...

...is just syntax sugar for

Record Patterns and Updates

isIvan :: User -> Bool
isIvan User{ login = userName } = userName == "Ivan"
isIvan :: User -> Bool
isIvan User{ login = "Ivan" } = True
isIvan _                      = False
cloneIvan :: User
cloneIvan = ivan { uid = 2 }  -- User 2 "Ivan" "123"

Record field patterns

Record update syntax

Operator record fields

ghci> data R = R { (-->) :: Int -> Int }
ghci> let r  = R { (-->) = (+1) }
ghci> r --> 8
9

Records and sum types

data Person 
    = User  { uid :: Int, login :: String } 
    | Admin { aid :: Int, login :: String }
login :: Person -> String  -- after desugaring
login (User  _ l) = l
login (Admin _ l) = l
ghci> uid $ Admin 0 "Vasya" 
*** Exception: No match in record selector uid
isAdmin :: Person -> Bool  -- To match just the type of the construction
isAdmin Admin{} = True     -- works even without records
isAdmin _       = False

Conclusion: records with sum types are not safe

DuplicateRecordFields

data Man = Man { name :: String }
data Cat = Cat { name :: String }

Record syntax restriction

Possible in GHC 8 with -XDuplicateRecordFields (not mature)

name :: ???

Current production solution: use different names + libraries

data Man = Man { manName :: String }
data Cat = Cat { catName :: String }
{-# LANGUAGE DuplicateRecordFields #-}

data Man = Man { name :: String }
data Cat = Cat { name :: String }

shoutOnHumanBeing :: Man -> String
shoutOnHumanBeing man = (name :: Man -> String) man ++ "!!1!"  -- though...

isGrumpy :: Cat -> Bool
isGrumpy Cat{ name = "Grumpy" } = True
isGrumpy _                      = False

RecordWildCards

{-# LANGUAGE RecordWildCards #-}

data User = User 
    { uid      :: Int
    , login    :: String
    , password :: String 
    } deriving (Show)

toUnsafeString :: User -> String
toUnsafeString User{ uid = 0, .. } = "ROOT: " ++ login ++ ", " ++ password
toUnsafeString User{..}            = login ++ ":" ++ password

Fields are functions but with RWC you can treat them as values

Works with with DuplicateRecordFields!

evilMagic :: Man -> Cat
evilMagic Man{..} = Cat{..}
ghci> evilMagic $ Man "Grumpy"
Cat {name = "Grumpy"}

newtype

data    Message = Message String
newtype Message = Message String

If data type has only one constructor with only one field then it can be defined as newtype, which has more efficient runtime representation.

Using types in a wrong way

-- public key from secret key
derivePublicKey :: String -> String

checkKeyPair :: (String, String) -> Bool
checkKeyPair (secretKey, publicKey) 
    = publicKey == derivePublicKey secretKey

Why newtype?

derivePublicKey :: SecretKey -> PublicKey

checkKeyPair :: (SecretKey, PublicKey) -> Bool
checkKeyPair (secretKey, publicKey) = publicKey == derivePublicKey secretKey
newtype PublicKey = PublicKey String
newtype SecretKey = SecretKey String

compile time guarantees + runtime performance =  

Type classes

Ad-hoc polymorphism

class Printable p where  -- we don't care what 'p' stores internally
    printMe :: p -> String
helloP :: Printable p => p -> String
helloP p = "Hello, " ++ printMe p ++ "!"

For now you can think of type classes as of interfaces

data Foo = Foo | Bar  -- don't care what we can do with 'Foo', care what it stores
instance Printable Foo where
    printMe Foo = "Foo"
    printMe Bar = "Bar (whatever)"

In Haskell data and functions to work with data are separated.

data answers question: What does it store?

class answers question: What can we do with this data?

Connection between data and classinstance keyword

Polymorphic function to work with Printable

ghci> helloP Bar
"Hello, Bar (whatever)!"
ghci> helloP True
    • No instance for (Printable Bool) arising from a use of ‘helloP’
    • In the expression: helloP True
class Eq a where  
    (==) :: a -> a -> Bool  
    (/=) :: a -> a -> Bool
 
    x == y = not (x /= y)  
    x /= y = not (x == y)
    {-# MINIMAL (==) | (/=) #-}  -- minimal complete definition

Base hype classes: Eq (1 / 5)

{-# LANGUAGE InstanceSigs #-}

data TrafficLight = Red | Yellow | Green

instance Eq TrafficLight where
    (==) :: TrafficLight -> TrafficLight -> Bool
    Red    == Red    = True  
    Green  == Green  = True  
    Yellow == Yellow = True 
         _ == _      = False
threeSame :: Eq a => a -> a -> a -> Bool
threeSame x y z = x == y && y == z
ghci> threeSame Red Red Red
True
ghci> threeSame 'a' 'b' 'b'
False

It's suggested to use -XInstanceSigs to specify types of methods

-- simplified version of Ord class
class Eq a => Ord a where
   compare              :: a -> a -> Ordering
   (<), (<=), (>=), (>) :: a -> a -> Bool

   compare x y
        | x == y    =  EQ
        | x <= y    =  LT
        | otherwise =  GT

   x <= y           =  compare x y /= GT
   x <  y           =  compare x y == LT
   x >= y           =  compare x y /= LT
   x >  y           =  compare x y == GT

Base hype classes: Ord (2 / 5)

data Ordering = LT | EQ | GT

Base hype classes: Num (3 / 5)

-- | Basic numeric class.
class Num a where
    {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}

    (+), (-), (*)       :: a -> a -> a  -- self-explained
    negate              :: a -> a       -- unary negation
    abs                 :: a -> a       -- absolute value
    signum              :: a -> a       -- sign of number, abs x * signum x == x
    fromInteger         :: Integer -> a -- used for numeral literals polymorphism

    x - y               = x + negate y
    negate x            = 0 - x

When you write something like 7 it's just a syntax sugar for

fromInteger 7. That's why numeric constants are polymorphic. 

ghci> :t 5
5 :: Num p => p
ghci> :t fromInteger 5
fromInteger 5 :: Num a => a
ghci> 5 :: Int
5
ghci> 5 :: Double
5.0

Base hype classes: Show (4 / 5)

-- simplified version; used for converting things into String
class Show a where
    show :: a -> String

Show is used (for example) when values are printed in GHCi 

ghci> 5
5
ghci> show 5
"5"
ghci> "5"
"5"
ghci> show "5"
""5""
ghci> 5 :: Int
5
ghci> 5 :: Double
5.0
ghci> 5 :: Rational
5 % 1

Showing different numeric values

Base hype classes: Read (5 / 5)

-- simplified version; used for parsing thigs from String
class Read a where
    read :: String -> a

Use Read when you need to parse String. Though be careful.

ghci> :t read
read :: Read a => String -> a
ghci> read "True"
*** Exception: Prelude.read: no parse
ghci> read "True" :: Bool
True
ghci> :module Text.Read  -- safe read functions are not in Prelude, unfortunately

read throws runtime exception. Use readMaybe/readEither .

ghci> :t readMaybe
readMaybe :: Read a => String -> Maybe a
ghci> :t readEither 
readEither :: Read a => String -> Either String a
ghci> readMaybe "5" :: Maybe Int
Just 5
ghci> readMaybe "5" :: Maybe Bool
Nothing
ghci> readEither "5" :: Either String Bool -- don't worry, convenient way exist
Left "Prelude.read: no parse"
subtract :: Num a => a -> a -> a
subtract x y = y - x
cmpSum x y = if x < y then x + y else x * y

Polymorphic examples

average :: Fractional a => a -> a -> a
average x y = (x + y) / 2
ghci> :info Fractional
class Num a => Fractional a where
  (/) :: a -> a -> a
  recip :: a -> a
  fromRational :: Rational -> a
  {-# MINIMAL fromRational, (recip | (/)) #-}
  	-- Defined in ‘GHC.Real’
instance Fractional Float -- Defined in ‘GHC.Float’
instance Fractional Double -- Defined in ‘GHC.Float’
ghci> cmpSum x y = if x < y then x + y else x * y
ghci> :t cmpSum
cmpSum :: (Ord a, Num a) => a -> a -> a

What is the most general type of this function?

GHCi can help with this!

foo :: (Ord a, Read a, Show b) => String -> a -> b -> b -> String
foo = undefined -- too difficult to implement

undefined: write tomorrow, typecheck today!

undefined is not a function

foo :: (Ord a, Read a, Show b) => String -> a -> b -> b -> String
foo = error "Function `foo` crashes your code, don't call it!" 
ghci> :t undefined
undefined :: a
ghci> undefined
*** Exception: Prelude.undefined
CallStack (from HasCallStack):
  error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err
  undefined, called at <interactive>:44:1 in interactive:Ghci27
ghci> :t error
error :: [Char] -> a
ghci> error "Some meaningful message"
*** Exception: Some meaningful message
CallStack (from HasCallStack):
  error, called at <interactive>:46:1 in interactive:Ghci27

undefined and error can exist on prototyping stage. But, please, try not to use these functions.

data TrafficLight = Red | Yellow | Green | Blue
    deriving Eq  -- autoderiving instances

deriving

data TrafficLight = Red | Yellow | Green | Blue
    deriving (Eq, Ord, Enum, Bounded, Show, Read, Ix)
ghci> :t maxBound 
maxBound :: Bounded a => a
ghci> maxBound :: TrafficLight  -- Bounded also has 'minBound'
Blue
ghci> [Yello .. maxBound]  -- .. is from Enum instance
[Yellow, Green, Blue] 
ghci> show Blue
"Blue"
ghci> read "Blue" :: TrafficLight 
Blue
ghci> Red == Yellow  -- (==) is from Eq  class
False
ghci> Red < Yellow   -- (<)  is from Ord class
True
ghci> :t fromEnum 
fromEnum :: Enum a => a -> Int
ghci> :t toEnum 
toEnum :: Enum a => Int -> a
ghci> fromEnum Green
2
ghci> toEnum 2 :: TrafficLight 
Green

deriving for functions?

data FunBox = FB (Int -> String)  -- remember? functions are first class values
    deriving (Eq, Ord, Enum, Bounded, Show, Read, Ix) -- what can we derive?

What we can derive for data types which store functions?

GeneralizedNewtypeDeriving

newtype Size = Size Int
    deriving (Show, Read, Eq, Ord, Num)

Do you see problems?

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

Typical newtype deriving

Modules cheatsheet

module Lib 
       ( module Exports
       , FooB1 (..), FooB3 (FF)
       , Data.List.nub, C.isUpper
       , fooA, bazA, BAZB.isLower
       ) where

import           Foo.A
import           Foo.B     (FooB2 (MkB1), 
                            FooB3 (..))
import           Prelude   hiding (print)
import           Bar.A     (print, (<||>))
import           Bar.B     ()

import           Baz.A     as BAZA  
import qualified Data.List
import qualified Data.Char as C hiding (chr)
import qualified Baz.B     as BAZB (isLower)

import qualified Foo.X     as Exports
import qualified Foo.Y     as Exports
module Foo.A where fooA = 3
module Foo.B 
       ( FooB1, FooB2 (..), 
         FooB3 (FF, val)
       ) where

data FooB1 = MkFooB1
data FooB2 = MkB1 | MkB2
data FooB3 = FF { val :: Int }
module Baz.B (C.isLower) where 

import Data.Char as C
module Bar.B () where

class Printable p where 
    printMe :: p -> String

instance Printable Int where 
    printMe = show
module Baz.A (bazA) where bazA = map

Extra knowledge

ADTs as functions (1 / 2)

data Doctor who = Tardis who who | Dalek Int
timeTravel :: a -> a -> String
timeTravel _ _ = "Travel through time and space!"

exterminate :: Int -> String
exterminate n = unwords $ replicate n "Exterminate!"

travel :: Doctor who -> String
travel (Tardis a b) = timeTravel a b
travel (Dalek x)    = exterminate x
ghci> travel (Tardis 0 0)
"Travel through time and space!"
ghci> travel (Dalek 3)
"Exterminate! Exterminate! Exterminate!"

Non-recursive ADT as example

ADTs as functions (2 / 2)

data Doctor who = Tardis who who 
                | Dalek Int
ghci> :t Tardis 
Tardis :: who -> who -> Doctor who
ghci> :t Dalek 
Dalek :: Int -> Doctor who
f_Tardis :: who -> who -> (who -> who -> r) -> (Int -> r) -> r
f_Tardis a b = \tardis _dalek -> tardis a b
f_Dalek :: Int -> (who -> who -> r) -> (Int -> r) -> r
f_Dalek x = \_tardis dalek -> dalek x
f_travel :: ((who -> who -> String) -> (Int -> String) -> String) -> String
f_travel pattern = pattern timeTravel exterminate
ghci> f_travel (f_Tardis 0 0)
"Travel through time and space!"

ghci> f_travel (f_Dalek 3)
"Exterminate! Exterminate! Exterminate!"
type Doctor_f who r = (who -> who -> r) -> (Int -> r) -> r
f_Tardis :: who -> who -> Doctor_f who r
f_Tardis a b = \tardis _dalek -> tardis a b
f_Dalek :: Int -> Doctor_f who r
f_Dalek x = \_tardis dalek -> dalek x
f_travel :: Doctor_f who String -> String
f_travel pattern = pattern timeTravel exterminate

This can be done better with sophisticated language extensions

class Eq a where  
    (==) :: a -> a -> Bool  
    (/=) :: a -> a -> Bool
    x == y = not (x /= y)  
    x /= y = not (x == y)

Type classes as dictionaries

data EqC a = EqDict
    { eq  :: a -> a -> Bool
    , neq :: a -> a -> Bool
    }
instanceEqCWithEq :: (a -> a -> Bool) -> EqC a
instanceEqCWithEq myEq = EqDict 
    { eq  = myEq
    , neq = \x y -> not $ x `myEq` y }

instanceEqCWithNeq :: (a -> a -> Bool) -> EqC a
instanceEqCWithNeq myNeq = EqDict 
    { eq  = \x y -> not $ x `myNeq` y
    , neq = myNeq }
isInList :: EqC a -> a -> [a] -> Bool
isInList eqc x = any (eq eqc x)
ghci> isInList (instanceEqCWithEq (==)) 3 [2, 1, 3]
True

Lecture 03: Data types

By ITMO CTD Haskell

Lecture 03: Data types

Lecture about type aliases, algebraic data types, record syntax, type classes and module system .

  • 7,836