Skip to content

Commit d64d84a

Browse files
committed
making progress
1 parent fc4b7f8 commit d64d84a

File tree

5 files changed

+170
-63
lines changed

5 files changed

+170
-63
lines changed

app/Main.hs

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Kiselyov
1717
import System.TimeIt
1818
import Text.RawString.QQ
1919
import qualified Data.Bifunctor
20+
import LambdaToSKI (compileBracket)
2021

2122

2223
printGraph :: ST s (STRef s (Graph s)) -> ST s String
@@ -35,7 +36,7 @@ main = do
3536
hSetEncoding stdout utf8 -- this is required to handle UTF-8 characters like λ
3637

3738
--let testSource = "main = (\\x y -> + x x) 3 4"
38-
mapM_ showCompilations [prod, factorial] --, fibonacci, ackermann, tak]
39+
mapM_ showCompilations [prod, factorial, fibonacci, ackermann, tak]
3940
--demo
4041

4142
type SourceCode = String
@@ -46,7 +47,7 @@ prod = "main = λx y. * x y"
4647
tak :: SourceCode
4748
tak = [r|
4849
tak = y(λf x y z. (if (geq y x) z (f (f (sub1 x) y z) (f (sub1 y) z x) (f (sub1 z) x y ))))
49-
main = tak 7 4 2 --18 6 3
50+
main = tak 7 4 2
5051
|]
5152

5253
ackermann :: SourceCode
@@ -76,7 +77,7 @@ showCompilations source = do
7677
putStrLn "The main expression in de Bruijn notation:"
7778
mapM_ (print . Data.Bifunctor.second deBruijn) env
7879

79-
let expr = compile env abstractToSKI
80+
let expr = compileBracket env
8081
putStrLn "The main expression compiled to SICKBY combinator expressions by recursice bracket abstraction:"
8182
print expr
8283
putStrLn ""
@@ -85,8 +86,14 @@ showCompilations source = do
8586
print $ compilePlain env
8687
putStrLn ""
8788

89+
let exprK = compileK env
90+
putStrLn "The main expression compiled to SICKBY combinator expressions with K-optimization:"
91+
print exprK
92+
putStrLn ""
93+
94+
8895
let expr' = compileEta env
89-
putStrLn "The main expression compiled to SICKBY combinator expressions with eta optimization:"
96+
putStrLn "The main expression compiled to SICKBY combinator expressions with Eta-optimization:"
9097
print expr'
9198
putStrLn ""
9299

benchmark/ReductionBenchmarks.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module ReductionBenchmarks where
22

33
import Criterion.Main ( defaultMain, bench, nf )
44
import Parser ( parseEnvironment, Expr(Int, App) )
5-
import LambdaToSKI ( abstractToSKI, compile )
5+
import LambdaToSKI ( compileBracket )
66
import CLTerm
77
import Kiselyov ( compileBulk, compileEta )
88
import GraphReduction ( allocate, normalForm, toString, Graph )
@@ -16,7 +16,7 @@ import BenchmarkSources
1616
loadTestCase :: SourceCode -> IO CL
1717
loadTestCase src = do
1818
let pEnv = parseEnvironment src
19-
expr = compile pEnv abstractToSKI
19+
expr = compileBracket pEnv
2020
return expr
2121

