Navigation Menu

Skip to content

Instantly share code, notes, and snippets.

@NicolasT
Last active May 25, 2017 03:15
Show Gist options
  • Star 7 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save NicolasT/8a79a6da9ffd8b8402cc to your computer and use it in GitHub Desktop.
Save NicolasT/8a79a6da9ffd8b8402cc to your computer and use it in GitHub Desktop.
Deriving Typeclass Instances using Typed Holes
# Deriving Typeclass Instances using Typed Holes
> module Conc where
> import Control.Applicative
We're presented with the following structure:
> data Concurrent a = Concurrent ((a -> Action) -> Action)
> data Action = Atom (IO Action)
> | Fork Action Action
> | Stop
We're asked to write a `Monad` instance for `Concurrent a`. As you know, every
data-type which has a `Monad` instance also has a `Functor` and `Applicative`
instance (optionally in GHC 7.8, but enforced in GHC 7.10). Since the functions
in these typeclasses are a little easier (especially `fmap`), let's start with
those.
## Functor
> instance Functor Concurrent where
At first, we'll assume we know nothing at all
```haskell
fmap f a = _
```
GHC reports
```
Found hole ‘_’ with type: Concurrent b
Where: ‘b’ is a rigid type variable bound by
the type signature for
fmap :: (a -> b) -> Concurrent a -> Concurrent b
at Conc.lhs:24:7
Relevant bindings include
a :: Concurrent a (bound at Conc.lhs:24:14)
f :: a -> b (bound at Conc.lhs:24:12)
fmap :: (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:24:7)
In the expression: _
In an equation for ‘fmap’: fmap f a = _
In the instance declaration for ‘Functor Concurrent’
```
So, we should construct a `Concurrent b` at the right-hand side, and all we got
is `a :: Concurrent a` and `f :: a -> b`. There's only one way to construct any
`Concurrent n`, so let's try
```haskell
fmap f a = Concurrent _
```
Now GHC says
```
Found hole ‘_’ with type: (b -> Action) -> Action
Where: ‘b’ is a rigid type variable bound by
the type signature for
fmap :: (a -> b) -> Concurrent a -> Concurrent b
at Conc.lhs:50:7
Relevant bindings include
a :: Concurrent a (bound at Conc.lhs:50:14)
f :: a -> b (bound at Conc.lhs:50:12)
fmap :: (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:50:7)
In the first argument of ‘Concurrent’, namely ‘_’
In the expression: Concurrent _
In an equation for ‘fmap’: fmap f a = Concurrent _
```
We need a function of type `(b -> Action) -> Action`, so let's build that:
```haskell
fmap f a = Concurrent (\c -> _)
```
which yields
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:74:31)
a :: Concurrent a (bound at Conc.lhs:74:14)
f :: a -> b (bound at Conc.lhs:74:12)
fmap :: (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:74:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
Now we need to construct something of type `Action`. The closest is `c :: b ->
Action`, but we don't have a `b` at hand...
It seems like we're stuck, but there's one more thing we can try: we have access
to the `Concurrent` constructor, so we can unpack `a :: Concurrent a` into
something hopefully more useful:
```haskell
fmap f (Concurrent a) = Concurrent (\c -> _)
```
GHC now reports
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:100:44)
a :: (a -> Action) -> Action (bound at Conc.lhs:100:26)
f :: a -> b (bound at Conc.lhs:100:12)
fmap :: (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:100:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
Now we're getting close... We need an `Action`, which `a :: (a -> Action) ->
Action` can give us when called with a function of type `a -> Action`, which we
don't have. We do have `c :: b -> Action` which comes close.
Luckily (well...) we also have `f :: a -> b` available, so we *can* construct
something of type `a -> Action` by combining `c :: b -> Action` after `f :: a ->
b`!
This brings us to
```haskell
fmap f (Concurrent a) = Concurrent (\c -> a (\a' -> c (f a')))
```
which we can rewrite as
> fmap f (Concurrent a) = Concurrent (\c -> a (c . f))
## Applicative
Next comes the `Applicative` type-class. This one consists of two functions,
which we'll handle one at a time.
> instance Applicative Concurrent where
### pure
The `pure` function is similar to `return` from the `Monad` class (actually it's
the very same). It's fairly simple to derive:
```haskell
pure a = _
```
GHC reports
```
Found hole ‘_’ with type: Concurrent a
Where: ‘a’ is a rigid type variable bound by
the type signature for pure :: a -> Concurrent a at Conc.lhs:154:7
Relevant bindings include
a :: a (bound at Conc.lhs:154:12)
pure :: a -> Concurrent a (bound at Conc.lhs:154:7)
In the expression: _
In an equation for ‘pure’: pure a = _
In the instance declaration for ‘Applicative Concurrent’
```
Again, we need to construct a `Concurrent a` value, so let's use the
constructor:
```haskell
pure a = Concurrent _
```
Like before we get
```
Found hole ‘_’ with type: (a -> Action) -> Action
Where: ‘a’ is a rigid type variable bound by
the type signature for pure :: a -> Concurrent a at Conc.lhs:175:7
Relevant bindings include
a :: a (bound at Conc.lhs:175:12)
pure :: a -> Concurrent a (bound at Conc.lhs:175:7)
In the first argument of ‘Concurrent’, namely ‘_’
In the expression: Concurrent _
In an equation for ‘pure’: pure a = Concurrent _
```
We already know how to handle this:
```haskell
pure a = Concurrent (\c -> _)
```
which gives
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: a -> Action (bound at Conc.lhs:195:29)
a :: a (bound at Conc.lhs:195:12)
pure :: a -> Concurrent a (bound at Conc.lhs:195:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
We need an `Action`, and we got `c :: a -> Action` and `a :: a`, couldn't be any
easier:
> pure a = Concurrent (\c -> c a)
### <\*>
Now comes `<*>` which is somewhat more difficult to derive. We'll start as
usual:
```haskell
f <*> a = _
```
resulting in
```
Found hole ‘_’ with type: Concurrent b
Where: ‘b’ is a rigid type variable bound by
the type signature for
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
at Conc.lhs:222:9
Relevant bindings include
a :: Concurrent a (bound at Conc.lhs:222:13)
f :: Concurrent (a -> b) (bound at Conc.lhs:222:7)
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:222:7)
In the expression: _
In an equation for ‘<*>’: f <*> a = _
In the instance declaration for ‘Applicative Concurrent’
```
As before, we construct a `Concurrent b` at the right-hand side, now skipping a
step and adding the function argument already:
```haskell
f <*> a = Concurrent (\c -> _)
```
which causes GHC to reply
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:247:30)
a :: Concurrent a (bound at Conc.lhs:247:13)
f :: Concurrent (a -> b) (bound at Conc.lhs:247:7)
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:247:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
We need an `Action`, which could be delivered through `c :: b -> Action`, but
that needs a `b` which we don't have. Since we're stuck, let's unpack the
`Concucrrent` structures, `a :: Concurrent a` and `f :: Concurrent (a -> b)`:
```haskell
Concurrent f <*> Concurrent a = Concurrent (\c -> _)
```
This gives
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:270:52)
a :: (a -> Action) -> Action (bound at Conc.lhs:270:35)
f :: ((a -> b) -> Action) -> Action (bound at Conc.lhs:270:18)
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:270:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
We need an `Action`, and we got 3 functions which all result in an `Action`, so
we'll need to make some strategic choice to move on.
The type of `f` is *larger* than the types of `a` and `c` (where `a` is *larger*
than `c`), so it's more likely we'll need to pass `a` or `c` (or some derived
value) to `f` than the other way around. Let's give that a try:
```haskell
Concurrent f <*> Concurrent a = Concurrent (\c -> f _)
```
```
Found hole ‘_’ with type: (a -> b) -> Action
Where: ‘a’ is a rigid type variable bound by
the type signature for
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
at Conc.lhs:294:20
‘b’ is a rigid type variable bound by
the type signature for
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
at Conc.lhs:294:20
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:294:52)
a :: (a -> Action) -> Action (bound at Conc.lhs:294:35)
f :: ((a -> b) -> Action) -> Action (bound at Conc.lhs:294:18)
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:294:7)
In the first argument of ‘f’, namely ‘_’
In the expression: f _
In the first argument of ‘Concurrent’, namely ‘(\ c -> f _)’
```
We need a function value again...
```haskell
Concurrent f <*> Concurrent a = Concurrent (\c -> f (\b -> _))
```
```
Found hole ‘_’ with type: Action
Relevant bindings include
b :: a -> b (bound at Conc.lhs:321:61)
c :: b -> Action (bound at Conc.lhs:321:52)
a :: (a -> Action) -> Action (bound at Conc.lhs:321:35)
f :: ((a -> b) -> Action) -> Action (bound at Conc.lhs:321:18)
(<*>) :: Concurrent (a -> b) -> Concurrent a -> Concurrent b
(bound at Conc.lhs:321:7)
In the expression: _
In the first argument of ‘f’, namely ‘(\ b -> _)’
In the expression: f (\ b -> _)
```
This should ring a bell... We need an `Action`, and we got `b :: a -> b`, `c ::
b -> Action` and `a :: (a -> Action) -> Action` available. We can get an
`Action` if we can call `a` with an `a -> Action` value, which we can construct
using `b :: a -> b` and `c :: b -> Action`:
```haskell
Concurrent f <*> Concurrent a = Concurrent (\c -> f (\b -> a (\a' -> c (b a'))))
```
This can be slightly rewritten as
> Concurrent f <*> Concurrent a = Concurrent (\c -> f (\b -> a (c . b)))
## Monad
Almost there!
> instance Monad Concurrent where
### return
The `return` case is trivial since we already defined `pure` above:
> return = pure
### >>=
We'll derive the `>>=` function similar to how we derived `<*>`. We can be
fairly certain we'll need to unpack the `Constructor a` values, and we already
know the basic pattern on the right hand side, so we can jump-start with
```haskell
Concurrent m >>= k = Concurrent (\c -> _)
```
GHC reports
```
Found hole ‘_’ with type: Action
Relevant bindings include
c :: b -> Action (bound at Conc.lhs:370:41)
k :: a -> Concurrent b (bound at Conc.lhs:370:24)
m :: (a -> Action) -> Action (bound at Conc.lhs:370:18)
(>>=) :: Concurrent a -> (a -> Concurrent b) -> Concurrent b
(bound at Conc.lhs:370:7)
In the expression: _
In the first argument of ‘Concurrent’, namely ‘(\ c -> _)’
In the expression: Concurrent (\ c -> _)
```
We need to construct an `Action`. `k :: a -> Concurrent b` seems useless at this
stage, since it doesn't construct an `Action` at all. Leaves `m :: (a -> Action)
-> Action` (we won't use `c`, since that would lead us into recursion and
whatnot, most likely not what we need!).
Let's give this a try, already passing in a function to `m`...
```haskell
Concurrent m >>= k = Concurrent (\c -> m (\a -> _))
```
```
Found hole ‘_’ with type: Action
Relevant bindings include
a :: a (bound at Conc.lhs:396:50)
c :: b -> Action (bound at Conc.lhs:396:41)
k :: a -> Concurrent b (bound at Conc.lhs:396:24)
m :: (a -> Action) -> Action (bound at Conc.lhs:396:18)
(>>=) :: Concurrent a -> (a -> Concurrent b) -> Concurrent b
(bound at Conc.lhs:396:7)
In the expression: _
In the first argument of ‘m’, namely ‘(\ a -> _)’
In the expression: m (\ a -> _)
```
So, now we have an `a :: a` available. Other than that, nothing changed. We can
use this `a` though, and pass it to `k :: a -> Concurrent b`. The resulting
`Concurrent b` value seems useless, but we can do one thing with it: unpack it!
```haskell
Concurrent m >>= k = Concurrent (\c -> m (\a -> let Concurrent k' = k a in _))
```
```
Found hole ‘_’ with type: Action
Relevant bindings include
k' :: (b -> Action) -> Action (bound at Conc.lhs:418:70)
a :: a (bound at Conc.lhs:418:50)
c :: b -> Action (bound at Conc.lhs:418:41)
k :: a -> Concurrent b (bound at Conc.lhs:418:24)
m :: (a -> Action) -> Action (bound at Conc.lhs:418:18)
(>>=) :: Concurrent a -> (a -> Concurrent b) -> Concurrent b
(bound at Conc.lhs:418:7)
In the expression: _
In the expression: let Concurrent k' = k a in _
In the first argument of ‘m’, namely
‘(\ a -> let Concurrent k' = k a in _)’
```
Given the above, the solution is obvious: we need an `Action`, and we have both
`k' :: (b -> Action) -> Action` and `c :: b -> Action` available, so creating an
`Action` is as simple as applying `c` to `k'`:
> Concurrent m >>= k = Concurrent (\c -> m (\a -> let Concurrent k' = k a in k' c))
Et voila!
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment