Start work on collecting all bindings when typechecking nested pattern match
[scheme.git] / typecheck.scm
1 (load "ast.scm")
2
3 (define (abs? t)
4   (and (list? t) (eq? (car t) 'abs)))
5
6 (define (tvar? t)
7   (and (not (list? t))
8        (not (concrete? t))
9        (symbol? t)))
10
11 (define (concrete? t)
12   (and (symbol? t)
13        (char-upper-case? (string-ref (symbol->string t) 0))))
14
15 (define (pretty-type t)
16   (cond ((abs? t)
17          (string-append
18           (if (abs? (cadr t))
19               (string-append "(" (pretty-type (cadr t)) ")")
20               (pretty-type (cadr t)))
21           " -> "
22           (pretty-type (caddr t))))
23         (else (symbol->string t))))
24
25 (define (pretty-constraints cs)
26   (string-append "{"
27                  (fold-left string-append
28                             ""
29                             (map (lambda (c)
30                                    (string-append
31                                     (pretty-type (car c))
32                                     ": "
33                                     (pretty-type (cdr c))
34                                     ", "))
35                                  cs))
36                  "}"))
37
38                                         ; ('a, ('b, 'a))
39 (define (env-lookup env n)
40   (if (null? env) (error #f "empty env" env n)                  ; it's a type equality
41       (if (eq? (caar env) n)
42           (cdar env)
43           (env-lookup (cdr env) n))))
44
45 (define (env-insert env n t)
46   (cons (cons n t) env))
47
48 (define abs-arg cadr)
49
50 (define cur-tvar 0)
51 (define (fresh-tvar)
52   (begin
53     (set! cur-tvar (+ cur-tvar 1))
54     (string->symbol
55      (string-append "t" (number->string (- cur-tvar 1))))))
56
57 (define (last xs)
58   (if (null? (cdr xs))
59       (car xs)
60       (last (cdr xs))))
61
62 (define (normalize prog) ; (+ a b) -> ((+ a) b)
63   (case (ast-type prog)
64     ('lambda 
65                                         ; (lambda (x y) (+ x y)) -> (lambda (x) (lambda (y) (+ x y)))
66         (if (> (length (lambda-args prog)) 1)       
67             (list 'lambda (list (car (lambda-args prog)))
68                   (normalize (list 'lambda (cdr (lambda-args prog)) (caddr prog))))
69             (list 'lambda (lambda-args prog) (normalize (caddr prog)))))
70     ('app
71      (if (null? (cddr prog))
72          `(,(normalize (car prog)) ,(normalize (cadr prog))) ; (f a)
73          (normalize `(,(list (normalize (car prog)) (normalize (cadr prog)))
74                       ,@(cddr prog))))) ; (f a b)
75     ('let
76         (append (list 'let
77                       (map (lambda (x) `(,(car x) ,(normalize (cadr x))))
78                            (let-bindings prog)))
79                 (map normalize (let-body prog))))
80     (else (ast-traverse normalize prog))))
81
82 (define (builtin-type x)
83   (case x
84     ('+ '(abs Int (abs Int Int)))
85     ('- '(abs Int (abs Int Int)))
86     ('* '(abs Int (abs Int Int)))
87     ('! '(abs Bool Bool))
88     ('= '(abs Int (abs Int Bool)))
89     ('bool->int '(abs Bool Int))
90     ('print '(abs String Void))
91     (else (error #f "Couldn't find type for builtin" x))))
92
93 (define (check-let dls env x)
94
95   ; acc is a pair of (env . annotated bindings)
96   (define (process-component acc comps)
97     (let*
98                                         ; create a new env with tvars for each component
99                                         ; e.g. scc of (x y)
100                                         ; scc-env = ((x . t0) (y . t1))
101         ([scc-env
102           (fold-left
103            (lambda (acc c)
104              (env-insert acc c (fresh-tvar)))
105            (car acc) comps)]
106                                         ; typecheck each component
107          [type-results
108           (map
109            (lambda (c)
110              (let ([body (cadr (assoc c (let-bindings x)))])
111                (check dls scc-env body)))
112            comps)]
113                                         ; collect all the constraints in the scc
114          [cs
115           (fold-left
116            (lambda (acc res c)
117              (constraint-merge
118               (constraint-merge
119                                         ; unify with tvars from scc-env
120                                         ; result ~ tvar
121                (~ (env-lookup scc-env c) (cadr res))
122                (car res))                                 
123               acc))
124            '() type-results comps)]
125                                         ; substitute *only* the bindings in this scc
126          [new-env
127           (map (lambda (x)
128                  (if (memv (car x) comps)
129                      (cons (car x) (substitute cs (cdr x)))
130                      x))
131                scc-env)]
132
133          [annotated-bindings (append (cdr acc) ; the previous annotated bindings
134                                      (map list
135                                           comps
136                                           (map caddr type-results)))])
137       (cons new-env annotated-bindings)))
138                                         ; takes in the current environment and a scc
139                                         ; returns new environment with scc's types added in
140   (let* ([components (reverse (sccs (graph (let-bindings x))))]
141          [results (fold-left process-component (cons env '()) components)]
142          [new-env (car results)]
143          [annotated-bindings (cdr results)]
144
145          [body-results (map (lambda (body) (check dls new-env body)) (let-body x))]
146          [let-type (cadr (last body-results))]
147          [cs (fold-left (lambda (acc cs) (constraint-merge acc cs)) '() (map car body-results))]
148
149          [annotated `((let ,annotated-bindings ,@(map caddr body-results)) : ,let-type)])
150     (list cs let-type annotated)))
151
152 (define (check-app dls env x)
153   (if (eqv? (car x) (cadr x))
154                                         ; recursive function (f f)
155                                         ; TODO: what about ((f a) f)????
156       (let* ([func-type (env-lookup env (car x))]
157              [return-type (fresh-tvar)]
158              [other-func-type `(abs ,func-type ,return-type)]
159              [cs (~ func-type other-func-type)]
160              [resolved-return-type (substitute cs return-type)]
161
162              [annotated `(((,(car x) : ,func-type)
163                            (,(cadr x) : ,func-type)) : ,resolved-return-type)])
164         (list cs resolved-return-type annotated)))
165
166                                         ; regular function
167   (let* ([arg-type-res (check dls env (cadr x))]
168          [arg-type (cadr arg-type-res)]
169          [func-type-res (check dls env (car x))]
170          [func-type (cadr func-type-res)]
171          
172                                         ; f ~ a -> t0
173          [func-c (~
174                   (substitute (car arg-type-res) func-type)
175                   `(abs ,arg-type ,(fresh-tvar)))]
176          [cs (constraint-merge
177               (constraint-merge func-c (car arg-type-res))
178               (car func-type-res))]
179          
180          [resolved-func-type (substitute cs func-type)]
181          [resolved-return-type (caddr resolved-func-type)]
182
183          [annotated `((,(caddr func-type-res)
184                        ,(caddr arg-type-res)) : ,resolved-return-type)])
185
186     (if (abs? resolved-func-type)
187         (let ((return-type (substitute cs (caddr resolved-func-type))))
188           (list cs return-type annotated))
189         (error #f "not a function"))))
190
191 (define (check-case dls env x)
192
193   (define (check-match switch-type x)
194     
195     (define (get-bindings product-types pattern)
196       (define (go product-type product)
197              (case (ast-type x)
198                ['var (list (cons product product-type))]
199                                         ; an inner pattern match
200                ['app (get-bindings product-type product)]))
201       (flat-map go product-types (cdr pattern)))
202
203     
204     (let ([pattern (car x)]
205           [expr (cadr x)])
206       (case (ast-type pattern)
207         ['app
208                                         ; a pattern match with bindings
209           (let ([sum (assoc (car pattern) (cdr (assoc switch-type dls)))])
210             (unless sum (error #f "can't pattern match ~a with ~a" switch-type pattern))
211             (let* ([names (cdr pattern)]
212                    [product-types (cdr sum)]
213                    [new-env (append (get-bindings product-types pattern) env)])
214               (check dls new-env expr)))]
215                                         ; pattern match with binding and no constructor
216         ['var (check dls (env-insert env pattern switch-type) expr)]
217                                         ; a pattern match without bindings
218         [else (check dls env expr)])))
219   
220   (let* ([switch-type-res (check dls env (case-switch x))]
221          [switch-type (cadr switch-type-res)]
222          
223          [case-expr-type-res (map (lambda (x) (check-match switch-type x)) (case-cases x))]
224          [case-expr-types (map cadr case-expr-type-res)]
225
226          [case-expr-equality-cs (fold-left constraint-merge '()
227                                            (map (lambda (t) (~ t (car case-expr-types)))
228                                                 (cdr case-expr-types)))]
229
230          [resolved-type (substitute case-expr-equality-cs (car case-expr-types))]
231
232          [annotated `((case ,(caddr switch-type-res)
233                         ,@(map (lambda (c e et)
234                                  `(,c ((,e : ,et))))
235                                (map car (case-cases x))
236                                (map cadr (case-cases x))
237                                case-expr-types)) : ,resolved-type)]
238          
239          [cs (fold-left constraint-merge '()
240                         (cons (car switch-type-res) case-expr-equality-cs))])
241     (list cs resolved-type annotated)))
242
243 ; returns a list (constraints type annotated)
244 (define (check dls env x)
245   (define (make-result cs type)
246     (list cs type `(,x : ,type)))
247   ;; (display "check: ")
248   ;; (display x)
249   ;; (display "\n\t")
250   ;; (display env)
251   ;; (newline)
252   (let
253       ((res
254         (case (ast-type x)
255           ('int-literal (make-result '() 'Int))
256           ('bool-literal (make-result '() 'Bool))
257           ('string-literal (make-result '() 'String))
258           ('builtin (make-result '() (builtin-type x)))
259
260           ('if
261            (let* ((cond-type-res (check dls env (cadr x)))
262                   (then-type-res (check dls env (caddr x)))
263                   (else-type-res (check dls env (cadddr x)))
264                   (then-eq-else-cs (~ (cadr then-type-res)
265                                       (cadr else-type-res)))
266                   (cs (constraint-merge
267                        (car then-type-res)
268                        (constraint-merge (~ (cadr cond-type-res) 'Bool)
269                                          (constraint-merge (car else-type-res)
270                                                            then-eq-else-cs))))
271                   (return-type (substitute cs (cadr then-type-res)))          
272                   [annotated `((if ,(caddr cond-type-res)
273                                    ,(caddr then-type-res)
274                                    ,(caddr else-type-res)) : ,return-type)])
275              (list cs return-type annotated)))
276           
277           ('var (make-result '() (env-lookup env x)))
278           ('let (check-let dls env x))
279
280           
281           ('lambda
282               (let* ([new-env (env-insert env (lambda-arg x) (fresh-tvar))]
283
284                      [body-type-res (check dls new-env (lambda-body x))]
285                      [cs (car body-type-res)]
286                      [subd-env (substitute-env (car body-type-res) new-env)]
287                      [arg-type (env-lookup subd-env (lambda-arg x))]
288                      [resolved-arg-type (substitute cs arg-type)]
289
290                      [lambda-type `(abs ,resolved-arg-type ,(cadr body-type-res))]
291
292                      [annotated `((lambda (,(lambda-arg x)) ,(caddr body-type-res)) : ,lambda-type)])
293                 
294                 (list (car body-type-res) ; constraints
295                       lambda-type  ; type
296                       annotated)))
297
298           
299           ('app (check-app dls env x))
300           ['case (check-case dls env x)])))
301               
302                 
303     ;; (display "result of ")
304     ;; (display x)
305     ;; (display ":\n\t")
306     ;; (display (pretty-type (cadr res)))
307     ;; (display "\n\t[")
308     ;; (display (pretty-constraints (car res)))
309     ;; (display "]\n")
310     res))
311
312 (define (init-adts-env prog)
313   (flat-map data-tors-type-env (program-data-layouts prog)))
314
315                                         ; we typecheck the lambda calculus only (only single arg lambdas)
316 (define (typecheck prog)
317   (let ([expanded (expand-pattern-matches prog)])
318     (cadr (check (program-data-layouts prog)
319                  (init-adts-env expanded)
320                  (normalize (program-body expanded))))))
321
322
323                                         ; before passing annotated types onto codegen
324                                         ; we need to restore the pre-normalization structure
325                                         ; (this is important for function arity etc)
326 (define (denormalize orig normed)
327
328   (define (collapse-lambdas n x)
329     (case n
330       [0 x]
331       [else
332        (let* ([inner-lambda (lambda-body (ann-expr x))]
333               [arg (lambda-arg (ann-expr x))]
334               [inner-collapsed (ann-expr (collapse-lambdas (- n 1) inner-lambda))])
335          `((lambda ,(cons arg (lambda-args inner-collapsed))
336              ,(lambda-body inner-collapsed)) : ,(ann-type x)))]))
337
338   (define (collapse-apps n x)
339     (case n
340       [-1 (error #f "nullary functions not handled yet")]
341       [0 x]
342       [else
343        (let* ([inner-app (car (ann-expr x))]
344               [inner-collapsed (collapse-apps (- n 1) inner-app)])
345          `(,(append (ann-expr inner-collapsed) (cdr (ann-expr x))) : ,(ann-type x)))]))
346
347   (case (ast-type orig)
348     ['lambda
349         (let ([collapsed (collapse-lambdas (- (length (lambda-args orig)) 1) normed)])
350           `((lambda ,(lambda-args (ann-expr collapsed))
351               ,(denormalize (lambda-body orig)
352                             (lambda-body (ann-expr collapsed)))) : ,(ann-type collapsed)))]
353     ['app
354      (let ([collapsed (collapse-apps (- (length orig) 2) normed)])
355        `(,(map (lambda (o n) (denormalize o n)) orig (ann-expr collapsed))
356          : ,(ann-type collapsed)))]
357     ['let
358         `((let ,(map (lambda (o n) (list (car o) (denormalize (cadr o) (cadr n))))
359                      (let-bindings orig)
360                      (let-bindings (ann-expr normed)))
361             ,@(map denormalize
362                    (let-body orig)
363                    (let-body (ann-expr normed)))) : ,(ann-type normed))]
364     ['if `((if ,@(map denormalize (cdr orig) (cdr (ann-expr normed))))
365            : ,(ann-type normed))]
366     ['case `((case ,(denormalize (case-switch orig) (case-switch (ann-expr normed)))
367                ,@(map (lambda (o n) (cons (car o) (denormalize (cadr o) (cadr n))))
368                       (case-cases orig) (case-cases (ann-expr normed))))
369              : ,(ann-type normed))]
370     [else normed]))
371
372 (define ann-expr car)
373 (define ann-type caddr)
374
375                                         ; prerequisites: expand-pattern-matches
376 (define (annotate-types prog)
377   (denormalize
378    (program-body prog)
379    (caddr (check (program-data-layouts prog)
380                  (init-adts-env prog)
381                  (normalize (program-body prog))))))
382
383   
384                                         ; returns a list of constraints
385 (define (~ a b)
386   (let ([res (unify? a b)])
387     (if res
388         res
389         (error #f
390                (format "couldn't unify ~a ~~ ~a" a b)))))
391
392 (define (unify? a b)
393   (cond [(eq? a b) '()]
394         [(tvar? a) (list (cons a b))]
395         [(tvar? b) (list (cons b a))]
396         [(and (abs? a) (abs? b))
397          (let* [(arg-cs (unify? (cadr a) (cadr b)))
398                 (body-cs (unify? (substitute arg-cs (caddr a))
399                                  (substitute arg-cs (caddr b))))]
400            (constraint-merge body-cs arg-cs))]
401         [else #f]))
402
403 (define (substitute cs t)
404   (cond
405    [(tvar? t)
406     (if (assoc t cs)
407         (cdr (assoc t cs))
408         t)]
409    [(abs? t) `(abs ,(substitute cs (cadr t))
410                    ,(substitute cs (caddr t)))]
411    [else t]))
412
413                                         ; applies substitutions to all variables in environment
414 (define (substitute-env cs env)
415   (map (lambda (x) (cons (car x) (substitute cs (cdr x)))) env))
416
417                                         ; composes constraints a onto b and merges, i.e. applies a to b
418                                         ; a should be the "more important" constraints
419 (define (constraint-merge a b)
420   (define (f cs constraint)
421     (cons (car constraint)
422           (substitute cs (cdr constraint))))
423   
424   (define (most-concrete a b)
425     (cond
426      [(tvar? a) b]
427      [(tvar? b) a]
428      [(and (abs? a) (abs? b))
429       `(abs ,(most-concrete (cadr a) (cadr b))
430             ,(most-concrete (caddr a) (caddr b)))]
431      [(abs? a) b]
432      [(abs? b) a]
433      [else a]))
434
435                                         ; for any two constraints that clash, e.g. t1 ~ abs t2 t3
436                                         ; and t1 ~ abs int t3
437                                         ; prepend the most concrete version of the type to the
438                                         ; list of constraints
439   (define (clashes)
440     (define (gen acc x)
441       (if (assoc (car x) a)
442           (cons (cons (car x) (most-concrete (cdr (assoc (car x) a))
443                                              (cdr x)))
444                 acc)
445           acc))
446     (fold-left gen '() b))
447
448   (define (union p q)
449     (append (filter (lambda (x) (not (assoc (car x) p)))
450                     q)
451             p))
452   (append (clashes) (union a (map (lambda (z) (f a z)) b))))
453
454
455 ;;                                      ; a1 -> a2 ~ a3 -> a4;
456 ;;                                      ; a1 -> a2 !~ Bool -> Bool
457 ;;                                      ; basically can the tvars be renamed
458 (define (types-equal? x y)
459   (let ([cs (unify? x y)])
460     (if (not cs) #f     
461         (let*
462             ([test (lambda (acc c)
463                      (and acc
464                           (tvar? (car c)) ; the only substitutions allowed are tvar -> tvar
465                           (tvar? (cdr c))))])
466           (fold-left test #t cs)))))
467
468                                         ; input: a list of binds ((x . y) (y . 3))
469                                         ; returns: pair of verts, edges ((x y) . (x . y))
470