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