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