2222
loadTestCaseBulk :: SourceCode -> IO CL
@@ -104,13 +104,13 @@ benchmarks = do
104104
, bench "ackermann HHI-Bulk" $ nf reducerTest akkBulk
105105
, bench "ackermann HHI-Bulk-Log" $ nf reducerTestLog akkBulk
106106
, bench "ackermann Native" $ nf ack_2 2
107-
, bench "gaussian Graph-Reduce" $ nf graphTest gau
108-
, bench "gaussian Graph-Reduce-Eta" $ nf graphTest gauEta
109-
, bench "gaussian HHI-Reduce" $ nf reducerTest gau
110-
, bench "gaussian HHI-Eta" $ nf reducerTest gauEta
111-
, bench "gaussian HHI-Bulk" $ nf reducerTest gauBulk
112-
, bench "gaussian HHI-Bulk-Log" $ nf reducerTestLog gauBulk
113-
, bench "gaussian Native" $ nf gaussianSum 100
107+
-- , bench "gaussian Graph-Reduce" $ nf graphTest gau
108+
-- , bench "gaussian Graph-Reduce-Eta" $ nf graphTest gauEta
109+
-- , bench "gaussian HHI-Reduce" $ nf reducerTest gau
110+
-- , bench "gaussian HHI-Eta" $ nf reducerTest gauEta
111+
-- , bench "gaussian HHI-Bulk" $ nf reducerTest gauBulk
112+
-- , bench "gaussian HHI-Bulk-Log" $ nf reducerTestLog gauBulk
113+
-- , bench "gaussian Native" $ nf gaussianSum 100
114114
, bench "tak Graph-Reduce" $ nf graphTest tak
115115
, bench "tak Graph-Reduce-Eta" $ nf graphTest takEta
116116
, bench "tak HHI-Reduce" $ nf reducerTest tak

kiselyov.md

