Merge branch 'master' of lukelau.me:/srv/git/scheme
[scheme.git] / codegen.scm
1 (load "typecheck.scm")
2 (load "ast.scm")
3 (load "platform.scm")
4
5 (define target host-os)
6
7 (define (emit . s)
8   (begin
9     (apply printf s)
10     (display "\n")))
11
12 (define (codegen-add xs si env)
13   (define (go ys)
14     (if (null? ys)
15         (emit "movq ~a(%rbp), %rax" si)
16         (begin
17           (let ((y (car ys)))
18             (if (integer? y)
19                 (emit "addq $~a, ~a(%rbp)" y si)
20                 (begin
21                   (codegen-expr y (- si wordsize) env)
22                   (emit "addq %rax, ~a(%rbp)" si))))
23           (go (cdr ys)))))
24   (begin
25                                         ; use si(%rbp) as the accumulator
26     (emit "movq $0, ~a(%rbp)" si)
27     (go xs)))
28
29 (define (codegen-binop opcode)
30   (lambda (a b si env)
31     (codegen-expr b si env)
32     (emit "movq %rax, ~a(%rbp)" si)
33     (codegen-expr a (- si wordsize) env)
34     (emit "~a ~a(%rbp), %rax" opcode si)))
35
36 (define codegen-sub (codegen-binop "sub"))
37
38 (define codegen-mul (codegen-binop "imul"))
39
40 (define (codegen-not x si env)
41   (codegen-expr x si env)
42   (emit "notq %rax")
43   (emit "andq $1, %rax"))
44
45 (define (codegen-eq a b si env)
46   (codegen-expr a si env)
47   (emit "movq %rax, ~a(%rbp)" si)
48   (codegen-expr b (- si wordsize) env)
49   (emit "## ~a = ~b" a b)
50   (emit "cmpq ~a(%rbp), %rax" si)
51   (emit "sete %al"))
52
53                                         ; 'write file handle addr-string num-bytes
54
55 (define (codegen-print x si env)
56   (codegen-expr x si env) ; x should be a static-string, producing a label
57
58                                         ; make a copy of string address since %rax and %rdi are clobbered
59   (emit "mov %rax, %rbx")
60   
61                                         ; get the length of the null terminated string
62   (emit "mov %rax, %rdi")
63   (emit "xor %al, %al")   ; set %al to 0
64   (emit "mov $-1, %rcx") ; max search length = max int = -1
65   (emit "cld")           ; clear direction flag, search up in memory
66   (emit "repne scasb")   ; scan string, %rcx = -strlen - 1 - 1
67   
68   (emit "not %rcx")      ; -%rcx = strlen + 1
69   (emit "dec %rcx")
70   
71   (emit "movq %rbx, %rsi") ; string addr
72   (emit "movq %rcx, %rdx") ; num bytes
73   (emit "movq $1, %rdi")   ; file handle (stdout)
74   (case target
75     ('darwin (emit "mov $0x2000004, %rax")) ; syscall 4 (write)
76     ('linux  (emit "mov $1, %rax"))) ; syscall 1 (write)
77   (emit "syscall"))
78
79 (define wordsize 8)
80
81 (define (codegen-let bindings body si env)
82
83                                         ; is this a closure that captures itself?
84                                         ; e.g. (let ([x 3] [f (closure lambda0 (f x))]) (f))
85   (define (self-captive-closure? name expr)
86     (and (eqv? (ast-type expr) 'closure)
87          (memv name (caddr expr))))
88   
89   (let* ((stack-offsets (map (lambda (name x) ; assoc map of binding name to offset
90                                (cons name (- si (* x wordsize))))
91                              (map car bindings)
92                              (range 0 (length bindings))))
93          (inner-si (- si (* (length bindings) wordsize)))
94
95          (get-offset (lambda (n) (cdr (assoc n stack-offsets))))
96          
97          [inner-env
98           (fold-left
99            (lambda (env comps)
100              (let ([scc-env
101                     (fold-left
102                      (lambda (acc name)
103                        (cons (cons name (get-offset name))
104                              acc))
105                      env
106                      comps)])
107                (for-each 
108                 (lambda (name)
109                   (let ([expr (cadr (assoc name bindings))])
110                     (emit "## generating ~a with scc-env ~a" name scc-env)
111                     (if (self-captive-closure? name expr)
112                                         ; if self-captive, insert a flag into the environment to let
113                                         ; codegen-closure realise this!
114                         (codegen-expr expr
115                                       inner-si
116                                       (cons (cons name 'self-captive)
117                                             scc-env))
118                         (codegen-expr expr inner-si scc-env))
119                     (emit "movq %rax, ~a(%rbp)" (get-offset name))))
120                 comps)
121                scc-env))
122            env (reverse (sccs (graph bindings))))])
123     
124     (for-each (lambda (form)
125                 (codegen-expr form inner-si inner-env))
126               body)))
127
128 (define (codegen-var name si env)
129   (when (not (assoc name env))
130     (error #f (format "Variable ~a is not bound" name)))
131   (let ((offset (cdr (assoc name env))))
132     (emit "movq ~a(%rbp), %rax" offset)))
133
134 (define cur-lambda 0)
135 (define (fresh-lambda)
136   (set! cur-lambda (+ 1 cur-lambda))
137   (format "_lambda~a" (- cur-lambda 1)))
138
139                                         ; a closure on the heap looks like:
140                                         ; 0    8         16        24
141                                         ; addr var1....  var2....  var3....
142
143 (define (codegen-closure label captured si env)
144   (let* ((heap-offsets (map (lambda (i) (+ 8 (* 8 i)))
145                             (range 0 (length captured))))) ; 4, 12, 20, etc.
146
147     (emit "## creating closure")
148
149     (emit "movq heap_start@GOTPCREL(%rip), %rbx")
150     
151     (emit "movq (%rbx), %rax")          ; %rax = heap addr of closure
152
153
154                                         ; point heap_start to next space
155     (emit "addq $~a, (%rbx)" (+ 8 (* 8 (length captured))))
156
157     (emit "## storing address to lambda")
158                                         ; store the address to the lambda code
159     (emit "movq ~a@GOTPCREL(%rip), %rbx" label)
160     (emit "movq %rbx, 0(%rax)")
161
162     (emit "## storing captives")
163                                         ; store the captured vars
164     (for-each
165      (lambda (var-name heap-offset)
166        (let ([stack-offset (cdr (assoc var-name env))])
167          (emit "### captive ~a" var-name)
168          (if (eqv? stack-offset 'self-captive)
169                                         ; captive refers to this closure:
170                                         ; move heap addr of this closure to stack! 
171              (emit "movq %rax, ~a(%rax)" heap-offset)
172              (begin
173                (emit "movq ~a(%rbp), %rbx" stack-offset)
174                (emit "movq %rbx, ~a(%rax)" heap-offset)))))
175      captured
176      heap-offsets)))
177
178                                         ; for now we can only call closures
179 (define (codegen-call f args si env)
180   (codegen-expr f si env)
181
182   (emit "## starting call")
183   
184   (emit "movq %rax, ~a(%rbp)" si) ; store address of closure first on stack
185   
186                                         ; codegen the arguments, store them intermediately
187   (for-each
188    (lambda (e i)
189      (begin
190        (emit "## arg no. ~a" (- i 1))
191        (codegen-expr e (- si (* wordsize i)) env)
192                                         ; store intermediate result on stack
193        (emit "movq %rax, ~a(%rbp)" (- si (* wordsize i)))))
194
195    args (range 1 (length args)))
196
197                                         ; now that we have everything we need on the stack,
198                                         ; move them into the param registers
199
200   (emit "## moving args into place")
201   (for-each
202    (lambda (i) (emit "movq ~a(%rbp), ~a"
203                      (- si (* wordsize i))
204                      (param-register i)))
205    (range 1 (length args)))
206
207                                         ; todo: can this be made more efficient
208   (emit "movq ~a(%rbp), %rax" si)       ; load back pointer to closure
209
210   (emit "## moving captives into place")
211   
212                                         ; move captives into first argument
213   (emit "movq %rax, %rbx")
214   (emit "addq $8, %rbx")
215   (emit "movq %rbx, ~a" (param-register 0))
216
217   (emit "## performing call")
218
219   (emit "addq $~a, %rsp" si) ; adjust the stack pointer to account all the stuff we put in the env
220   (emit "callq *(%rax)")                ; call closure function
221   (emit "subq $~a, %rsp" si))
222
223                                         ; LAMBDAS:
224                                         ; 1st param: pointer to captured args
225                                         ; 2nd param: 1st arg
226                                         ; 3rd param: 2nd arg, etc.
227
228 (define (codegen-lambda l)
229   (let* ((label (car l))
230          (stuff (cdr l))
231          (captives (car stuff))
232          (args (cadr stuff))
233          (body (caddr stuff))
234                                         ; params = what actually gets passed
235          (params (append captives args))
236
237          (stack-offsets (map (lambda (i)
238                                (* (- wordsize) (+ 1 i)))
239                              (range 0 (length params))))
240
241          (env (map cons params stack-offsets)))
242     (emit "~a:" label)
243
244     (display "## lambda captives: ")
245     (display captives)
246     (newline)
247     (display "## lambda args: ")
248     (display args)
249     (newline)
250     (display "## lambda body: ")
251     (display body)
252     (newline)
253     
254     (emit "push %rbp") ; preserve caller's base pointer
255     
256     (emit "movq %rsp, %rbp") ; set up our own base pointer
257
258                                         ; load the captured vars onto the stack
259     (for-each
260      (lambda (i)
261        (begin
262          (emit "# loading captive ~a" (list-ref captives i))
263          (emit "movq ~a(~a), %rbx" (* wordsize i) (param-register 0))
264          (emit "movq %rbx, ~a(%rbp)" (* (- wordsize) (+ 1 i)))))
265      (range 0 (length captives)))
266
267                                         ; load the args onto the stack
268     (for-each
269      (lambda (i)
270        (begin
271          (emit "movq ~a, %rbx" (param-register (+ 1 i)))
272          (emit "movq %rbx, ~a(%rbp)"
273                (* (- wordsize)
274                   (+ 1 (length captives) i)))))
275      (range 0 (length args)))
276     
277     (codegen-expr body (* (- wordsize) (+ 1 (length params))) env)
278
279     (emit "pop %rbp") ; restore caller's base pointer
280     (emit "ret")))
281
282 (define cur-label 0)
283 (define (fresh-label)
284   (set! cur-label (+ 1 cur-label))
285   (format "label~a" (- cur-label 1)))
286
287 (define (codegen-if cond then else si env)
288   (codegen-expr cond si env)
289   (emit "cmpq $0, %rax")
290   (let ((exit-label (fresh-label))
291         (else-label (fresh-label)))
292     (emit "je ~a" else-label)
293     (codegen-expr then si env)
294     (emit "jmp ~a" exit-label)
295     (emit "~a:" else-label)
296     (codegen-expr else si env)
297     (emit "~a:" exit-label)))
298
299 (define (codegen-expr e si env)
300   (emit "# ~a" e)
301   (case (ast-type e)
302     ('closure (codegen-closure (cadr e) (caddr e) si env))
303     ('app
304      (case (car e)
305        ('+ (codegen-add (cdr e) si env))
306        ('- (codegen-sub (cadr e) (caddr e) si env))
307        ('* (codegen-mul (cadr e) (caddr e) si env))
308        ('! (codegen-not (cadr e) si env))
309        ('= (codegen-eq  (cadr e) (caddr e) si env))
310        ('bool->int (codegen-expr (cadr e) si env))
311        ('print (codegen-print (cadr e) si env))
312        (else (codegen-call (car e) (cdr e) si env))))
313
314                                         ; this is a builtin being passed around as a variable
315     ('builtin (emit "movq $~a, %rax" (builtin-id e)))
316
317     ('let (codegen-let (let-bindings e)
318                        (let-body e)
319                        si
320                        env))
321
322     ('var (codegen-var e si env))
323
324     ('if (codegen-if (cadr e) (caddr e) (cadddr e) si env))
325     
326     ('bool-literal (emit "movq $~a, %rax" (if e 1 0)))
327     ('int-literal (emit "movq $~a, %rax" e))
328     
329     ('static-string (emit "movq ~a@GOTPCREL(%rip), %rax"
330                           (cadr e)))
331
332     (else (error #f "don't know how to codegen this"))))
333
334
335
336 (define (free-vars prog)
337   (define bound '())
338   (define (collect e)
339     (case (ast-type e)
340       ('builtin '()) ; do nothing
341       ('var (if (memv e bound) '() (list e)))
342       ('lambda
343           (begin
344             (set! bound (append (lambda-args e) bound))
345             (collect (lambda-body e))))
346
347       ('app (flat-map collect e))
348       ('if (flat-map collect (cdr e)))
349       ('let
350           (let ([bind-fvs (flat-map (lambda (a)
351                                       (begin
352                                         (set! bound (cons (car a) bound))
353                                         (collect (cdr a))))
354                                     (let-bindings e))])
355             (append bind-fvs (flat-map collect (let-body e)))))
356       (else '())))
357   (collect prog))
358
359                                         ; ((lambda (x) (+ x y)) 42) => ((closure lambda1 (y)) 42)
360                                         ;                              [(lambda1 . ((y), (x), (+ x y))]
361                                         ; for builtins, this generates a closure if it is used
362                                         ; outside of an immediate app
363                                         ; but only one closure for each builtin
364
365 (define (extract-lambdas program)
366   (define lambdas '())
367   (define (add-lambda e)
368     (let* ((label (fresh-lambda))
369            (args (lambda-args e))
370            (captured (free-vars e))
371            (body (extract (lambda-body e)))
372            (new-lambda (cons label (list captured args body))))
373       (set! lambdas (cons new-lambda lambdas))
374       `(closure ,label ,captured))) ; todo: should we string->symbol?
375
376   (define (find-builtin-lambda e)
377     (let [(l (assq (builtin-name e) lambdas))]
378       (if l `(closure ,(car l) ,(caadr l)) #f)))
379
380   (define (builtin-name e)
381     (case e
382       ('+ "_add")
383       ('- "_sub")
384       ('* "_mul")
385       ('! "_not")
386       ('= "_eq")
387       ('bool->int "_bool2int")
388       ('print "_print")
389       (else (error #f "don't know this builtin"))))
390   (define (builtin-args e)
391     (case e
392       ('+ '(x y))
393       ('- '(x y))
394       ('* '(x y))
395       ('! '(x))
396       ('= '(x y))
397       ('bool->int '(x))
398       ('print '(x))
399       (else (error #f "don't know this builtin"))))
400
401   (define (add-builtin-lambda e)
402     (let* [(label (builtin-name e))
403            (captured '())
404            (args (builtin-args e))
405            (body `(,e ,@args))
406            (new-lambda (cons label (list captured args body)))]
407       (set! lambdas (cons new-lambda lambdas))
408       `(closure ,label ,captured)))
409   
410   (define (extract e)
411     (case (ast-type e)
412       ('lambda (add-lambda e))
413       ('let `(let ,(map (lambda (b) `(,(car b) ,@(extract (cdr b)))) (let-bindings e))
414                ,@(map extract (let-body e))))
415       ('app (append
416                                         ; if a builtin is used as a function, don't generate lambda
417              (if (eqv? 'builtin (ast-type (car e)))
418                  (list (car e))
419                  (list (extract (car e))))
420              (map extract (cdr e))))
421       
422       ('builtin
423        (if (find-builtin-lambda e)
424            (find-builtin-lambda e)
425            (add-builtin-lambda e)))
426
427       
428       (else (ast-traverse extract e))))
429   (let ((transformed (extract program)))
430     (cons lambdas transformed)))
431
432 (define (extract-strings program)
433   (let ((cur-string 0)
434         (strings '())) ; assoc list of labels -> string
435     (define (fresh-string)
436       (set! cur-string (+ cur-string 1))
437       (format "string~a" (- cur-string 1)))
438     (define (extract e)
439       (case (ast-type e)
440         ('string-literal
441          (let ((label (fresh-string)))
442            (set! strings (cons (cons label e) strings))
443            `(static-string ,label)))
444         (else (ast-traverse extract e))))
445     (let ((transformed (extract program)))
446       (cons strings transformed))))
447
448 (define (emit-string-data s)
449   (emit "~a:" (car s))
450   (emit "\t.string \"~a\"" (cdr s)))
451
452 ;; (define (amd64-abi f)
453 ;;                                      ; preserve registers
454 ;;   (emit "push %rbp")
455 ;;   ;; (emit "push %rbx")
456 ;;   ;; (for-each (lambda (i)
457 ;;   ;;               (emit (string-append
458 ;;   ;;                      "push %r"
459 ;;   ;;                      (number->string i))))
460 ;;   ;;             '(12 13 14 15))
461
462 ;;   (emit "movq %rsp, %rbp")              ; set up the base pointer
463
464 ;;   (f) ; call stuff
465 ;;                                      ; restore preserved registers
466 ;;   ;; (for-each (lambda (i)
467 ;;   ;;               (emit (string-append
468 ;;   ;;                      "pop %r"
469 ;;   ;;                      (number->string i))))
470 ;;   ;;             '(15 14 13 12))
471 ;;   ;; (emit "pop %rbx")
472 ;;   (emit "pop %rbp")
473 ;;   (emit "ret"))
474
475                                         ; 24(%rbp) mem arg 1
476                                         ; 16(%rbp) mem arg 0          prev frame
477                                         ; -----------------------
478                                         ;  8(%rbp) return address     cur frame
479                                         ;  0(%rbp) prev %rbp
480                                         ; -8(%rbp) do what you want
481                                         ;  ...     do what you want
482                                         ;  0(%rsp) do what you want
483
484 (define (param-register n)
485   (case n
486     (0 "%rdi")
487     (1 "%rsi")
488     (2 "%rdx")
489     (3 "%rcx")
490     (4 "%r8")
491     (5 "%r9")
492     (else (error #f "need to test out the below"))
493     (else (format "~a(%rsp)" (- n 6)))))
494
495 (define (initialize-heap)
496   (let ((mmap
497          (case target
498            ('darwin "0x20000c5")
499            ('linux "9"))))
500                                         ; allocate some heap memory
501     (emit "mov $~a, %rax" mmap) ; mmap
502     (emit "xor %rdi, %rdi")  ; addr = null
503     (emit "movq $1024, %rsi")   ; length = 1kb
504     (emit "movq $0x3, %rdx") ; prot = read | write = 0x2 | 0x1
505                                         ;    flags = anonymous | private
506     (case target
507       ('darwin (emit "movq $0x1002, %r10")) ; anon = 0x1000, priv = 0x02
508       ('linux (emit "movq $0x22, %r10")))   ; anon = 0x20,   priv = 0x02
509     (emit "movq $-1, %r8") ; fd = -1
510     (emit "xor %r9, %r9") ; offset = 0
511     (emit "syscall")
512                                         ; %rax now contains pointer to the start of the heap
513                                         ; keep track of it
514
515     (emit "movq heap_start@GOTPCREL(%rip), %rsi")
516     (emit "movq %rax, (%rsi)")))
517
518 (define (codegen program)
519   (set! cur-label 0)
520   (set! cur-lambda 0)
521   (let* ([body (program-body program)]  
522          
523          (extract-res-0 (extract-strings body))
524          (strings (car extract-res-0))
525          (extract-res-1 (extract-lambdas (cdr extract-res-0)))
526          (lambdas (car extract-res-1))
527          (xform-prog (cdr extract-res-1)))
528
529     (emit "\t.global _start")
530     (emit "\t.text")
531                                         ;    (emit ".p2align 4,,15") is this needed?
532
533     (for-each codegen-lambda lambdas)
534
535     (emit "_start:")
536
537     (initialize-heap)
538
539     (emit "movq %rsp, %rbp")            ; set up the base pointer
540     
541     (codegen-expr xform-prog (- wordsize) '())
542
543                                         ; exit syscall
544     (emit "mov %rax, %rdi")
545     (case target
546       ('darwin (emit "movq $0x2000001, %rax"))
547       ('linux (emit "mov $60, %rax")))
548     (emit "syscall")
549
550     (emit ".data")
551
552     (emit "heap_start:")
553     (emit "\t.quad 0")
554
555     (for-each emit-string-data strings)))
556
557 (define (compile-to-binary program output t)
558   (set! target t)
559   (when (not (eq? (typecheck program) 'Int)) (error #f "not an Int"))
560   (let ([tmp-path "/tmp/a.s"])
561     (when (file-exists? tmp-path) (delete-file tmp-path))
562     (with-output-to-file tmp-path
563       (lambda () (codegen program)))
564
565     (case target
566       ('darwin
567        (system "as /tmp/a.s -o /tmp/a.o")
568        (system (format "ld /tmp/a.o -e _start -macosx_version_min 10.14 -static -o ~a" output)))
569       ('linux
570        (system "as /tmp/a.s -o /tmp/a.o")
571        (system (format "ld /tmp/a.o -o ~a" output))))))
572
573 ; NOTES
574 ; syscalls in linux and darwin use the following arguments for syscall instruction:
575 ; %rax = syscall #
576 ; %rdi = 1st arg
577 ; %rsi = 2nd arg
578 ; %rdx = 3rd arg
579 ; %r10 = 4th arg
580 ; %r8  = 5th arg
581 ; %r9  = 6th arg
582
583 ; on darwin, the syscall is offset by 0x2000000
584 ; https://opensource.apple.com/source/xnu/xnu-2782.20.48/bsd/kern/syscalls.master
585 ; documentation for most syscalls: /Applications/Xcode.app/Contents/Developer/Platforms/MacOSX.platform/Developer/SDKs/MacOSX.sdk/usr/include/sys