-
Notifications
You must be signed in to change notification settings - Fork 28
/
2014-12-12-type-families.lhs
155 lines (124 loc) · 5.42 KB
/
2014-12-12-type-families.lhs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
---
title: "24 Days of GHC Extensions: Type Families"
---
Today, we're going to look at an extension that radically alters the behavior of
GHC Haskell by extending what we can do with types. The extension that we're
looking at is known as [type
families](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/type-families.html),
and it has a wide variety of applications.
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE TypeFamilies #-}
> import Control.Concurrent.STM
> import Control.Concurrent.MVar
> import Data.Foldable (forM_)
> import Data.IORef
As the extension is so large, we're only going to touch the surface of the
capabilities - though this extension is well documented, so there's plenty of
extra reading for those who are interested!
Associated Types
----------------
To begin, lets look at the interaction of type families and type classes. In
ordinary Haskell, a type class can associate a set of *methods* with a type. The
type families extension will now allow us to associate *types* with a type.
As an example, lets try and abstract over the various mutable stores that we
have available in Haskell. In the `IO` monad, we can use `IORef`s and `MVar`s to
store data, whereas other monads have their own specific stores, as we'll soon
see. To begin with, we'll start with a class over the different types of store:
> class IOStore store where
> newIO :: a -> IO (store a)
> getIO :: store a -> IO a
> putIO :: store a -> a -> IO ()
This works fine for `IO` stores: we can add an instance for `MVar`...
> instance IOStore MVar where
> newIO = newMVar
> getIO = readMVar
> putIO mvar a = modifyMVar_ mvar (return . const a)
and an instance for `IORef`:
> instance IOStore IORef where
> newIO = newIORef
> getIO = readIORef
> putIO ioref a = modifyIORef ioref (const a)
Now we have the ability to write functions that are polymorphic over stores:
> type Present = String
> storePresentsIO :: IOStore store => [Present] -> IO (store [Present])
> storePresentsIO xs = do
> store <- newIO []
> forM_ xs $ \x -> do
> old <- getIO store
> putIO store (x : old)
> return store
While this example is obviously contrived, hopefully you can see how we are able
to interact with a memory store without choosing *which* store we are commiting
to. We can use this by choosing the type we need, as the following GHCI session
illustrates:
```
.> s <- storePresentsIO ["Category Theory Books"] :: IO (IORef [Present])
.> :t s
s :: IORef [Present]
.> get s
["Category Theory Books"]
```
Cool - now we can go and extend this to `TVar` and other `STM` cells!
Ack... there is a problem. Reviewing our `IOStore` type class, we can see that
we've commited to working in the `IO` monad - and that's a shame. What we'd like
to be able to do is associate the type of monad with the type of store we're
using - as knowing the store tells us the monad that we have to work in.
To use type families, we use the `type` keyword within the `class` definition,
and specify the *kind* of the type:
> class Store store where
> type StoreMonad store :: * -> *
> new :: a -> (StoreMonad store) (store a)
> get :: store a -> (StoreMonad store) a
> put :: store a -> a -> (StoreMonad store) ()
As you can see, the types of the methods in the type class has become a little
more complicated. Rather than working in the `IO` monad, we calculate the monad
by using the `StoreMonad` type family.
The instances are similar to what we saw before, but we also have to provide the
necessary type of monad:
> instance Store IORef where
> type StoreMonad IORef = IO
> new = newIORef
> get = readIORef
> put ioref a = modifyIORef ioref (const a)
>
> instance Store TVar where
> type StoreMonad TVar = STM
> new = newTVar
> get = readTVar
> put ioref a = modifyTVar ioref (const a)
As you can see - our methods don't need to change at all; type families
naturally extend the existing type class functionality. Our original
`storePresentsIO` can now be made to work in any monad, with only a change to
the type:
> storePresents :: (Store store, Monad (StoreMonad store))
> => [Present] -> (StoreMonad store) (store [Present])
> storePresents xs = do
> store <- new []
> forM_ xs $ \x -> do
> old <- get store
> put store (x : old)
> return store
As we have an instance for `Store TVar`, we can now use this directly in an
`STM` transaction:
````
.> atomically (do (storePresents ["Distributed Computing Through Combinatorial Topology"]
:: STM (TVar [Present])) >>= get)
["Distributed Computing Through Combinatorial Topology"]
````
Awesome!
Type Families and Computation
-----------------------------
What we've seen so far is extremely useful, but the fun needn't stop there! Type
families also give us the ability to compute over types! Traditionally, Haskell
is built around value level computation - running programs should do
something. That said, we all know how useful it is to have functions - so why
can't we have them at the type level? Well, now that we have the ability to
associate types with types, we can!
To look at this new functionality (closed type families), we need a few more
extensions to really unlock the potential here, so I'll finish this blog post on
that cliff hanger. Watch this space!
----
*This post is part of
[24 Days of GHC Extensions](/pages/2014-12-01-24-days-of-ghc-extensions.html) -
for more posts like this, check out the
[calendar](/pages/2014-12-01-24-days-of-ghc-extensions.html)*.