-
Notifications
You must be signed in to change notification settings - Fork 42
/
Copy pathexample0002-monad-instances-for-set.lhs
130 lines (112 loc) · 4.9 KB
/
example0002-monad-instances-for-set.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
In this example, we will use two different monad instances on sets.
In standard haskell, this is impossible because sets require an `Ord` constraint;
but in subhask we can make monads that require constraints.
The key is that set is not a monad over Hask.
It is a monad over the subcategories `OrdHask` and `Mon`.
`OrdHask` contains only those objects in Hask that have `Ord` constraints.
`Mon` is the subcategory on `OrdHask` whose arrows are monotonic functions.
Now for the preliminaries:
> {-# LANGUAGE NoImplicitPrelude #-}
> {-# LANGUAGE RebindableSyntax #-}
> {-# LANGUAGE OverloadedLists #-}
> {-# LANGUAGE TypeOperators #-}
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE GADTs #-}
>
> import SubHask
> import SubHask.Category.Trans.Constrained
> import SubHask.Category.Trans.Monotonic
> import SubHask.Compatibility.Containers
> import System.IO
We'll do everything within the `main` function so we can print some output as we go.
> main = do
Before we get into monads, let's take a quick look at the `Functor` instances.
We start by defining a set:
> let xs = [1..5] :: LexSet Int
There are multiple types for sets in SubHask, each with slightly different semantics.
The `LexSet` type has semantics similar to the `Set` type from the containers package.
In particular, the `Lex` stands for "lexical" because the `Lattice` instance corresponds to a lexical ordering.
The `Set` type in SubHask uses the more traditional subset ordering for its `Lattice` instance.
`Set` is not an instance of `Functor` or `Monad`, so we don't use it in this example.
Next, we'll create two set functions and map those functions onto the set `xs`.
The type signatures below are not mandatory, just added for clarity.
> -- f is monotonic
> let f :: Semigroup a => a -> a
> f x = x+x
>
> fxs :: LexSet Int
> fxs = fmap (proveOrdHask f) $ xs
>
> -- g is not monotonic
> let g :: (Eq a, Integral a) => a -> a
> g x = if x`mod`2 == 0 then x else -x
>
> gxs :: LexSet Int
> gxs = fmap (proveOrdHask g) $ xs
>
> putStrLn $ "xs = " + show xs
> putStrLn $ "fxs = " + show fxs
> putStrLn $ "gxs = " + show gxs
Notice in the code above that when we call `fmap`, we also called the function `proveOrdHask`.
When we map a function over a container, we must explicitly say which `Functor` instance we want to use.
The `proveOrdHask` function transform the functions from arrows in `Hask` to arrows in the `OrdHask` category.
The program would not type check without these "proofs."
Now let's see the `Functor Mon LexSet` instance in action.
This instance applies monotonic functions to the elements of the set.
Monotonic functions can be applied in time O(n), whereas non-monotonic functions take time O(n*log n).
GHC can mechanistically prove when a function in `Hask` belongs in `OrdHask`,
but it cannot always prove when functions in `OrdHask` also belong to `Mon`.
(This proof would require dependent types.)
Therefore we must use the `unsafeProveMon` function, as follows:
> let fxs' = fmap (unsafeProveMon f) $ xs
> gxs' = fmap (unsafeProveMon g) $ xs
>
> putStrLn ""
> putStrLn $ "fxs' = " + show fxs'
> putStrLn $ "gxs' = " + show gxs'
Notice that we were able to use the `Functor Mon` instance on the non-monotonic function `g`.
But since the `g` function is not in fact monotonic, the mapping did not work correctly.
Notice that equality checking is now broken:
> putStrLn ""
> putStrLn $ "fxs == fxs' = " + show (fxs == fxs')
> putStrLn $ "gxs == gxs' = " + show (gxs == gxs')
We're now ready to talk about the `Monad` instances.
To test it out, we'll create two functions, the latter of which is monotonic.
The type signatures are provided only to aide reading.
> let oddneg :: Int `OrdHask` (LexSet Int)
> oddneg = proveConstrained f
> where
> f :: (Integral a, Ord a) => a -> LexSet a
> f i = if i `mod` 2 == 0
> then [i]
> else [-i]
>
> let times3 :: (Ord a, Ring a) => a `OrdHask` (LexSet a)
> times3 = proveConstrained f
> where
> f :: (Ord a, Ring a) => a -> LexSet a
> f a = [a,2*a,3*a]
>
> let times3mon :: (Ord a, Ring a) => a `Mon` (LexSet a)
> times3mon = unsafeProveMon (times3 $)
>
> putStrLn ""
> putStrLn $ "xs >>= oddneg = " + show (xs >>= oddneg)
> putStrLn $ "xs >>= times3 = " + show (xs >>= times3)
> putStrLn $ "xs >>= times3mon = " + show (xs >>= times3mon)
One of the main advantages of monads is do notation.
Unfortunately, that's only partially supported at the moment.
Consider the do block:
```
do
x <- xs
times3 x
```
which gets desugared as:
```
xs >>= (\x -> times3 x)
```
The above code doesn't type check because the lambda expression is an arrow in Hask,
but we need an arrow in OrdHask.
This problem can be fixed by modifying the syntactic sugar of the do block to prefix its lambdas with a proof statement.
But for now, you have to do the desugaring manually.