Lines changed: 139 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ type Environment = [(String, Expr)]
6363
```
6464

6565
Now we can define a compiler that translates such λ-expressions to combinator terms.
66+
(You will find the complete code in [Kiselyov.hs](https://github.com/thma/lambda-ski/blob/main/src/Kiselyov.hs)
6667

6768
Our journey begins by translating λ-expressions to a data type `DB` which is quite similar to the λ-calculus terms but uses indices instead of variable names. This is done by the function `deBruijn`:
6869

@@ -108,81 +109,170 @@ The innermost lambda-abstraction binds the variable `y` which is represented by
108109
This notation is quite helpful as it allows to systematically adress variables by their respective position in a complex term.
109110

110111
But why are we using Peano numbers for the indices? Why not just use integers?
111-
Well it's definitely possible to [use integers instead of Peano numbers](https://crypto.stanford.edu/~blynn/lambda/cl.html).
112+
Well it's definitely possible to [use integers as indices](https://crypto.stanford.edu/~blynn/lambda/cl.html).
112113
But there is a good reason to use Peano numbers in our case:
113-
In the subsequent compilation steps we want to be able to do pattern matching on the indices. This is not possible with integers but it is possible with Peano numbers, because they are defined as an algebraic data type:
114+
In the subsequent compilation steps we want to be able to do pattern matching on the indices. This is possible with Peano numbers, because they are defined as an algebraic data type:
114115

115116
```haskell
116117
data Peano = Succ Peano | Zero
117118
```
118119

119-
Starting with the de Bruijn notation Ben Lynn's implementation of Kiselyov's algorithm builds up a series of increasingly optimized compilers that translate λ-expressions to combinator terms.
120+
Starting with the de Bruijn notation Ben Lynn's implementation of Kiselyov's algorithm builds up a series of six increasingly optimized compilers that translate λ-expressions to combinator terms:
120121

121-
I'll don't want to go into all the details of the algorithm. [Ben's blog post](https://crypto.stanford.edu/~blynn/lambda/kiselyov.html) is a great resource for this. I'll just give a brief overview of the compilation results of the different compilers.
122+
- a plain compiler without any optimizations (`compilePlain`)
123+
- a compiler that implements K-optimization (`compileK`)
124+
- a compiler that implements K- and Eta-optimization (`compileEta`)
125+
- a compiler that generates code with *Bulk Combinators* (`compileBulk`)
126+
- a compiler that eliminates *Bulk Combinators* with linear size(`compileBulkLinear`)
127+
- a compiler that eliminates *Bulk Combinators* with logarithmic size(`compileBulkLog`)
122128

123-
## The Plain compiler
124-
``` haskell
125-
compilePlain :: Environment -> CL
126-
compilePlain env = case lookup "main" env of
127-
Nothing -> error "main function missing"
128-
Just main -> snd $ plain env (deBruijn main)
129+
I'll don't want to go into all the details of the algorithms. [Ben's blog post](https://crypto.stanford.edu/~blynn/lambda/kiselyov.html) is a great resource for this. I'll just give a brief overview of the compilation outputs of the different compilers. And then I'll focus on performance comparisons between the different approaches.
130+
I will use [my original compiler](https://github.com/thma/lambda-ski/blob/main/src/LambdaToSKI.hs) based on the classic (recursively optimized) bracket abstraction as a baseline for the performance comparisons.
131+
132+
### The simple `main` example
133+
134+
```haskell
135+
main = λx y. * x y
136+
```
137+
138+
| Compiler | Output |
139+
| --- | --- |
140+
| `benchmark: bracket abstraction` | `MUL` |
141+
| `compilePlain` | `R I(B S(B(B MUL)(B K I)))` |
142+
| `compileK` | `R I(B B(B MUL I)))` |
143+
| `compileEta` | `MUL` |
144+
| `compileBulk` | `MUL` |
145+
| `compileBulkLinear` | `MUL` |
146+
| `compileBulkLog` | `MUL` |
147+
148+
From this simple example it's obvious that `compilePlain` and `compileK` generate a lot of redundant code. All the other compilers generate the same output as the baseline.
149+
150+
Please also note that the Kiselyov algorithms may emit code for an additional `R` combinator with the following reduction rule:
151+
152+
```haskell
153+
R f g x = g x f
129154
```
130155

131-
The first compiler is called `plain`. It is a straightforward translation of the de Bruijn notation to combinators. It uses the `CL` data type to represent combinator-terms:
156+
### The factorial function
132157

133158
```haskell
134-
data CL = Com Combinator | INT Integer | CL :@ CL
159+
fact = y(λf n. if (is0 n) 1 (* n (f (sub1 n))))
160+
main = fact 100
135161

136-
data Combinator = I | K | S | B | C | Y | R | B' | C' | S' | T |
137-
ADD | SUB | MUL | DIV | REM | SUB1 | EQL | GEQ | ZEROP
138-
deriving (Eq, Show)
162+
-- in de Bruijn Notation
163+
("fact", A (Free "y") (L (L (A (A (A (Free "if") (A (Free "is0") (N Zero))) (IN 1)) (A (A (Free "*") (N Zero)) (A (N (Succ Zero)) (A (Free "sub1") (N Zero))))))))
164+
("main", A (Free "fact") (IN 100))
139165
```
140166

141-
The `plain` function is defined as follows:
167+
| Compiler | Output |
168+
| --- | --- |
169+
| `benchmark: bracket abstraction` | `Y(B' S(C' IF ZEROP 1)(B' S MUL(C' S K SUB1))) 100` |
170+
| `compilePlain` | `Y(B(S(R 1(B IF(B ZEROP I))))(B(S(B MUL I))(R(B SUB1 I)(B S(B K I))))) 100` |
171+
| `compileK` | `Y(B(S(C(B IF(B ZEROP I)) 1))(B(S(B MUL I))(R(B SUB1 I)(B B I)))) 100` |
172+
| `compileEta` | `Y(B(S(C(B IF ZEROP) 1))(B(S MUL)(R SUB1 B))) 100` |
173+
| `compileBulk` | `Y(B(S(C(B IF ZEROP) 1))(B(S MUL)(C C SUB1 B))) 100` |
174+
| `compileBulkLinear` | `Y(B(S(C(B IF ZEROP) 1))(B(S MUL)(C C SUB1 B))) 100` |
175+
| `compileBulkLog` | `Y(B(S(C(B IF ZEROP) 1))(B(S MUL)(C C SUB1 B))) 100` |
176+
177+
178+
What's interesting here is that only `compileEta` produces code of the same size as the baseline. All others produce code that uses at least one more combinator. Again `compilePlain` and `compileK` generate the largest code sizes.
179+
180+
### The fibonacci function
181+
182+
```haskell
183+
fib = y(λf n. if (is0 n) 1 (if (eql n 1) 1 (+ (f (sub1 n)) (f (sub n 2)))))
184+
main = fib 10
185+
186+
-- in de Bruijn notation
187+
("fib", A (Free "y") (L (L (A (A (A (Free "if") (A (Free "is0") (N Zero))) (IN 1)) (A (A (A (Free "if") (A (A (Free "eql") (N Zero)) (IN 1))) (IN 1)) (A (A (Free "+") (A (N (Succ Zero)) (A (Free "sub1") (N Zero)))) (A (N (Succ Zero)) (A (A (Free "sub") (N Zero)) (IN 2)))))))))
188+
("main", A (Free "fib") (IN 10))
189+
```
190+
191+
| Compiler | Output |
192+
| --- | --- |
193+
| `benchmark: bracket abstraction` | `Y(B' S(C' IF ZEROP 1)(B' S(C' IF(C EQL 1) 1)(S' S(B' S(K ADD)(C' S K SUB1))(C' S K(C SUB 2))))) 10` |
194+
| `compilePlain` | `Y(B(S(R 1(B IF(B ZEROP I))))(B(S(R 1(B IF(R 1(B EQL I)))))(S(B S(B(B ADD)(R(B SUB1 I)(B S(B K I)))))(R(R 2(B SUB I))(B S(B K I)))))) 10` |
195+
| `compileK` | `Y(B(S(C(B IF(B ZEROP I)) 1))(B(S(C(B IF(C(B EQL I) 1)) 1))(S(B S(B(B ADD)(R(B SUB1 I)(B B I))))(R(C(B SUB I) 2)(B B I))))) 10` |
196+
| `compileEta` | `Y(B(S(C(B IF ZEROP) 1))(B(S(C(B IF(C EQL 1)) 1))(S(B S(B(B ADD)(R SUB1 B)))(R(C SUB 2) B)))) 10` |
197+
| `compileBulk` | `Y(B(S(C(B IF ZEROP) 1))(B(S(C(B IF(C EQL 1)) 1))(S2(B2 ADD(C C SUB1 B))(C C(C SUB 2) B)))) 10` |
198+
| `compileBulkLinear` | `Y(B(S(C(B IF ZEROP) 1))(B(S(C(B IF(C EQL 1)) 1))(B(B S) B S(B B B ADD(C C SUB1 B))(C C(C SUB 2) B)))) 10` |
199+
| `compileBulkLog` | `Y(B(S(C(B IF ZEROP) 1))(B(S(C(B IF(C EQL 1)) 1))(S B I(B(B S) B) I(S B I B ADD(C C SUB1 B))(C C(C SUB 2) B)))) 10` |
200+
201+
202+
Here we see that `compileEta` produce code of the same size as the baseline. `compileBulk` generates code with one less combinator.
203+
204+
Please also note that `compileBulk` now emits code for additional bulk combinators `S2` and `B2`. I'll come back to the semantics of these later.
205+
206+
207+
### The ackermann function
142208

143209
```haskell
144-
plain :: Environment -> DB -> (Int, CL)
145-
plain = convert (#) where
146-
(0 , d1) # (0 , d2) = d1 :@ d2
147-
(0 , d1) # (n , d2) = (0, Com B :@ d1) # (n - 1, d2)
148-
(n , d1) # (0 , d2) = (0, Com R :@ d2) # (n - 1, d1)
149-
(n1, d1) # (n2, d2) = (n1 - 1, (0, Com S) # (n1 - 1, d1)) # (n2 - 1, d2)
150-
151-
convert :: ((Int, CL) -> (Int, CL) -> CL) -> [(String, Expr)] -> DB -> (Int, CL)
152-
convert (#) env = \case
153-
N Zero -> (1, Com I)
154-
N (Succ e) -> (n + 1, (0, Com K) # t) where t@(n, _) = rec $ N e
155-
L e -> case rec e of
156-
(0, d) -> (0, Com K :@ d)
157-
(n, d) -> (n - 1, d)
158-
A e1 e2 -> (max n1 n2, t1 # t2) where
159-
t1@(n1, _) = rec e1
160-
t2@(n2, _) = rec e2
161-
IN i -> (0, INT i)
162-
Free s -> convertVar (#) env s
163-
where rec = convert (#) env
164-
165-
-- | convert a free variable to a combinator.
166-
-- first we try to find a definition in the environment.
167-
-- if that fails, we assume it is a combinator.
168-
convertVar :: ((Int, CL) -> (Int, CL) -> CL) -> [(String, Expr)] -> String -> (Int, CL)
169-
convertVar (#) env s
170-
| Just t <- lookup s env = convert (#) env (deBruijn t)
171-
| otherwise = (0, Com (fromString s))
210+
ack = y(λf n m. if (is0 n) (+ m 1) (if (is0 m) (f (sub1 n) 1) (f (sub1 n) (f n (sub1 m)))))
211+
main = ack 2 2
212+
213+
-- in de Bruijn notation
214+
("ack", A (Free "y") (L (L (L (A (A (A (Free "if") (A (Free "is0") (N (Succ Zero)))) (A (A (Free "+") (N Zero)) (IN 1))) (A (A (A (Free "if") (A (Free "is0") (N Zero))) (A (A (N (Succ (Succ Zero))) (A (Free "sub1") (N (Succ Zero)))) (IN 1))) (A (A (N (Succ (Succ Zero))) (A (Free "sub1") (N (Succ Zero)))) (A (A (N (Succ (Succ Zero))) (N (Succ Zero))) (A (Free "sub1") (N Zero))))))))))
215+
("main", A (A (Free "ack") (IN 2)) (IN 2))
172216
```
173217

218+
| Compiler | Output |
219+
| --- | --- |
220+
| `benchmark: bracket abstraction` | `Y(B' S(B S(C'(B S K)(B IF ZEROP)(C ADD 1)))(S'(B S(S(K S)))(B' S(K(S(B IF ZEROP)))(B' S(K K)(C' S(C' S K SUB1)(K 1))))(S'(B S(S(K(B S K))))(C' S K SUB1)(C' S(S(K(B S K)))(K SUB1))))) 2 2` |
221+
| `compilePlain` | `Y(B(S(B S(R(R 1(B ADD I))(B S(B(B IF)(B(B ZEROP)(B K I)))))))(S(B S(B(B S)(B(B(S(B IF(B ZEROP I))))(B(B(R 1))(R(B(B SUB1)(B K I))(B S(B(B S)(B(B K)(B K I)))))))))(S(B S(B(B S)(R(B(B SUB1)(B K I))(B S(B(B S)(B(B K)(B K I)))))))(B(R(B SUB1 I))(B(B S)(R(B K I)(B S(B(B S)(B(B K)(B K I)))))))))) 2 2` |
222+
| `compileK` | `Y(B(S(B S(R(C(B ADD I) 1)(B B(B IF(B ZEROP I))))))(S(B S(B(B S)(B(B(C(B IF(B ZEROP I))))(B(R 1)(R(B SUB1 I)(B B I))))))(S(B S(B(B B)(R(B SUB1 I)(B B I))))(B(R(B SUB1 I))(B(B B)(R I(B B I))))))) 2 2` |
223+
| `compileEta` | `Y(B(S(B S(R(C ADD 1)(B B(B IF ZEROP)))))(S(B S(B(B S)(B(B(C(B IF ZEROP)))(B(R 1)(R SUB1 B)))))(S(B S(B(B B)(R SUB1 B)))(B(R SUB1)(B B))))) 2 2` |
224+
| `compileBulk` | `Y(B(S2(C C(C ADD 1)(B B(B IF ZEROP))))(S3(B2(C(B IF ZEROP))(C C2 1(C C SUB1 B)))(S2(B2 B(C C SUB1 B))(C C2 SUB1(B B))))) 2 2` |
225+
| `compileBulkLinear` | `Y(B(B(B S) B S(C C(C ADD 1)(B B(B IF ZEROP))))(B(B S) B(B(B S) B S)(B B B(C(B IF ZEROP))(C(B(B C) B C) 1(C C SUB1 B)))(B(B S) B S(B B B B(C C SUB1 B))(C(B(B C) B C) SUB1(B B))))) 2 2` |
226+
| `compileBulkLog` | `Y(B(S B I(B(B S) B) I(C C(C ADD 1)(B B(B IF ZEROP))))(B(B(B(B S) B))(S B I)(B(B S) B) I(S B I B(C(B IF ZEROP))(C(S B I(B(B C) B) I) 1(C C SUB1 B)))(S B I(B(B S) B) I(S B I B B(C C SUB1 B))(C(S B I(B(B C) B) I) SUB1(B B))))) 2 2` |
227+
228+
As mentioned in my last post the output size of braxcket abstraction grows quadratic with the number of variables.
229+
In this case with three variables the output size for the bracket abstraction is already significantly larger than for
230+
the previous example with two variables.
231+
232+
Now the Kiselyov algorithms really start to shine. `compileEta` produces code is significantly smaller as the baseline. And `compileBulk` output is even smaller.
233+
234+
235+
### The tak function
236+
174237
```haskell
175-
The main expression compiled to SICKBY combinator expressions by recursice bracket abstraction:
176-
MUL
238+
tak = y(λf x y z. (if (geq y x) z (f (f (sub1 x) y z) (f (sub1 y) z x) (f (sub1 z) x y ))))
239+
main = tak 7 4 2
177240

178-
applying plain Kiselyov compilation:
179-
R I(B S(B(B MUL)(B K I)))
241+
-- in de Bruijn notation
242+
("tak",A (Free "y") (L (L (L (L (A (A (A (Free "if") (A (A (Free "geq") (N (Succ Zero))) (N (Succ (Succ Zero))))) (N Zero)) (A (A (A (N (Succ (Succ (Succ Zero)))) (A (A (A (N (Succ (Succ (Succ Zero)))) (A (Free "sub1") (N (Succ (Succ Zero))))) (N (Succ Zero))) (N Zero))) (A (A (A (N (Succ (Succ (Succ Zero)))) (A (Free "sub1") (N (Succ Zero)))) (N Zero)) (N (Succ (Succ Zero))))) (A (A (A (N (Succ (Succ (Succ Zero)))) (A (Free "sub1") (N Zero))) (N (Succ (Succ Zero)))) (N (Succ Zero))))))))))
243+
("main",A (A (A (Free "tak") (IN 7)) (IN 4)) (IN 2))
180244
```
181245

182-
## to be continued...
246+
| Compiler | Output |
247+
| --- | --- |
248+
| `benchmark: bracket abstraction` | `Y(B' S(B'(S(K S))(S(K S))(B' S(K IF)(B' S GEQ K)))(S'(B S(S(K(B S(S(K S))))))(S'(B S(S(K(B S(S(K S))))))(S'(B'(S(K(B'(S(K S)) K S))) K S) K(C' S K SUB1))(C'(B'(S(K(B S K))) S(S(K S)))(C' S K SUB1)(B K K)))(C'(B S(S(K(B'(S(K S)) K S))))(C'(B'(S(K S)) K S)(C' S K SUB1) K)(K K)))) 7 4 2` |
249+
| `compilePlain` | `Y(B(S(B S(B(B S)(B(R I)(B(B S)(B(B(B IF))(B(S(B S(B(B GEQ)(B K I))))(B(B K)(B K I)))))))))(S(B S(B(B S)(B(B(B S))(S(B S(B(B S)(B(B(B S))(S(B S(B(B S)(B(B(B S))(B(B(B K))(B(B K)(B K I))))))(B(B(R I))(B(B(B S))(B(R(B K I))(B(B S)(B(B(B S))(R(B(B(B SUB1))(B(B K)(B K I)))(B S(B(B S)(B(B(B S))(B(B(B K))(B(B K)(B K I))))))))))))))))(R(B(B K)(B K I))(B S(B(B S)(B(B(B S))(B(B(R I))(B(B(B S))(B(R(B(B SUB1)(B K I)))(B(B S)(B(B(B S))(B(B(B K))(B(B K)(B K I))))))))))))))))(B(R(B K I))(B(B S)(B(B(B S))(R(B(B K)(B K I))(B S(B(B S)(B(B(B S))(B(B(R(B SUB1 I)))(B(B(B S))(B(B(B K))(B(B K)(B K I)))))))))))))) 7 4 2` |
250+
| `compileK` | `Y(B(S(B S(B(B S)(B(R I)(B(B B)(B(B IF)(B(C(B GEQ I)) I)))))))(S(B S(B(B S)(B(B(B S))(S(B S(B(B S)(B(B(B S))(S(B B(B B(B B I)))(B(B(R I))(B(B(B B))(B(R I)(B(B B)(R(B SUB1 I)(B B I))))))))))(R I(B B(B C(B(B C)(B(R I)(B(B B)(R(B SUB1 I)(B B I))))))))))))(B(R I)(B(B B)(B(B C)(R I(B B(B C(R(B SUB1 I)(B B I)))))))))) 7 4 2` |
251+
| `compileEta` | `Y(B(S(B S(B(B S)(B(B IF)(C GEQ)))))(S(B S(B(B S)(B(B(B S))(S(B S(B(B S)(B(B(B S))(S(B B(B B B))(R SUB1 B)))))(B C(B(B C)(R SUB1 B)))))))(B(B C)(B C(R SUB1 B))))) 7 4 2` |
252+
| `compileBulk` | `Y(B(S3(B2 IF(C GEQ)))(S4(S4(S B3(C C SUB1 B))(B C2(C C SUB1 B)))(B2 C(B C(C C SUB1 B))))) 7 4 2` |
253+
| `compileBulkLinear` | `Y(B(B(B S) B(B(B S) B S)(B B B IF(C GEQ)))(B(B S) B(B(B S) B(B(B S) B S))(B(B S) B(B(B S) B(B(B S) B S))(S(B B(B B B))(C C SUB1 B))(B(B(B C) B C)(C C SUB1 B)))(B B B C(B C(C C SUB1 B))))) 7 4 2` |
254+
| `compileBulkLog` | `Y(B(B(B(B(B S) B))(S B I)(B(B S) B) I(S B I B IF(C GEQ)))(S B I(S B I(B(B S) B)) I(S B I(S B I(B(B S) B)) I(S(B(B B)(S B I) B)(C C SUB1 B))(B(S B I(B(B C) B) I)(C C SUB1 B)))(S B I B C(B C(C C SUB1 B))))) 7 4 2` |
255+
256+
In this example with four variables the trend continues. `compileEta` produces code is significantly smaller as the baseline. And `compileBulk` output now is only about 1/3 of the baseline.
257+
183258

184259
## performance comparison
185260

261+
So far we have seen that for functions with more than two variables the Kiselyov algorithms generate code that is significantly smaller than optimized versions of classic bracket abstraction.
262+
But what about performance? Is the code generated by the Kiselyov algorithms also faster?
263+
264+
To answer this question i have implemented a simple benchmarking suite based on the [micro-benchmarking framework Criterion](http://www.serpentine.com/criterion/).
265+
266+
In my suite I am testing the performance of combinations of the following components:
267+
268+
- the compilers `compileBracket`, `compileEta` and `compileBulk` from the previous section
269+
- the function factorial, fibonacci, ackermann and tak from the previous section
270+
- the execution backenda Graph Reduction Engine and the native Haskell functions implementaion from my previous post
271+
272+
273+
##
274+
275+
186276
![Alt text](image.png)
187277

188278
## Conclusion

src/Kiselyov.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,9 @@ module Kiselyov
44
deBruijn,
55
bulkOpt,
66
compilePlain,
7-
compileBulk,
7+
compileK,
88
compileEta,
9+
compileBulk,
910
compileBulkLinear,
1011
compileBulkLog,
1112
optK,
@@ -75,6 +76,11 @@ bulk :: Combinator -> Int -> CL
7576
bulk c 1 = Com c
7677
bulk c n = Com $ BulkCom (show c) n
7778

79+
compileK :: Environment -> CL
80+
compileK env = case lookup "main" env of
81+
Nothing -> error "main function missing"
82+
Just main -> snd $ optK env (deBruijn main)
83+
7884
compileEta :: Environment -> CL
7985
compileEta env = case lookup "main" env of
8086
Nothing -> error "main function missing"

src/LambdaToSKI.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module LambdaToSKI
22
( compileEither,
33
compile,
4+
compileBracket,
45
abstractToSKI,
56
abstractSimple,
67
abstractToCCC,
@@ -98,6 +99,9 @@ compileEither env abstractFun = case lookup "main" env of
9899
Nothing -> Left $ "main function missing in " ++ show env
99100
Just main -> Right $ abstractFun env main
100101

102+
compileBracket :: Environment -> CL
103+
compileBracket env = compile env abstractToSKI
104+
101105
compile :: Environment -> (Environment -> Expr -> Expr) -> CL
102106
compile env abstractFun =
103107
case compileEither env abstractFun of

0 commit comments

Comments
 (0)