Fix bindings in ADT pattern matching codegen
[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 (stack-type? data-layouts type)
15   (if (assoc type data-layouts) #t #f))
16
17
18 (define (type-size data-layouts type)
19
20   (define (adt-size adt)
21     (let ([sizes
22            (map (lambda (sum)
23                   (fold-left (lambda (acc x) (+ acc (type-size data-layouts x)))
24                              wordsize ; one word needed to store tag
25                              (cdr sum)))
26                 (cdr adt))])
27       (apply max sizes)))
28   
29   (case type
30     ['Int wordsize]
31     ['Bool wordsize]
32     [else
33      (let ([adt (assoc type data-layouts)])
34        (if adt
35            (adt-size adt)
36            (error #f "unknown size" type)))]))
37
38                                         ; returns the size of an expression's result in bytes
39 (define (expr-size dls e)
40   (if (eqv? (ast-type e) 'stack)
41       (type-size dls (cadr e))
42       wordsize))
43
44 (define (on-stack? expr)
45   (case (ast-type expr)
46     ['stack (cadr expr)]
47     [else #f]))
48
49                                         ; does a movsq for something on the stack
50                                         ; src points to the start stack index, but not the top of that index
51                                         ; likewise for dst
52                                         ; | ...  |
53                                         ; +------+ <-- to here
54                                         ; | tag0 |
55                                         ; +------+ <-- src (size = 16)
56                                         ; |  42  |
57                                         ; +------+ <-- start copying from here...
58 (define (emit-stack-copy src dst size)
59   (let ([size-to-copy (- size wordsize)])
60     (emit "leaq ~a(%rbp), %rsi" (- src size-to-copy))
61     (emit "leaq ~a(%rbp), %rdi" (- dst size-to-copy))
62     (emit "movq $~a, %rcx" (/ size wordsize))
63     (emit "rep movsq")))
64   
65
66                                         ; an environment consists of adt layouts in scope,
67                                         ; and any bound variables.
68                                         ; bound variables are an assoc list with their stack offset
69 (define make-env list)
70 (define env-data-layouts car)
71 (define env-bindings cadr)
72 (define (env-append-bindings env bindings)
73   (make-env (env-data-layouts env)
74             (append bindings (env-bindings env))))
75
76 (define (codegen-add xs si env)
77   (define (go ys)
78     (if (null? ys)
79         (emit "movq ~a(%rbp), %rax" si)
80         (begin
81           (let ((y (car ys)))
82             (if (integer? y)
83                 (emit "addq $~a, ~a(%rbp)" y si)
84                 (begin
85                   (codegen-expr y (- si wordsize) env)
86                   (emit "addq %rax, ~a(%rbp)" si))))
87           (go (cdr ys)))))
88   (begin
89                                         ; use si(%rbp) as the accumulator
90     (emit "movq $0, ~a(%rbp)" si)
91     (go xs)))
92
93 (define (codegen-binop opcode)
94   (lambda (a b si env)
95     (codegen-expr b si env)
96     (emit "movq %rax, ~a(%rbp)" si)
97     (codegen-expr a (- si wordsize) env)
98     (emit "~a ~a(%rbp), %rax" opcode si)))
99
100 (define codegen-sub (codegen-binop "sub"))
101
102 (define codegen-mul (codegen-binop "imul"))
103
104 (define (codegen-not x si env)
105   (codegen-expr x si env)
106   (emit "notq %rax")
107   (emit "andq $1, %rax"))
108
109 (define (codegen-eq a b si env)
110   (codegen-expr a si env)
111   (emit "movq %rax, ~a(%rbp)" si)
112   (codegen-expr b (- si wordsize) env)
113   (emit "## ~a = ~b" a b)
114   (emit "cmpq ~a(%rbp), %rax" si)
115   (emit "sete %al"))
116
117                                         ; 'write file handle addr-string num-bytes
118
119 (define (codegen-print x si env)
120   (codegen-expr x si env) ; x should be a static-string, producing a label
121
122                                         ; make a copy of string address since %rax and %rdi are clobbered
123   (emit "mov %rax, %rbx")
124   
125                                         ; get the length of the null terminated string
126   (emit "mov %rax, %rdi")
127   (emit "xor %al, %al")   ; set %al to 0
128   (emit "mov $-1, %rcx") ; max search length = max int = -1
129   (emit "cld")           ; clear direction flag, search up in memory
130   (emit "repne scasb")   ; scan string, %rcx = -strlen - 1 - 1
131   
132   (emit "not %rcx")      ; -%rcx = strlen + 1
133   (emit "dec %rcx")
134   
135   (emit "movq %rbx, %rsi") ; string addr
136   (emit "movq %rcx, %rdx") ; num bytes
137   (emit "movq $1, %rdi")   ; file handle (stdout)
138   (case target
139     ('darwin (emit "mov $0x2000004, %rax")) ; syscall 4 (write)
140     ('linux  (emit "mov $1, %rax"))) ; syscall 1 (write)
141   (emit "syscall"))
142
143 (define (codegen-let bindings body si env)
144
145                                         ; is this a closure that captures itself?
146                                         ; e.g. (let ([x 3] [f (closure lambda0 (f x))]) (f))
147   (define (self-captive-closure? name expr)
148     (and (eqv? (ast-type expr) 'closure)
149          (memv name (caddr expr))))
150
151   ;; (define (emit-scc scc env)
152   ;;   ; acc is a pair of the env and list of touchups
153   ;;   (define (emit-binding acc binding)
154   ;;     (let ([binding-name (car binding)]
155   ;;        [binding-body (cadr binding)]
156
157   ;;        [other-bindings (filter
158   ;;                         (lambda (x) (not (eqv? binding-name x)))
159   ;;                         scc)]
160   ;;        [mutually-recursives
161   ;;         (filter
162   ;;          (lambda (other-binding)
163   ;;            (memv other-binding (references binding-body)))
164   ;;          other-bindings)]
165
166   ;;        [new-touchups (append touchups (cdr acc))])
167
168   ;;                                    ; TODO: assert that the only mutually recursives are closures
169   ;;    (for-each
170   ;;     (lambda (binding)
171   ;;       (when (not (eqv? (ast-type (cadr binding))
172   
173   ;;    (emit "asdf")
174   ;;    (cons new-env new-touchups)
175   ;;    ))
176
177   ;;   (fold-left emit-binding (cons env '()) scc))))
178                                         ; assoc map of binding name to size
179
180
181   (define dls (env-data-layouts env))
182   
183   (define stack-sizes
184     (map (lambda (binding) (cons (car binding) (expr-size dls (cadr binding))))
185          bindings))
186
187                                         ; assoc map of binding name to offset
188   (define stack-offsets
189                                         ; 2  4  2  8  6
190     (let* ([totals                      ; 2  6  8  16 22
191             (reverse (fold-left (lambda (acc x)
192                                   (if (null? acc)
193                                       (list x)
194                                       (cons (+ x (car acc)) acc)))
195                                 '()
196                                 (map cdr stack-sizes)))]
197                                         ; 0  2  6  8  16
198            [relative-offsets (map - totals (map cdr stack-sizes))]
199            [absolute-offsets (map (lambda (x) (- si x)) relative-offsets)])
200       (map cons (map car stack-sizes) absolute-offsets)))
201   
202   (let* (
203                                         ; the stack index used when codegening binding body and main body
204                                         ; -> stack ->
205                                         ; [stack-offsets | inner-si]
206          [inner-si (- si (fold-left + 0 (map cdr stack-sizes)))]
207
208          [get-offset (lambda (n) (cdr (assoc n stack-offsets)))]
209          
210          [inner-env
211           (fold-left
212            (lambda (env comps)
213              (let* ([scc-binding-offsets
214                      (fold-left
215                       (lambda (acc name)
216                         (cons (cons name (get-offset name))
217                               acc))
218                       (env-bindings env)
219                       comps)]
220                     [scc-env (make-env (env-data-layouts env) scc-binding-offsets)])
221                (for-each 
222                 (lambda (name)
223                   (let* ([expr (cadr (assoc name bindings))]
224                          [size (expr-size dls expr)])
225                     (emit "## generating ~a with scc-env ~a" name scc-env)
226                     (if (self-captive-closure? name expr)
227                                         ; if self-captive, insert a flag into the environment to let
228                                         ; codegen-closure realise this!
229                         (codegen-expr expr
230                                       inner-si
231                                       (make-env
232                                        (env-data-layouts scc-env)
233                                        (cons (cons name 'self-captive)
234                                              (env-bindings scc-env))))
235                         (codegen-expr expr inner-si scc-env))
236
237                     (if (on-stack? expr)
238                                                   ; copy over whatevers on the stack
239                         (emit-stack-copy inner-si (get-offset name) size)
240                         (emit "movq %rax, ~a(%rbp)" (get-offset name)))))
241                 comps)
242                scc-env))
243            env
244            (reverse (sccs (graph bindings))))])
245
246     (for-each (lambda (form)
247                 (codegen-expr form inner-si inner-env))
248               body)))
249
250 (define (codegen-var e si env)
251   (let* ([stack-type (on-stack? e)]      
252          [name (if stack-type (caddr e) e)]
253
254          [dls (env-data-layouts env)]
255          
256          [singleton? (and stack-type
257                         (assoc name
258                                (cdr (assoc stack-type dls))))]
259                                     
260          [stack-offset (assoc name (env-bindings env))])
261     (when (and (not stack-offset) (not singleton?))
262       (error #f (format "Variable ~a is not bound" name)))
263
264     (if (on-stack? e)
265         (if singleton?
266                                         ; singletons don't need to be in the environment
267                                         ; just copy over the tag
268             (emit "movq $~a, ~a(%rbp)"
269                   (data-sum-tag (env-data-layouts env)
270                                 stack-type
271                                 name)
272                   si)
273             (emit-stack-copy (cdr stack-offset) si (type-size dls stack-type)))
274         (emit "movq ~a(%rbp), %rax" (cdr stack-offset)))))
275
276 (define cur-lambda 0)
277 (define (fresh-lambda)
278   (set! cur-lambda (+ 1 cur-lambda))
279   (format "_lambda~a" (- cur-lambda 1)))
280
281                                         ; a closure on the heap looks like:
282                                         ; 0    8         16        24
283                                         ; addr var1....  var2....  var3....
284
285 (define (codegen-closure label captured si env)
286   (let* ((heap-offsets (map (lambda (i) (+ 8 (* 8 i)))
287                             (range 0 (length captured))))) ; 4, 12, 20, etc.
288
289     (emit "## creating closure")
290
291     (emit "movq heap_start@GOTPCREL(%rip), %rbx")
292     
293     (emit "movq (%rbx), %rax")          ; %rax = heap addr of closure
294
295
296                                         ; point heap_start to next space
297     (emit "addq $~a, (%rbx)" (+ 8 (* 8 (length captured))))
298
299     (emit "## storing address to lambda")
300                                         ; store the address to the lambda code
301     (emit "movq ~a@GOTPCREL(%rip), %rbx" label)
302     (emit "movq %rbx, 0(%rax)")
303
304     (emit "## storing captives")
305                                         ; store the captured vars
306     (for-each
307      (lambda (var-name heap-offset)
308        (let ([stack-offset (cdr (assoc var-name (env-bindings env)))])
309          (emit "### captive ~a" var-name)
310          (if (eqv? stack-offset 'self-captive)
311                                         ; captive refers to this closure:
312                                         ; move heap addr of this closure to stack! 
313              (emit "movq %rax, ~a(%rax)" heap-offset)
314              (begin
315                (emit "movq ~a(%rbp), %rbx" stack-offset)
316                (emit "movq %rbx, ~a(%rax)" heap-offset)))))
317      captured
318      heap-offsets)))
319
320                                         ; for now we can only call closures
321 (define (codegen-call f args si env)
322   (codegen-expr f si env)
323
324   (emit "## starting call")
325   
326   (emit "movq %rax, ~a(%rbp)" si) ; store address of closure first on stack
327   
328                                         ; codegen the arguments, store them intermediately
329   (for-each
330    (lambda (e i)
331      (begin
332        (emit "## arg no. ~a" (- i 1))
333        (codegen-expr e (- si (* wordsize i)) env)
334                                         ; store intermediate result on stack
335        (emit "movq %rax, ~a(%rbp)" (- si (* wordsize i)))))
336
337    args (range 1 (length args)))
338
339                                         ; now that we have everything we need on the stack,
340                                         ; move them into the param registers
341
342   (emit "## moving args into place")
343   (for-each
344    (lambda (i) (emit "movq ~a(%rbp), ~a"
345                      (- si (* wordsize i))
346                      (param-register i)))
347    (range 1 (length args)))
348
349                                         ; todo: can this be made more efficient
350   (emit "movq ~a(%rbp), %rax" si)       ; load back pointer to closure
351
352   (emit "## moving captives into place")
353   
354                                         ; move captives into first argument
355   (emit "movq %rax, %rbx")
356   (emit "addq $8, %rbx")
357   (emit "movq %rbx, ~a" (param-register 0))
358
359   (emit "## performing call")
360
361   (emit "addq $~a, %rsp" si) ; adjust the stack pointer to account all the stuff we put in the env
362   (emit "callq *(%rax)")                ; call closure function
363   (emit "subq $~a, %rsp" si))
364
365                                         ; LAMBDAS:
366                                         ; 1st param: pointer to captured args
367                                         ; 2nd param: 1st arg
368                                         ; 3rd param: 2nd arg, etc.
369
370 (define (codegen-lambda l)
371   (let* ((label (car l))
372          (stuff (cdr l))
373          (captives (car stuff))
374          (args (cadr stuff))
375          (body (caddr stuff))
376                                         ; params = what actually gets passed
377          (params (append captives args))
378
379          (stack-offsets (map (lambda (i)
380                                (* (- wordsize) (+ 1 i)))
381                              (range 0 (length params))))
382
383          [bindings (map cons params stack-offsets)]
384          [env (make-env '() bindings)])
385     (emit "~a:" label)
386
387     (display "## lambda captives: ")
388     (display captives)
389     (newline)
390     (display "## lambda args: ")
391     (display args)
392     (newline)
393     (display "## lambda body: ")
394     (display body)
395     (newline)
396     
397     (emit "push %rbp") ; preserve caller's base pointer
398     
399     (emit "movq %rsp, %rbp") ; set up our own base pointer
400
401                                         ; load the captured vars onto the stack
402     (for-each
403      (lambda (i)
404        (begin
405          (emit "# loading captive ~a" (list-ref captives i))
406          (emit "movq ~a(~a), %rbx" (* wordsize i) (param-register 0))
407          (emit "movq %rbx, ~a(%rbp)" (* (- wordsize) (+ 1 i)))))
408      (range 0 (length captives)))
409
410                                         ; load the args onto the stack
411     (for-each
412      (lambda (i)
413        (begin
414          (emit "movq ~a, %rbx" (param-register (+ 1 i)))
415          (emit "movq %rbx, ~a(%rbp)"
416                (* (- wordsize)
417                   (+ 1 (length captives) i)))))
418      (range 0 (length args)))
419     
420     (codegen-expr body (* (- wordsize) (+ 1 (length params))) env)
421
422     (emit "pop %rbp") ; restore caller's base pointer
423     (emit "ret")))
424
425 (define cur-label 0)
426 (define (fresh-label)
427   (set! cur-label (+ 1 cur-label))
428   (format "label~a" (- cur-label 1)))
429
430 (define (codegen-if cond then else si env)
431   (codegen-expr cond si env)
432   (emit "cmpq $0, %rax")
433   (let ((exit-label (fresh-label))
434         (else-label (fresh-label)))
435     (emit "je ~a" else-label)
436     (codegen-expr then si env)
437     (emit "jmp ~a" exit-label)
438     (emit "~a:" else-label)
439     (codegen-expr else si env)
440     (emit "~a:" exit-label)))
441
442 (define (codegen-case switch cases si env)
443   (define dls (env-data-layouts env))
444   (define exit-label (fresh-label))
445
446
447                                         ; checks if equal and returns assoc list of bindings
448   (define (check-equal jne-label type inner-offset x)
449
450                                         ; TODO: tidy this up! comparibles and binds could be merged
451                                         ; (foo a 2 (bar x)) -> ((2 Int 1) ((bar x) A 2))
452                                         ; sum: foo
453     (define (comparibles sum)
454       (let ([product-types (cdr (assoc sum (cdr (assoc type dls))))])
455         (if (null? product-types)
456             '()
457             (filter (lambda (x) (not (eqv? 'var (ast-type (car x)))))
458                     (map (lambda (x t i) (list x t i))
459                          (cdr x)
460                          product-types
461                          (range 0 (length product-types)))))))
462     
463     (define (binds sum)
464       (let ([product-types (cdr (assoc sum (cdr (assoc type dls))))])
465         (if (null? product-types)
466             '()
467             (filter (lambda (x) (eqv? 'var (ast-type (car x))))
468                     (map (lambda (x i)
469                            (cons x
470                                  (- inner-offset
471                                     (data-product-offset dls type sum i))))
472                          (cdr x)
473                          (range 0 (length (cdr x))))))))
474              
475
476     (let ([sums (assoc type dls)])
477       (if sums
478           (let* ([sum (if (list? x) (car x) x)] ; can sometimes be a singleton
479                  [tag (data-sum-tag dls type sum)])
480                                         ; the tag is at the top (beginning) of the adt on the stack
481             (emit "cmpq $~a, ~a(%rbp)" tag inner-offset)
482             (emit "jne ~a" jne-label)
483
484             (append (binds sum)
485              (flat-map
486              (lambda (cmp) ; cmp = (x type index)
487                (check-equal jne-label
488                             (cadr cmp)
489                             (- inner-offset (data-product-offset dls type sum (caddr cmp)))
490                             (car cmp)))
491              (comparibles sum))))
492           (if (eqv? 'var (ast-type x))
493               (list (cons x inner-offset))
494               (begin
495                 (emit "cmp $~a, ~a(%rbp)" x inner-offset)
496                 (emit "jne ~a" jne-label)
497                 '() )))))
498   
499   (define (codegen-adt-match type case)
500     (let* ([match (car case)]
501            [expr (cadr case)]
502            [next-section-label (fresh-label)]
503            [inner-si (- si (type-size dls type))]
504            [new-env (env-append-bindings env
505                      (check-equal next-section-label type si match))])
506
507
508       (codegen-expr expr inner-si new-env)
509       (emit "jmp ~a" exit-label)
510
511       (emit "~a:" next-section-label)))
512
513   (define (codegen-literal-match case)
514     (let ([next-section-label (fresh-label)])
515       (emit "cmpq $~a, %rax" (car case))
516       (emit "jne ~a" next-section-label)
517       (codegen-expr (cadr case) si env)
518       (emit "jmp ~a" exit-label)
519       (emit "~a:" next-section-label)))
520   
521                                         ; generate the switch
522                                         ; (and store it on the stack if not a stack value)
523   (codegen-expr switch si env)
524
525   (if (eqv? 'stack (ast-type switch))
526                                         ; adt pattern match
527       (for-each (lambda (x) (codegen-adt-match (cadr switch) x)) cases)
528       (for-each codegen-literal-match cases))
529   (emit "~a:" exit-label))
530       
531
532 (define (data-tor env e)
533   (if (not (list? e)) #f    
534       (assoc (car e) (flat-map data-tors (env-data-layouts env)))))
535
536                                         ; returns the internal offset in bytes of a product within an ADT
537                                         ; given the constructor layout
538                                         ; constructor-layout: (foo (Int Bool))
539 (define (data-product-offset data-layouts type sum index)
540   (let* ([products (cdr (assoc sum (cdr (assoc type data-layouts))))]
541          [to-traverse (list-head products index)])
542     (fold-left
543      (lambda (acc t) (+ acc (type-size data-layouts t)))
544      wordsize ; skip the tag in the first word
545      to-traverse)))
546
547 (define (data-sum-tag data-layouts type sum)
548
549   (define (go acc sums)
550     (when (null? sums) (error #f "data-sum-tag no sum for type" sum type))
551     (if (eqv? sum (car sums))
552         acc
553         (go (+ 1 acc) (cdr sums))))
554   (let* ([type-sums (cdr (assoc type data-layouts))])
555     (go 0 (map car type-sums))))
556
557 (define (codegen-data-tor e si env)
558
559   (define dls (env-data-layouts env))
560
561   (define (codegen-destructor tor)
562     (let* ([res (codegen-expr (cadr e) si env)]
563            [info (cadr tor)]
564            [type (car info)]
565            [sum (cadr info)]
566            [index (caddr info)]
567            [product-type (cadddr info)]
568            [product-type-size (type-size dls product-type)]
569
570            [safe-space-offset (- si (type-size dls type))]
571
572            [inner-offset (- si (data-product-offset dls type sum index))])
573       
574       (when (not (on-stack? (cadr e)))
575         (error #f "trying to destruct something that isn't a stack expression"))      
576       (emit "# deconstructing")
577
578       (if (stack-type? (env-data-layouts env) product-type)
579                                         ; if copying from the stack, need to first copy
580                                         ; to a safe space above to avoid overwriting
581                                         ; the original result on the stack
582                                         ; this is bad. please remove this in the rewrite.
583           (begin
584             (emit-stack-copy inner-offset safe-space-offset product-type-size)
585             (emit-stack-copy safe-space-offset si product-type-size))
586           (emit "movq ~a(%rbp), %rax" inner-offset))))
587
588   (define (codegen-constructor tor)
589     (let* ([info (cadr tor)]
590            [type (car info)]
591            [sum (cadr info)]
592            [constructor (car e)]
593
594            [args (cdr e)]
595
596            [tag (data-sum-tag (env-data-layouts env)
597                               type
598                               sum)]
599
600            [inner-si (- si (type-size dls type))]
601
602            [product-types (cdr (assoc sum (cdr (assoc type dls))))]
603            
604            [insert-product
605             (lambda (expr i product-type)
606               (let ([dest-offset
607                      (- si (data-product-offset dls type sum i))]
608                     [product-size (type-size dls product-type)])
609                 (codegen-expr expr inner-si env)
610                 (if (on-stack? expr)
611                     (emit-stack-copy inner-si dest-offset product-size)
612                     (emit "movq %rax, ~a(%rbp)" dest-offset))))])
613            
614                                         ; emit the tag
615       (emit "movq $~a, ~a(%rbp)" tag si)     
616                                         ; generate products
617       (for-each insert-product args (range 0 (length args)) product-types)))
618   
619   (let* ([tor (data-tor env e)]
620          [constructor (eqv? 'constructor (caddr (cadr tor)))])
621     (if constructor
622         (codegen-constructor tor)
623         (codegen-destructor tor))))
624
625 (define (codegen-expr e si env)
626   (emit "# ~a" e)
627   (case (ast-type e)
628     ('closure (codegen-closure (cadr e) (caddr e) si env))
629     ('app
630      (case (car e)
631        ('+ (codegen-add (cdr e) si env))
632        ('- (codegen-sub (cadr e) (caddr e) si env))
633        ('* (codegen-mul (cadr e) (caddr e) si env))
634        ('! (codegen-not (cadr e) si env))
635        ('= (codegen-eq  (cadr e) (caddr e) si env))
636        ('bool->int (codegen-expr (cadr e) si env))
637        ('print (codegen-print (cadr e) si env))
638        (else
639         (if (data-tor env e)
640             (codegen-data-tor e si env)
641             (codegen-call (car e) (cdr e) si env)))))
642
643                                         ; this is a builtin being passed around as a variable
644                                         ; this should have been converted to a closure!
645     ('builtin (error #f "passing about a builtin!" e))
646
647     ('let (codegen-let (let-bindings e)
648                        (let-body e)
649                        si
650                        env))
651
652     ('var (codegen-var e si env))
653
654     ('if (codegen-if (cadr e) (caddr e) (cadddr e) si env))
655     ('case (codegen-case (case-switch e) (case-cases e) si env))
656     
657     ('bool-literal (emit "movq $~a, %rax" (if e 1 0)))
658     ('int-literal (emit "movq $~a, %rax" e))
659     
660     ('static-string (emit "movq ~a@GOTPCREL(%rip), %rax"
661                           (cadr e)))
662
663     ('stack (case (ast-type (caddr e))
664               ['var (codegen-var e si env)]
665               [else (codegen-expr (caddr e) si env)]))
666
667     (else (error #f "don't know how to codegen this")))
668   (emit "# done ~a" e))
669
670                                         ; takes in a expr annotated with types and returns a type-less AST
671                                         ; with stack values wrapped
672 (define (annotate-stack-values data-layouts ann-e)
673   (define (stack-type? type)
674     (assoc type data-layouts))
675   (define (strip e)
676     (ast-traverse strip (ann-expr e)))
677   (let* ([e (ann-expr ann-e)]
678          [type (ann-type ann-e)])
679     (if (stack-type? type)
680         `(stack ,type
681                 ,(ast-traverse (lambda (x) (annotate-stack-values data-layouts x)) e))
682         (ast-traverse (lambda (x)
683                         (annotate-stack-values data-layouts x))
684                       e))))
685
686 (define (free-vars prog)
687   (define bound '())
688   (define (collect e)
689     (case (ast-type e)
690       ('builtin '()) ; do nothing
691       ('var (if (memv e bound) '() (list e)))
692       ('lambda
693           (begin
694             (set! bound (append (lambda-args e) bound))
695             (collect (lambda-body e))))
696
697       ('app (flat-map collect e))
698       ('if (flat-map collect (cdr e)))
699       ('let
700           (let ([bind-fvs (flat-map (lambda (a)
701                                       (begin
702                                         (set! bound (cons (car a) bound))
703                                         (collect (cdr a))))
704                                     (let-bindings e))])
705             (append bind-fvs (flat-map collect (let-body e)))))
706       (else '())))
707   (collect prog))
708
709                                         ; ((lambda (x) (+ x y)) 42) => ((closure lambda1 (y)) 42)
710                                         ;                              [(lambda1 . ((y), (x), (+ x y))]
711                                         ; for builtins, this generates a closure if it is used
712                                         ; outside of an immediate app
713                                         ; but only one closure for each builtin
714
715 (define (extract-lambdas program)
716   (define lambdas '())
717   (define (add-lambda e)
718     (let* ((label (fresh-lambda))
719            (args (lambda-args e))
720            (captured (free-vars e))
721            (body (extract (lambda-body e)))
722            (new-lambda (cons label (list captured args body))))
723       (set! lambdas (cons new-lambda lambdas))
724       `(closure ,label ,captured))) ; todo: should we string->symbol?
725
726   (define (find-builtin-lambda e)
727     (let [(l (assq (builtin-name e) lambdas))]
728       (if l `(closure ,(car l) ,(caadr l)) #f)))
729
730   (define (builtin-name e)
731     (case e
732       ('+ "_add")
733       ('- "_sub")
734       ('* "_mul")
735       ('! "_not")
736       ('= "_eq")
737       ('bool->int "_bool2int")
738       ('print "_print")
739       (else (error #f "don't know this builtin"))))
740   (define (builtin-args e)
741     (case e
742       ('+ '(x y))
743       ('- '(x y))
744       ('* '(x y))
745       ('! '(x))
746       ('= '(x y))
747       ('bool->int '(x))
748       ('print '(x))
749       (else (error #f "don't know this builtin"))))
750
751   (define (add-builtin-lambda e)
752     (let* [(label (builtin-name e))
753            (captured '())
754            (args (builtin-args e))
755            (body `(,e ,@args))
756            (new-lambda (cons label (list captured args body)))]
757       (set! lambdas (cons new-lambda lambdas))
758       `(closure ,label ,captured)))
759   
760   (define (extract e)
761     (case (ast-type e)
762       ('lambda (add-lambda e))
763       ('let `(let ,(map (lambda (b) `(,(car b) ,@(extract (cdr b)))) (let-bindings e))
764                ,@(map extract (let-body e))))
765       ('app (append
766                                         ; if a builtin is used as a function, don't generate lambda
767              (if (eqv? 'builtin (ast-type (car e)))
768                  (list (car e))
769                  (list (extract (car e))))
770              (map extract (cdr e))))
771       
772       ('builtin
773        (if (find-builtin-lambda e)
774            (find-builtin-lambda e)
775            (add-builtin-lambda e)))
776
777       
778       (else (ast-traverse extract e))))
779   (let ((transformed (extract program)))
780     (cons lambdas transformed)))
781
782 (define (extract-strings program)
783   (let ((cur-string 0)
784         (strings '())) ; assoc list of labels -> string
785     (define (fresh-string)
786       (set! cur-string (+ cur-string 1))
787       (format "string~a" (- cur-string 1)))
788     (define (extract e)
789       (case (ast-type e)
790         ('string-literal
791          (let ((label (fresh-string)))
792            (set! strings (cons (cons label e) strings))
793            `(static-string ,label)))
794         (else (ast-traverse extract e))))
795     (let ((transformed (extract program)))
796       (cons strings transformed))))
797
798 (define (emit-string-data s)
799   (emit "~a:" (car s))
800   (emit "\t.string \"~a\"" (cdr s)))
801
802                                         ; 24(%rbp) mem arg 1
803                                         ; 16(%rbp) mem arg 0          prev frame
804                                         ; -----------------------
805                                         ;  8(%rbp) return address     cur frame
806                                         ;  0(%rbp) prev %rbp
807                                         ; -8(%rbp) do what you want
808                                         ;  ...     do what you want
809                                         ;  0(%rsp) do what you want
810
811 (define (param-register n)
812   (case n
813     (0 "%rdi")
814     (1 "%rsi")
815     (2 "%rdx")
816     (3 "%rcx")
817     (4 "%r8")
818     (5 "%r9")
819     (else (error #f "need to test out the below"))
820     (else (format "~a(%rsp)" (- n 6)))))
821
822 (define (initialize-heap)
823   (let ((mmap
824          (case target
825            ('darwin "0x20000c5")
826            ('linux "9"))))
827                                         ; allocate some heap memory
828     (emit "mov $~a, %rax" mmap) ; mmap
829     (emit "xor %rdi, %rdi")  ; addr = null
830     (emit "movq $1024, %rsi")   ; length = 1kb
831     (emit "movq $0x3, %rdx") ; prot = read | write = 0x2 | 0x1
832                                         ;    flags = anonymous | private
833     (case target
834       ('darwin (emit "movq $0x1002, %r10")) ; anon = 0x1000, priv = 0x02
835       ('linux (emit "movq $0x22, %r10")))   ; anon = 0x20,   priv = 0x02
836     (emit "movq $-1, %r8") ; fd = -1
837     (emit "xor %r9, %r9") ; offset = 0
838     (emit "syscall")
839                                         ; %rax now contains pointer to the start of the heap
840                                         ; keep track of it
841
842     (emit "movq heap_start@GOTPCREL(%rip), %rsi")
843     (emit "movq %rax, (%rsi)")))
844
845 (define (codegen program)
846   (set! cur-label 0)
847   (set! cur-lambda 0)
848   (let* ([data-layouts (program-data-layouts program)]
849
850          [pattern-matched (expand-pattern-matches program)]
851          [type-annotated (annotate-types pattern-matched)]
852          [stack-annotated (annotate-stack-values data-layouts
853                                                  type-annotated)]
854          
855          (strings-res (extract-strings stack-annotated))
856          (strings (car strings-res))
857          (lambdas-res (extract-lambdas (cdr strings-res)))
858          (lambdas (car lambdas-res))
859          (xform-prog (cdr lambdas-res)))
860
861     (emit "\t.global _start")
862     (emit "\t.text")
863                                         ;    (emit ".p2align 4,,15") is this needed?
864
865     (for-each codegen-lambda lambdas)
866
867     (emit "_start:")
868
869     (initialize-heap)
870
871     (emit "movq %rsp, %rbp")            ; set up the base pointer
872     
873     (codegen-expr xform-prog (- wordsize) (make-env data-layouts '()))
874
875                                         ; exit syscall
876     (emit "mov %rax, %rdi")
877     (case target
878       ('darwin (emit "movq $0x2000001, %rax"))
879       ('linux (emit "mov $60, %rax")))
880     (emit "syscall")
881
882     (emit ".data")
883
884     (emit "heap_start:")
885     (emit "\t.quad 0")
886
887     (for-each emit-string-data strings)))
888
889 (define (compile-to-binary program output t)
890   (set! target t)
891   (when (not (eq? (typecheck program) 'Int)) (error #f "not an Int"))
892   (let ([tmp-path "/tmp/a.s"])
893     (when (file-exists? tmp-path) (delete-file tmp-path))
894     (with-output-to-file tmp-path
895       (lambda () (codegen program)))
896
897     (case target
898       ('darwin
899        (system "as /tmp/a.s -o /tmp/a.o")
900        (system (format "ld /tmp/a.o -e _start -macosx_version_min 10.14 -static -o ~a" output)))
901       ('linux
902        (system "as /tmp/a.s -o /tmp/a.o")
903        (system (format "ld /tmp/a.o -o ~a" output))))))
904
905 ; NOTES
906 ; syscalls in linux and darwin use the following arguments for syscall instruction:
907 ; %rax = syscall #
908 ; %rdi = 1st arg
909 ; %rsi = 2nd arg
910 ; %rdx = 3rd arg
911 ; %r10 = 4th arg
912 ; %r8  = 5th arg
913 ; %r9  = 6th arg
914
915 ; on darwin, unix/posix syscalls are offset by 0x2000000 (syscall classes)
916 ; https://opensource.apple.com/source/xnu/xnu-2782.20.48/bsd/kern/syscalls.master
917 ; documentation for most syscalls: /Applications/Xcode.app/Contents/Developer/Platforms/MacOSX.platform/Developer/SDKs/MacOSX.sdk/usr/include/sys