May 2020
newtype USD = USD Integer
deriving (Eq, Ord, Show, Num)
newtype EUR = EUR Integer
deriving (Eq, Ord, Show, Num)
The different types avoid mixing currencies:
No way to write a generic function, e.g. to apply an interest rate:
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) ...
> 100 :: Money USD + 50 :: Money EUR
-- Couldn't match expected type ‘EUR’
-- with actual type ‘USD’
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 Rational
s to avoid rounding errors.)
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.
{-# 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
A type that distinguished empty from non-empty lists:
List Empty
is always emptyList NonEmpty
is always non-emptydata Empty -- phantom types
data NonEmpty
data List t a where
Nil :: List Empty a
Cons :: a -> List t a -> List NonEmpty a
Cons
always results in non-empty lists.
We can now define a safe head function:
We get a type error if we apply to the empty list:
Also a type error to add an equation safeHead Nil = ...
.
A type for lists of a given length (also know as vectors):
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
Nil
has length zeroCons
is one more than the length of argumentWe 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
safeTail
has length one less than the argumentzip :: 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)
{-# 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)
> 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.)
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)
Will the next Haskell be a fully-dependently typed language?