Encoding invariants using types

Pedro Vasconcelos, DCC/FCUP

May 2020

Motivation

Encoding invariants in types

Dependent types

Phantom types and GADTs

Phantom types

Example: money

First attempt

newtype USD = USD Integer
    deriving (Eq, Ord, Show, Num)
            
newtype EUR = EUR Integer
    deriving (Eq, Ord, Show, Num)   

The different types avoid mixing currencies:

> 100 :: USD + 50 :: EUR
-- Couldn't match expected type
-- ‘EUR’ with actual type ‘USD’

Limitations

No way to write a generic function, e.g. to apply an interest rate:

interest :: Float -> USD -> USD
interest :: Float -> EUR -> EUR

Second attempt

A money type with a phantom parameter (currency):

newtype Money curr = Money Integer
           -- ^ phantom parameter 

data USD   -- phantom types for currencies
data EUR
...

instance Show (Money USD) ...
instance Show (Money EUR) ...

Phantom currencies

  > 100 :: Money USD + 50 :: Money EUR
  --  Couldn't match expected type ‘EUR’ 
  --  with actual type ‘USD’

Generic currency functions

interest :: Float -> Money curr -> Money curr
interest rate (Money amount) 
   = Money (round (rate*fromIntegral amount))

> rate 0.1 (100 :: Money USD)
USD 10 

> rate (1/3) (100 :: Money EUR)
EUR 33

(Could use Rationals to avoid rounding errors.)

Second example: ST monad

newSTRef :: a -> ST s (STRef s a)
                --  ^--------^ phantom param
                
runST :: (forall s. ST s a) -> a
            --   ^----- prevents escape

The s parameter ensures safe use of the library: references cannot escape the ST computation.

GADTs

Algebraic data types

data Bool = True | False

data Maybe a = Nothing | Just a

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

Using GADT syntax

{-# LANGUAGE GADTs #-}

data Bool where
    True :: Bool
    False :: Bool
    
data Maybe a where
    Nothing :: Maybe a
    Just :: a -> Maybe a
    
data List a where
    Nil :: List a 
    Cons :: a -> List a -> List a

Generalized Algebraic DataTypes

Example: non-empty lists

A type that distinguished empty from non-empty lists:

data Empty     -- phantom types
data NonEmpty

data List t a where
   Nil :: List Empty a 
   Cons :: a -> List t a -> List NonEmpty a

Examples

Nil          :: List Empty a
Cons 'A' Nil :: List NonEmpty Char
Cons 1 (Cons 2 Nil) :: List NonEmpty Int

Cons always results in non-empty lists.

Non-empty lists (cont.)

We can now define a safe head function:

safeHead :: List NonEmpty a -> a
safeHead (Cons x xs) = x

We get a type error if we apply to the empty list:

> safeHead Nil
 -- Couldn't match type ‘Empty’ with ‘NonEmpty’

Also a type error to add an equation safeHead Nil = ....

Sized lists

A type for lists of a given length (also know as vectors):

List Z           -- length 0
List (S Z)       -- length 1
List (S (S Z))   -- length 2
...              -- etc.

Sized lists (cont.)

data Z    -- type-level Peano naturals
data S n  -- i.e., Z, S Z, S (S Z), ...

data List n a where
  Nil :: List Z a
  Cons :: a -> List n a -> List (S n) a

Programming with sizes

We can now define both safe head and safe tail.

safeHead :: List (S n) a -> a
safeHead (Cons x xs) = x

safeTail :: List (S n) a -> List n a
safeTail (Cons x xs) = xs

Size relations

zip :: List n a -> List n b -> List n (a,b)
zip Nil Nil = Nil
zip (Cons x xs) (Cons y ys) 
                   = Cons (a,b) (zip xs ys)

Size relations (cont.)

map :: (a -> b) -> List n a -> List n b
map f Nil = Nil
map f (Cons x xs) = Cons (f x) (map f xs)
map f (Cons x xs) = map f xs
-- type error: Cannot deduce n1 ~ S n1 ...

Beyond equality

append :: List n a -> List m a 
                   -> List (Add n m) a 
 -- Add n m: addition of type-level naturals

Appending lists

{-# LANGUAGE TypeFamilies #-}

append :: List n a -> List m a
                   -> List (Add n m) a
append Nil ys = ys
append (Cons x xs) ys = Cons x (append xs ys)

-- a type-level function for addition
type family Add n m
type instance Add Z y = y
type instance Add (S x) y = S (Add x y)

Appending lists: example

>  append (Cons 1 Nil) (Cons 2 Nil)
Cons 1 (Cons 2 Nil) 
> :t append (Cons 1 Nil) (Cons 2 Nil)
List (S (S Z)) Int

(show interactive example.)

Appending lists (version 2)

We can make the syntax nicer with type level operators:

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}

append :: List n a -> List m a -> List (n+m) a
...
-- addition using type operators
type family n + m
type instance Z + y = y
type instance (S x) + y = S (x+y)

Towards dependent types?

Will the next Haskell be a fully-dependently typed language?