fix scm_protects deprecation warning
[bpt/guile.git] / module / language / tree-il / analyze.scm
1 ;;; TREE-IL -> GLIL compiler
2
3 ;; Copyright (C) 2001, 2008, 2009, 2010, 2011 Free Software Foundation, Inc.
4
5 ;;;; This library is free software; you can redistribute it and/or
6 ;;;; modify it under the terms of the GNU Lesser General Public
7 ;;;; License as published by the Free Software Foundation; either
8 ;;;; version 3 of the License, or (at your option) any later version.
9 ;;;;
10 ;;;; This library is distributed in the hope that it will be useful,
11 ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
12 ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
13 ;;;; Lesser General Public License for more details.
14 ;;;;
15 ;;;; You should have received a copy of the GNU Lesser General Public
16 ;;;; License along with this library; if not, write to the Free Software
17 ;;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
18
19 ;;; Code:
20
21 (define-module (language tree-il analyze)
22 #:use-module (srfi srfi-1)
23 #:use-module (srfi srfi-9)
24 #:use-module (srfi srfi-11)
25 #:use-module (ice-9 vlist)
26 #:use-module (ice-9 match)
27 #:use-module (system base syntax)
28 #:use-module (system base message)
29 #:use-module (system vm program)
30 #:use-module (language tree-il)
31 #:use-module (system base pmatch)
32 #:export (analyze-lexicals
33 analyze-tree
34 unused-variable-analysis
35 unused-toplevel-analysis
36 unbound-variable-analysis
37 arity-analysis
38 format-analysis))
39
40 ;; Allocation is the process of assigning storage locations for lexical
41 ;; variables. A lexical variable has a distinct "address", or storage
42 ;; location, for each procedure in which it is referenced.
43 ;;
44 ;; A variable is "local", i.e., allocated on the stack, if it is
45 ;; referenced from within the procedure that defined it. Otherwise it is
46 ;; a "closure" variable. For example:
47 ;;
48 ;; (lambda (a) a) ; a will be local
49 ;; `a' is local to the procedure.
50 ;;
51 ;; (lambda (a) (lambda () a))
52 ;; `a' is local to the outer procedure, but a closure variable with
53 ;; respect to the inner procedure.
54 ;;
55 ;; If a variable is ever assigned, it needs to be heap-allocated
56 ;; ("boxed"). This is so that closures and continuations capture the
57 ;; variable's identity, not just one of the values it may have over the
58 ;; course of program execution. If the variable is never assigned, there
59 ;; is no distinction between value and identity, so closing over its
60 ;; identity (whether through closures or continuations) can make a copy
61 ;; of its value instead.
62 ;;
63 ;; Local variables are stored on the stack within a procedure's call
64 ;; frame. Their index into the stack is determined from their linear
65 ;; postion within a procedure's binding path:
66 ;; (let (0 1)
67 ;; (let (2 3) ...)
68 ;; (let (2) ...))
69 ;; (let (2 3 4) ...))
70 ;; etc.
71 ;;
72 ;; This algorithm has the problem that variables are only allocated
73 ;; indices at the end of the binding path. If variables bound early in
74 ;; the path are not used in later portions of the path, their indices
75 ;; will not be recycled. This problem is particularly egregious in the
76 ;; expansion of `or':
77 ;;
78 ;; (or x y z)
79 ;; -> (let ((a x)) (if a a (let ((b y)) (if b b z))))
80 ;;
81 ;; As you can see, the `a' binding is only used in the ephemeral
82 ;; `consequent' clause of the first `if', but its index would be
83 ;; reserved for the whole of the `or' expansion. So we have a hack for
84 ;; this specific case. A proper solution would be some sort of liveness
85 ;; analysis, and not our linear allocation algorithm.
86 ;;
87 ;; Closure variables are captured when a closure is created, and stored in a
88 ;; vector inline to the closure object itself. Each closure variable has a
89 ;; unique index into that vector.
90 ;;
91 ;; There is one more complication. Procedures bound by <fix> may, in
92 ;; some cases, be rendered inline to their parent procedure. That is to
93 ;; say,
94 ;;
95 ;; (letrec ((lp (lambda () (lp)))) (lp))
96 ;; => (fix ((lp (lambda () (lp)))) (lp))
97 ;; => goto FIX-BODY; LP: goto LP; FIX-BODY: goto LP;
98 ;; ^ jump over the loop ^ the fixpoint lp ^ starting off the loop
99 ;;
100 ;; The upshot is that we don't have to allocate any space for the `lp'
101 ;; closure at all, as it can be rendered inline as a loop. So there is
102 ;; another kind of allocation, "label allocation", in which the
103 ;; procedure is simply a label, placed at the start of the lambda body.
104 ;; The label is the gensym under which the lambda expression is bound.
105 ;;
106 ;; The analyzer checks to see that the label is called with the correct
107 ;; number of arguments. Calls to labels compile to rename + goto.
108 ;; Lambda, the ultimate goto!
109 ;;
110 ;;
111 ;; The return value of `analyze-lexicals' is a hash table, the
112 ;; "allocation".
113 ;;
114 ;; The allocation maps gensyms -- recall that each lexically bound
115 ;; variable has a unique gensym -- to storage locations ("addresses").
116 ;; Since one gensym may have many storage locations, if it is referenced
117 ;; in many procedures, it is a two-level map.
118 ;;
119 ;; The allocation also stored information on how many local variables
120 ;; need to be allocated for each procedure, lexicals that have been
121 ;; translated into labels, and information on what free variables to
122 ;; capture from its lexical parent procedure.
123 ;;
124 ;; In addition, we have a conflation: while we're traversing the code,
125 ;; recording information to pass to the compiler, we take the
126 ;; opportunity to generate labels for each lambda-case clause, so that
127 ;; generated code can skip argument checks at runtime if they match at
128 ;; compile-time.
129 ;;
130 ;; Also, while we're a-traversing and an-allocating, we check prompt
131 ;; handlers to see if the "continuation" argument is used. If not, we
132 ;; mark the prompt as being "escape-only". This allows us to implement
133 ;; `catch' and `throw' using `prompt' and `control', but without causing
134 ;; a continuation to be reified. Heh heh.
135 ;;
136 ;; That is:
137 ;;
138 ;; sym -> {lambda -> address}
139 ;; lambda -> (labels . free-locs)
140 ;; lambda-case -> (gensym . nlocs)
141 ;; prompt -> escape-only?
142 ;;
143 ;; address ::= (local? boxed? . index)
144 ;; labels ::= ((sym . lambda) ...)
145 ;; free-locs ::= ((sym0 . address0) (sym1 . address1) ...)
146 ;; free variable addresses are relative to parent proc.
147
148 (define (make-hashq k v)
149 (let ((res (make-hash-table)))
150 (hashq-set! res k v)
151 res))
152
153 (define (analyze-lexicals x)
154 ;; bound-vars: lambda -> (sym ...)
155 ;; all identifiers bound within a lambda
156 (define bound-vars (make-hash-table))
157 ;; free-vars: lambda -> (sym ...)
158 ;; all identifiers referenced in a lambda, but not bound
159 ;; NB, this includes identifiers referenced by contained lambdas
160 (define free-vars (make-hash-table))
161 ;; assigned: sym -> #t
162 ;; variables that are assigned
163 (define assigned (make-hash-table))
164 ;; refcounts: sym -> count
165 ;; allows us to detect the or-expansion in O(1) time
166 (define refcounts (make-hash-table))
167 ;; labels: sym -> lambda
168 ;; for determining if fixed-point procedures can be rendered as
169 ;; labels.
170 (define labels (make-hash-table))
171
172 ;; returns variables referenced in expr
173 (define (analyze! x proc labels-in-proc tail? tail-call-args)
174 (define (step y) (analyze! y proc '() #f #f))
175 (define (step-tail y) (analyze! y proc labels-in-proc tail? #f))
176 (define (step-tail-call y args) (analyze! y proc labels-in-proc #f
177 (and tail? args)))
178 (define (recur/labels x new-proc labels)
179 (analyze! x new-proc (append labels labels-in-proc) #t #f))
180 (define (recur x new-proc) (analyze! x new-proc '() tail? #f))
181 (record-case x
182 ((<application> proc args)
183 (apply lset-union eq? (step-tail-call proc args)
184 (map step args)))
185
186 ((<conditional> test consequent alternate)
187 (lset-union eq? (step test) (step-tail consequent) (step-tail alternate)))
188
189 ((<lexical-ref> gensym)
190 (hashq-set! refcounts gensym (1+ (hashq-ref refcounts gensym 0)))
191 (if (not (and tail-call-args
192 (memq gensym labels-in-proc)
193 (let ((p (hashq-ref labels gensym)))
194 (and p
195 (let lp ((c (lambda-body p)))
196 (and c (lambda-case? c)
197 (or
198 ;; for now prohibit optional &
199 ;; keyword arguments; can relax this
200 ;; restriction later
201 (and (= (length (lambda-case-req c))
202 (length tail-call-args))
203 (not (lambda-case-opt c))
204 (not (lambda-case-kw c))
205 (not (lambda-case-rest c)))
206 (lp (lambda-case-alternate c)))))))))
207 (hashq-set! labels gensym #f))
208 (list gensym))
209
210 ((<lexical-set> gensym exp)
211 (hashq-set! assigned gensym #t)
212 (hashq-set! labels gensym #f)
213 (lset-adjoin eq? (step exp) gensym))
214
215 ((<module-set> exp)
216 (step exp))
217
218 ((<toplevel-set> exp)
219 (step exp))
220
221 ((<toplevel-define> exp)
222 (step exp))
223
224 ((<sequence> exps)
225 (let lp ((exps exps) (ret '()))
226 (cond ((null? exps) '())
227 ((null? (cdr exps))
228 (lset-union eq? ret (step-tail (car exps))))
229 (else
230 (lp (cdr exps) (lset-union eq? ret (step (car exps))))))))
231
232 ((<lambda> body)
233 ;; order is important here
234 (hashq-set! bound-vars x '())
235 (let ((free (recur body x)))
236 (hashq-set! bound-vars x (reverse! (hashq-ref bound-vars x)))
237 (hashq-set! free-vars x free)
238 free))
239
240 ((<lambda-case> opt kw inits gensyms body alternate)
241 (hashq-set! bound-vars proc
242 (append (reverse gensyms) (hashq-ref bound-vars proc)))
243 (lset-union
244 eq?
245 (lset-difference eq?
246 (lset-union eq?
247 (apply lset-union eq? (map step inits))
248 (step-tail body))
249 gensyms)
250 (if alternate (step-tail alternate) '())))
251
252 ((<let> gensyms vals body)
253 (hashq-set! bound-vars proc
254 (append (reverse gensyms) (hashq-ref bound-vars proc)))
255 (lset-difference eq?
256 (apply lset-union eq? (step-tail body) (map step vals))
257 gensyms))
258
259 ((<letrec> gensyms vals body)
260 (hashq-set! bound-vars proc
261 (append (reverse gensyms) (hashq-ref bound-vars proc)))
262 (for-each (lambda (sym) (hashq-set! assigned sym #t)) gensyms)
263 (lset-difference eq?
264 (apply lset-union eq? (step-tail body) (map step vals))
265 gensyms))
266
267 ((<fix> gensyms vals body)
268 ;; Try to allocate these procedures as labels.
269 (for-each (lambda (sym val) (hashq-set! labels sym val))
270 gensyms vals)
271 (hashq-set! bound-vars proc
272 (append (reverse gensyms) (hashq-ref bound-vars proc)))
273 ;; Step into subexpressions.
274 (let* ((var-refs
275 (map
276 ;; Since we're trying to label-allocate the lambda,
277 ;; pretend it's not a closure, and just recurse into its
278 ;; body directly. (Otherwise, recursing on a closure
279 ;; that references one of the fix's bound vars would
280 ;; prevent label allocation.)
281 (lambda (x)
282 (record-case x
283 ((<lambda> body)
284 ;; just like the closure case, except here we use
285 ;; recur/labels instead of recur
286 (hashq-set! bound-vars x '())
287 (let ((free (recur/labels body x gensyms)))
288 (hashq-set! bound-vars x (reverse! (hashq-ref bound-vars x)))
289 (hashq-set! free-vars x free)
290 free))))
291 vals))
292 (vars-with-refs (map cons gensyms var-refs))
293 (body-refs (recur/labels body proc gensyms)))
294 (define (delabel-dependents! sym)
295 (let ((refs (assq-ref vars-with-refs sym)))
296 (if refs
297 (for-each (lambda (sym)
298 (if (hashq-ref labels sym)
299 (begin
300 (hashq-set! labels sym #f)
301 (delabel-dependents! sym))))
302 refs))))
303 ;; Stepping into the lambdas and the body might have made some
304 ;; procedures not label-allocatable -- which might have
305 ;; knock-on effects. For example:
306 ;; (fix ((a (lambda () (b)))
307 ;; (b (lambda () a)))
308 ;; (a))
309 ;; As far as `a' is concerned, both `a' and `b' are
310 ;; label-allocatable. But `b' references `a' not in a proc-tail
311 ;; position, which makes `a' not label-allocatable. The
312 ;; knock-on effect is that, when back-propagating this
313 ;; information to `a', `b' will also become not
314 ;; label-allocatable, as it is referenced within `a', which is
315 ;; allocated as a closure. This is a transitive relationship.
316 (for-each (lambda (sym)
317 (if (not (hashq-ref labels sym))
318 (delabel-dependents! sym)))
319 gensyms)
320 ;; Now lift bound variables with label-allocated lambdas to the
321 ;; parent procedure.
322 (for-each
323 (lambda (sym val)
324 (if (hashq-ref labels sym)
325 ;; Remove traces of the label-bound lambda. The free
326 ;; vars will propagate up via the return val.
327 (begin
328 (hashq-set! bound-vars proc
329 (append (hashq-ref bound-vars val)
330 (hashq-ref bound-vars proc)))
331 (hashq-remove! bound-vars val)
332 (hashq-remove! free-vars val))))
333 gensyms vals)
334 (lset-difference eq?
335 (apply lset-union eq? body-refs var-refs)
336 gensyms)))
337
338 ((<let-values> exp body)
339 (lset-union eq? (step exp) (step body)))
340
341 ((<dynwind> body winder unwinder)
342 (lset-union eq? (step body) (step winder) (step unwinder)))
343
344 ((<dynlet> fluids vals body)
345 (apply lset-union eq? (step body) (map step (append fluids vals))))
346
347 ((<dynref> fluid)
348 (step fluid))
349
350 ((<dynset> fluid exp)
351 (lset-union eq? (step fluid) (step exp)))
352
353 ((<prompt> tag body handler)
354 (lset-union eq? (step tag) (step body) (step-tail handler)))
355
356 ((<abort> tag args tail)
357 (apply lset-union eq? (step tag) (step tail) (map step args)))
358
359 (else '())))
360
361 ;; allocation: sym -> {lambda -> address}
362 ;; lambda -> (nlocs labels . free-locs)
363 (define allocation (make-hash-table))
364
365 (define (allocate! x proc n)
366 (define (recur y) (allocate! y proc n))
367 (record-case x
368 ((<application> proc args)
369 (apply max (recur proc) (map recur args)))
370
371 ((<conditional> test consequent alternate)
372 (max (recur test) (recur consequent) (recur alternate)))
373
374 ((<lexical-set> exp)
375 (recur exp))
376
377 ((<module-set> exp)
378 (recur exp))
379
380 ((<toplevel-set> exp)
381 (recur exp))
382
383 ((<toplevel-define> exp)
384 (recur exp))
385
386 ((<sequence> exps)
387 (apply max (map recur exps)))
388
389 ((<lambda> body)
390 ;; allocate closure vars in order
391 (let lp ((c (hashq-ref free-vars x)) (n 0))
392 (if (pair? c)
393 (begin
394 (hashq-set! (hashq-ref allocation (car c))
395 x
396 `(#f ,(hashq-ref assigned (car c)) . ,n))
397 (lp (cdr c) (1+ n)))))
398
399 (let ((nlocs (allocate! body x 0))
400 (free-addresses
401 (map (lambda (v)
402 (hashq-ref (hashq-ref allocation v) proc))
403 (hashq-ref free-vars x)))
404 (labels (filter cdr
405 (map (lambda (sym)
406 (cons sym (hashq-ref labels sym)))
407 (hashq-ref bound-vars x)))))
408 ;; set procedure allocations
409 (hashq-set! allocation x (cons labels free-addresses)))
410 n)
411
412 ((<lambda-case> opt kw inits gensyms body alternate)
413 (max
414 (let lp ((gensyms gensyms) (n n))
415 (if (null? gensyms)
416 (let ((nlocs (apply
417 max
418 (allocate! body proc n)
419 ;; inits not logically at the end, but they
420 ;; are the list...
421 (map (lambda (x) (allocate! x proc n)) inits))))
422 ;; label and nlocs for the case
423 (hashq-set! allocation x (cons (gensym ":LCASE") nlocs))
424 nlocs)
425 (begin
426 (hashq-set! allocation (car gensyms)
427 (make-hashq
428 proc `(#t ,(hashq-ref assigned (car gensyms)) . ,n)))
429 (lp (cdr gensyms) (1+ n)))))
430 (if alternate (allocate! alternate proc n) n)))
431
432 ((<let> gensyms vals body)
433 (let ((nmax (apply max (map recur vals))))
434 (cond
435 ;; the `or' hack
436 ((and (conditional? body)
437 (= (length gensyms) 1)
438 (let ((v (car gensyms)))
439 (and (not (hashq-ref assigned v))
440 (= (hashq-ref refcounts v 0) 2)
441 (lexical-ref? (conditional-test body))
442 (eq? (lexical-ref-gensym (conditional-test body)) v)
443 (lexical-ref? (conditional-consequent body))
444 (eq? (lexical-ref-gensym (conditional-consequent body)) v))))
445 (hashq-set! allocation (car gensyms)
446 (make-hashq proc `(#t #f . ,n)))
447 ;; the 1+ for this var
448 (max nmax (1+ n) (allocate! (conditional-alternate body) proc n)))
449 (else
450 (let lp ((gensyms gensyms) (n n))
451 (if (null? gensyms)
452 (max nmax (allocate! body proc n))
453 (let ((v (car gensyms)))
454 (hashq-set!
455 allocation v
456 (make-hashq proc
457 `(#t ,(hashq-ref assigned v) . ,n)))
458 (lp (cdr gensyms) (1+ n)))))))))
459
460 ((<letrec> gensyms vals body)
461 (let lp ((gensyms gensyms) (n n))
462 (if (null? gensyms)
463 (let ((nmax (apply max
464 (map (lambda (x)
465 (allocate! x proc n))
466 vals))))
467 (max nmax (allocate! body proc n)))
468 (let ((v (car gensyms)))
469 (hashq-set!
470 allocation v
471 (make-hashq proc
472 `(#t ,(hashq-ref assigned v) . ,n)))
473 (lp (cdr gensyms) (1+ n))))))
474
475 ((<fix> gensyms vals body)
476 (let lp ((in gensyms) (n n))
477 (if (null? in)
478 (let lp ((gensyms gensyms) (vals vals) (nmax n))
479 (cond
480 ((null? gensyms)
481 (max nmax (allocate! body proc n)))
482 ((hashq-ref labels (car gensyms))
483 ;; allocate lambda body inline to proc
484 (lp (cdr gensyms)
485 (cdr vals)
486 (record-case (car vals)
487 ((<lambda> body)
488 (max nmax (allocate! body proc n))))))
489 (else
490 ;; allocate closure
491 (lp (cdr gensyms)
492 (cdr vals)
493 (max nmax (allocate! (car vals) proc n))))))
494
495 (let ((v (car in)))
496 (cond
497 ((hashq-ref assigned v)
498 (error "fixpoint procedures may not be assigned" x))
499 ((hashq-ref labels v)
500 ;; no binding, it's a label
501 (lp (cdr in) n))
502 (else
503 ;; allocate closure binding
504 (hashq-set! allocation v (make-hashq proc `(#t #f . ,n)))
505 (lp (cdr in) (1+ n))))))))
506
507 ((<let-values> exp body)
508 (max (recur exp) (recur body)))
509
510 ((<dynwind> body winder unwinder)
511 (max (recur body) (recur winder) (recur unwinder)))
512
513 ((<dynlet> fluids vals body)
514 (apply max (recur body) (map recur (append fluids vals))))
515
516 ((<dynref> fluid)
517 (recur fluid))
518
519 ((<dynset> fluid exp)
520 (max (recur fluid) (recur exp)))
521
522 ((<prompt> tag body handler)
523 (let ((cont-var (and (lambda-case? handler)
524 (pair? (lambda-case-gensyms handler))
525 (car (lambda-case-gensyms handler)))))
526 (hashq-set! allocation x
527 (and cont-var (zero? (hashq-ref refcounts cont-var 0))))
528 (max (recur tag) (recur body) (recur handler))))
529
530 ((<abort> tag args tail)
531 (apply max (recur tag) (recur tail) (map recur args)))
532
533 (else n)))
534
535 (analyze! x #f '() #t #f)
536 (allocate! x #f 0)
537
538 allocation)
539
540 \f
541 ;;;
542 ;;; Tree analyses for warnings.
543 ;;;
544
545 (define-record-type <tree-analysis>
546 (make-tree-analysis leaf down up post init)
547 tree-analysis?
548 (leaf tree-analysis-leaf) ;; (lambda (x result env locs) ...)
549 (down tree-analysis-down) ;; (lambda (x result env locs) ...)
550 (up tree-analysis-up) ;; (lambda (x result env locs) ...)
551 (post tree-analysis-post) ;; (lambda (result env) ...)
552 (init tree-analysis-init)) ;; arbitrary value
553
554 (define (analyze-tree analyses tree env)
555 "Run all tree analyses listed in ANALYSES on TREE for ENV, using
556 `tree-il-fold'. Return TREE. The leaf/down/up procedures of each analysis are
557 passed a ``location stack', which is the stack of `tree-il-src' values for each
558 parent tree (a list); it can be used to approximate source location when
559 accurate information is missing from a given `tree-il' element."
560
561 (define (traverse proc update-locs)
562 ;; Return a tree traversing procedure that returns a list of analysis
563 ;; results prepended by the location stack.
564 (lambda (x results)
565 (let ((locs (update-locs x (car results))))
566 (cons locs ;; the location stack
567 (map (lambda (analysis result)
568 ((proc analysis) x result env locs))
569 analyses
570 (cdr results))))))
571
572 ;; Keeping/extending/shrinking the location stack.
573 (define (keep-locs x locs) locs)
574 (define (extend-locs x locs) (cons (tree-il-src x) locs))
575 (define (shrink-locs x locs) (cdr locs))
576
577 (let ((results
578 (tree-il-fold (traverse tree-analysis-leaf keep-locs)
579 (traverse tree-analysis-down extend-locs)
580 (traverse tree-analysis-up shrink-locs)
581 (cons '() ;; empty location stack
582 (map tree-analysis-init analyses))
583 tree)))
584
585 (for-each (lambda (analysis result)
586 ((tree-analysis-post analysis) result env))
587 analyses
588 (cdr results)))
589
590 tree)
591
592 \f
593 ;;;
594 ;;; Unused variable analysis.
595 ;;;
596
597 ;; <binding-info> records are used during tree traversals in
598 ;; `unused-variable-analysis'. They contain a list of the local vars
599 ;; currently in scope, and a list of locals vars that have been referenced.
600 (define-record-type <binding-info>
601 (make-binding-info vars refs)
602 binding-info?
603 (vars binding-info-vars) ;; ((GENSYM NAME LOCATION) ...)
604 (refs binding-info-refs)) ;; (GENSYM ...)
605
606 (define (gensym? sym)
607 ;; Return #t if SYM is (likely) a generated symbol.
608 (string-any #\space (symbol->string sym)))
609
610 (define unused-variable-analysis
611 ;; Report unused variables in the given tree.
612 (make-tree-analysis
613 (lambda (x info env locs)
614 ;; X is a leaf: extend INFO's refs accordingly.
615 (let ((refs (binding-info-refs info))
616 (vars (binding-info-vars info)))
617 (record-case x
618 ((<lexical-ref> gensym)
619 (make-binding-info vars (vhash-consq gensym #t refs)))
620 (else info))))
621
622 (lambda (x info env locs)
623 ;; Going down into X: extend INFO's variable list
624 ;; accordingly.
625 (let ((refs (binding-info-refs info))
626 (vars (binding-info-vars info))
627 (src (tree-il-src x)))
628 (define (extend inner-vars inner-names)
629 (fold (lambda (var name vars)
630 (vhash-consq var (list name src) vars))
631 vars
632 inner-vars
633 inner-names))
634
635 (record-case x
636 ((<lexical-set> gensym)
637 (make-binding-info vars (vhash-consq gensym #t refs)))
638 ((<lambda-case> req opt inits rest kw gensyms)
639 (let ((names `(,@req
640 ,@(or opt '())
641 ,@(if rest (list rest) '())
642 ,@(if kw (map cadr (cdr kw)) '()))))
643 (make-binding-info (extend gensyms names) refs)))
644 ((<let> gensyms names)
645 (make-binding-info (extend gensyms names) refs))
646 ((<letrec> gensyms names)
647 (make-binding-info (extend gensyms names) refs))
648 ((<fix> gensyms names)
649 (make-binding-info (extend gensyms names) refs))
650 (else info))))
651
652 (lambda (x info env locs)
653 ;; Leaving X's scope: shrink INFO's variable list
654 ;; accordingly and reported unused nested variables.
655 (let ((refs (binding-info-refs info))
656 (vars (binding-info-vars info)))
657 (define (shrink inner-vars refs)
658 (vlist-for-each
659 (lambda (var)
660 (let ((gensym (car var)))
661 ;; Don't report lambda parameters as unused.
662 (if (and (memq gensym inner-vars)
663 (not (vhash-assq gensym refs))
664 (not (lambda-case? x)))
665 (let ((name (cadr var))
666 ;; We can get approximate source location by going up
667 ;; the LOCS location stack.
668 (loc (or (caddr var)
669 (find pair? locs))))
670 (if (and (not (gensym? name))
671 (not (eq? name '_)))
672 (warning 'unused-variable loc name))))))
673 vars)
674 (vlist-drop vars (length inner-vars)))
675
676 ;; For simplicity, we leave REFS untouched, i.e., with
677 ;; names of variables that are now going out of scope.
678 ;; It doesn't hurt as these are unique names, it just
679 ;; makes REFS unnecessarily fat.
680 (record-case x
681 ((<lambda-case> gensyms)
682 (make-binding-info (shrink gensyms refs) refs))
683 ((<let> gensyms)
684 (make-binding-info (shrink gensyms refs) refs))
685 ((<letrec> gensyms)
686 (make-binding-info (shrink gensyms refs) refs))
687 ((<fix> gensyms)
688 (make-binding-info (shrink gensyms refs) refs))
689 (else info))))
690
691 (lambda (result env) #t)
692 (make-binding-info vlist-null vlist-null)))
693
694 \f
695 ;;;
696 ;;; Unused top-level variable analysis.
697 ;;;
698
699 ;; <reference-graph> record top-level definitions that are made, references to
700 ;; top-level definitions and their context (the top-level definition in which
701 ;; the reference appears), as well as the current context (the top-level
702 ;; definition we're currently in). The second part (`refs' below) is
703 ;; effectively a graph from which we can determine unused top-level definitions.
704 (define-record-type <reference-graph>
705 (make-reference-graph refs defs toplevel-context)
706 reference-graph?
707 (defs reference-graph-defs) ;; ((NAME . LOC) ...)
708 (refs reference-graph-refs) ;; ((REF-CONTEXT REF ...) ...)
709 (toplevel-context reference-graph-toplevel-context)) ;; NAME | #f
710
711 (define (graph-reachable-nodes root refs reachable)
712 ;; Add to REACHABLE the nodes reachable from ROOT in graph REFS. REFS is a
713 ;; vhash mapping nodes to the list of their children: for instance,
714 ;; ((A -> (B C)) (B -> (A)) (C -> ())) corresponds to
715 ;;
716 ;; ,-------.
717 ;; v |
718 ;; A ----> B
719 ;; |
720 ;; v
721 ;; C
722 ;;
723 ;; REACHABLE is a vhash of nodes known to be otherwise reachable.
724
725 (let loop ((root root)
726 (path vlist-null)
727 (result reachable))
728 (if (or (vhash-assq root path)
729 (vhash-assq root result))
730 result
731 (let* ((children (or (and=> (vhash-assq root refs) cdr) '()))
732 (path (vhash-consq root #t path))
733 (result (fold (lambda (kid result)
734 (loop kid path result))
735 result
736 children)))
737 (fold (lambda (kid result)
738 (vhash-consq kid #t result))
739 result
740 children)))))
741
742 (define (graph-reachable-nodes* roots refs)
743 ;; Return the list of nodes in REFS reachable from the nodes listed in ROOTS.
744 (vlist-fold (lambda (root+true result)
745 (let* ((root (car root+true))
746 (reachable (graph-reachable-nodes root refs result)))
747 (vhash-consq root #t reachable)))
748 vlist-null
749 roots))
750
751 (define (partition* pred vhash)
752 ;; Partition VHASH according to PRED. Return the two resulting vhashes.
753 (let ((result
754 (vlist-fold (lambda (k+v result)
755 (let ((k (car k+v))
756 (v (cdr k+v))
757 (r1 (car result))
758 (r2 (cdr result)))
759 (if (pred k)
760 (cons (vhash-consq k v r1) r2)
761 (cons r1 (vhash-consq k v r2)))))
762 (cons vlist-null vlist-null)
763 vhash)))
764 (values (car result) (cdr result))))
765
766 (define unused-toplevel-analysis
767 ;; Report unused top-level definitions that are not exported.
768 (let ((add-ref-from-context
769 (lambda (graph name)
770 ;; Add an edge CTX -> NAME in GRAPH.
771 (let* ((refs (reference-graph-refs graph))
772 (defs (reference-graph-defs graph))
773 (ctx (reference-graph-toplevel-context graph))
774 (ctx-refs (or (and=> (vhash-assq ctx refs) cdr) '())))
775 (make-reference-graph (vhash-consq ctx (cons name ctx-refs) refs)
776 defs ctx)))))
777 (define (macro-variable? name env)
778 (and (module? env)
779 (let ((var (module-variable env name)))
780 (and var (variable-bound? var)
781 (macro? (variable-ref var))))))
782
783 (make-tree-analysis
784 (lambda (x graph env locs)
785 ;; X is a leaf.
786 (let ((ctx (reference-graph-toplevel-context graph)))
787 (record-case x
788 ((<toplevel-ref> name src)
789 (add-ref-from-context graph name))
790 (else graph))))
791
792 (lambda (x graph env locs)
793 ;; Going down into X.
794 (let ((ctx (reference-graph-toplevel-context graph))
795 (refs (reference-graph-refs graph))
796 (defs (reference-graph-defs graph)))
797 (record-case x
798 ((<toplevel-define> name src)
799 (let ((refs refs)
800 (defs (vhash-consq name (or src (find pair? locs))
801 defs)))
802 (make-reference-graph refs defs name)))
803 ((<toplevel-set> name src)
804 (add-ref-from-context graph name))
805 (else graph))))
806
807 (lambda (x graph env locs)
808 ;; Leaving X's scope.
809 (record-case x
810 ((<toplevel-define>)
811 (let ((refs (reference-graph-refs graph))
812 (defs (reference-graph-defs graph)))
813 (make-reference-graph refs defs #f)))
814 (else graph)))
815
816 (lambda (graph env)
817 ;; Process the resulting reference graph: determine all private definitions
818 ;; not reachable from any public definition. Macros
819 ;; (syntax-transformers), which are globally bound, never considered
820 ;; unused since we can't tell whether a macro is actually used; in
821 ;; addition, macros are considered roots of the graph since they may use
822 ;; private bindings. FIXME: The `make-syntax-transformer' calls don't
823 ;; contain any literal `toplevel-ref' of the global bindings they use so
824 ;; this strategy fails.
825 (define (exported? name)
826 (if (module? env)
827 (module-variable (module-public-interface env) name)
828 #t))
829
830 (let-values (((public-defs private-defs)
831 (partition* (lambda (name)
832 (or (exported? name)
833 (macro-variable? name env)))
834 (reference-graph-defs graph))))
835 (let* ((roots (vhash-consq #f #t public-defs))
836 (refs (reference-graph-refs graph))
837 (reachable (graph-reachable-nodes* roots refs))
838 (unused (vlist-filter (lambda (name+src)
839 (not (vhash-assq (car name+src)
840 reachable)))
841 private-defs)))
842 (vlist-for-each (lambda (name+loc)
843 (let ((name (car name+loc))
844 (loc (cdr name+loc)))
845 (if (not (gensym? name))
846 (warning 'unused-toplevel loc name))))
847 unused))))
848
849 (make-reference-graph vlist-null vlist-null #f))))
850
851 \f
852 ;;;
853 ;;; Unbound variable analysis.
854 ;;;
855
856 ;; <toplevel-info> records are used during tree traversal in search of
857 ;; possibly unbound variable. They contain a list of references to
858 ;; potentially unbound top-level variables, and a list of the top-level
859 ;; defines that have been encountered.
860 (define-record-type <toplevel-info>
861 (make-toplevel-info refs defs)
862 toplevel-info?
863 (refs toplevel-info-refs) ;; ((VARIABLE-NAME . LOCATION) ...)
864 (defs toplevel-info-defs)) ;; (VARIABLE-NAME ...)
865
866 (define (goops-toplevel-definition proc args env)
867 ;; If application of PROC to ARGS is a GOOPS top-level definition, return
868 ;; the name of the variable being defined; otherwise return #f. This
869 ;; assumes knowledge of the current implementation of `define-class' et al.
870 (define (toplevel-define-arg args)
871 (match args
872 ((($ <const> _ (and (? symbol?) exp)) _)
873 exp)
874 (_ #f)))
875
876 (match proc
877 (($ <module-ref> _ '(oop goops) 'toplevel-define! #f)
878 (toplevel-define-arg args))
879 (($ <toplevel-ref> _ 'toplevel-define!)
880 ;; This may be the result of expanding one of the GOOPS macros within
881 ;; `oop/goops.scm'.
882 (and (eq? env (resolve-module '(oop goops)))
883 (toplevel-define-arg args)))
884 (_ #f)))
885
886 (define unbound-variable-analysis
887 ;; Report possibly unbound variables in the given tree.
888 (make-tree-analysis
889 (lambda (x info env locs)
890 ;; X is a leaf: extend INFO's refs accordingly.
891 (let ((refs (toplevel-info-refs info))
892 (defs (toplevel-info-defs info)))
893 (define (bound? name)
894 (or (and (module? env)
895 (module-variable env name))
896 (vhash-assq name defs)))
897
898 (record-case x
899 ((<toplevel-ref> name src)
900 (if (bound? name)
901 info
902 (let ((src (or src (find pair? locs))))
903 (make-toplevel-info (vhash-consq name src refs)
904 defs))))
905 (else info))))
906
907 (lambda (x info env locs)
908 ;; Going down into X.
909 (let* ((refs (toplevel-info-refs info))
910 (defs (toplevel-info-defs info))
911 (src (tree-il-src x)))
912 (define (bound? name)
913 (or (and (module? env)
914 (module-variable env name))
915 (vhash-assq name defs)))
916
917 (record-case x
918 ((<toplevel-set> name src)
919 (if (bound? name)
920 (make-toplevel-info refs defs)
921 (let ((src (find pair? locs)))
922 (make-toplevel-info (vhash-consq name src refs)
923 defs))))
924 ((<toplevel-define> name)
925 (make-toplevel-info (vhash-delq name refs)
926 (vhash-consq name #t defs)))
927
928 ((<application> proc args)
929 ;; Check for a dynamic top-level definition, as is
930 ;; done by code expanded from GOOPS macros.
931 (let ((name (goops-toplevel-definition proc args
932 env)))
933 (if (symbol? name)
934 (make-toplevel-info (vhash-delq name refs)
935 (vhash-consq name #t defs))
936 (make-toplevel-info refs defs))))
937 (else
938 (make-toplevel-info refs defs)))))
939
940 (lambda (x info env locs)
941 ;; Leaving X's scope.
942 info)
943
944 (lambda (toplevel env)
945 ;; Post-process the result.
946 (vlist-for-each (lambda (name+loc)
947 (let ((name (car name+loc))
948 (loc (cdr name+loc)))
949 (warning 'unbound-variable loc name)))
950 (vlist-reverse (toplevel-info-refs toplevel))))
951
952 (make-toplevel-info vlist-null vlist-null)))
953
954 \f
955 ;;;
956 ;;; Arity analysis.
957 ;;;
958
959 ;; <arity-info> records contain information about lexical definitions of
960 ;; procedures currently in scope, top-level procedure definitions that have
961 ;; been encountered, and calls to top-level procedures that have been
962 ;; encountered.
963 (define-record-type <arity-info>
964 (make-arity-info toplevel-calls lexical-lambdas toplevel-lambdas)
965 arity-info?
966 (toplevel-calls toplevel-procedure-calls) ;; ((NAME . APPLICATION) ...)
967 (lexical-lambdas lexical-lambdas) ;; ((GENSYM . DEFINITION) ...)
968 (toplevel-lambdas toplevel-lambdas)) ;; ((NAME . DEFINITION) ...)
969
970 (define (validate-arity proc application lexical?)
971 ;; Validate the argument count of APPLICATION, a tree-il application of
972 ;; PROC, emitting a warning in case of argument count mismatch.
973
974 (define (filter-keyword-args keywords allow-other-keys? args)
975 ;; Filter keyword arguments from ARGS and return the resulting list.
976 ;; KEYWORDS is the list of allowed keywords, and ALLOW-OTHER-KEYS?
977 ;; specified whethere keywords not listed in KEYWORDS are allowed.
978 (let loop ((args args)
979 (result '()))
980 (if (null? args)
981 (reverse result)
982 (let ((arg (car args)))
983 (if (and (const? arg)
984 (or (memq (const-exp arg) keywords)
985 (and allow-other-keys?
986 (keyword? (const-exp arg)))))
987 (loop (if (pair? (cdr args))
988 (cddr args)
989 '())
990 result)
991 (loop (cdr args)
992 (cons arg result)))))))
993
994 (define (arities proc)
995 ;; Return the arities of PROC, which can be either a tree-il or a
996 ;; procedure.
997 (define (len x)
998 (or (and (or (null? x) (pair? x))
999 (length x))
1000 0))
1001 (cond ((program? proc)
1002 (values (procedure-name proc)
1003 (map (lambda (a)
1004 (list (arity:nreq a) (arity:nopt a) (arity:rest? a)
1005 (map car (arity:kw a))
1006 (arity:allow-other-keys? a)))
1007 (program-arities proc))))
1008 ((procedure? proc)
1009 (let ((arity (procedure-minimum-arity proc)))
1010 (values (procedure-name proc)
1011 (list (list (car arity) (cadr arity) (caddr arity)
1012 #f #f)))))
1013 (else
1014 (let loop ((name #f)
1015 (proc proc)
1016 (arities '()))
1017 (if (not proc)
1018 (values name (reverse arities))
1019 (record-case proc
1020 ((<lambda-case> req opt rest kw alternate)
1021 (loop name alternate
1022 (cons (list (len req) (len opt) rest
1023 (and (pair? kw) (map car (cdr kw)))
1024 (and (pair? kw) (car kw)))
1025 arities)))
1026 ((<lambda> meta body)
1027 (loop (assoc-ref meta 'name) body arities))
1028 (else
1029 (values #f #f))))))))
1030
1031 (let ((args (application-args application))
1032 (src (tree-il-src application)))
1033 (call-with-values (lambda () (arities proc))
1034 (lambda (name arities)
1035 (define matches?
1036 (find (lambda (arity)
1037 (pmatch arity
1038 ((,req ,opt ,rest? ,kw ,aok?)
1039 (let ((args (if (pair? kw)
1040 (filter-keyword-args kw aok? args)
1041 args)))
1042 (if (and req opt)
1043 (let ((count (length args)))
1044 (and (>= count req)
1045 (or rest?
1046 (<= count (+ req opt)))))
1047 #t)))
1048 (else #t)))
1049 arities))
1050
1051 (if (not matches?)
1052 (warning 'arity-mismatch src
1053 (or name (with-output-to-string (lambda () (write proc))))
1054 lexical?)))))
1055 #t)
1056
1057 (define arity-analysis
1058 ;; Report arity mismatches in the given tree.
1059 (make-tree-analysis
1060 (lambda (x info env locs)
1061 ;; X is a leaf.
1062 info)
1063 (lambda (x info env locs)
1064 ;; Down into X.
1065 (define (extend lexical-name val info)
1066 ;; If VAL is a lambda, add NAME to the lexical-lambdas of INFO.
1067 (let ((toplevel-calls (toplevel-procedure-calls info))
1068 (lexical-lambdas (lexical-lambdas info))
1069 (toplevel-lambdas (toplevel-lambdas info)))
1070 (record-case val
1071 ((<lambda> body)
1072 (make-arity-info toplevel-calls
1073 (vhash-consq lexical-name val
1074 lexical-lambdas)
1075 toplevel-lambdas))
1076 ((<lexical-ref> gensym)
1077 ;; lexical alias
1078 (let ((val* (vhash-assq gensym lexical-lambdas)))
1079 (if (pair? val*)
1080 (extend lexical-name (cdr val*) info)
1081 info)))
1082 ((<toplevel-ref> name)
1083 ;; top-level alias
1084 (make-arity-info toplevel-calls
1085 (vhash-consq lexical-name val
1086 lexical-lambdas)
1087 toplevel-lambdas))
1088 (else info))))
1089
1090 (let ((toplevel-calls (toplevel-procedure-calls info))
1091 (lexical-lambdas (lexical-lambdas info))
1092 (toplevel-lambdas (toplevel-lambdas info)))
1093
1094 (record-case x
1095 ((<toplevel-define> name exp)
1096 (record-case exp
1097 ((<lambda> body)
1098 (make-arity-info toplevel-calls
1099 lexical-lambdas
1100 (vhash-consq name exp toplevel-lambdas)))
1101 ((<toplevel-ref> name)
1102 ;; alias for another toplevel
1103 (let ((proc (vhash-assq name toplevel-lambdas)))
1104 (make-arity-info toplevel-calls
1105 lexical-lambdas
1106 (vhash-consq (toplevel-define-name x)
1107 (if (pair? proc)
1108 (cdr proc)
1109 exp)
1110 toplevel-lambdas))))
1111 (else info)))
1112 ((<let> gensyms vals)
1113 (fold extend info gensyms vals))
1114 ((<letrec> gensyms vals)
1115 (fold extend info gensyms vals))
1116 ((<fix> gensyms vals)
1117 (fold extend info gensyms vals))
1118
1119 ((<application> proc args src)
1120 (record-case proc
1121 ((<lambda> body)
1122 (validate-arity proc x #t)
1123 info)
1124 ((<toplevel-ref> name)
1125 (make-arity-info (vhash-consq name x toplevel-calls)
1126 lexical-lambdas
1127 toplevel-lambdas))
1128 ((<lexical-ref> gensym)
1129 (let ((proc (vhash-assq gensym lexical-lambdas)))
1130 (if (pair? proc)
1131 (record-case (cdr proc)
1132 ((<toplevel-ref> name)
1133 ;; alias to toplevel
1134 (make-arity-info (vhash-consq name x toplevel-calls)
1135 lexical-lambdas
1136 toplevel-lambdas))
1137 (else
1138 (validate-arity (cdr proc) x #t)
1139 info))
1140
1141 ;; If GENSYM wasn't found, it may be because it's an
1142 ;; argument of the procedure being compiled.
1143 info)))
1144 (else info)))
1145 (else info))))
1146
1147 (lambda (x info env locs)
1148 ;; Up from X.
1149 (define (shrink name val info)
1150 ;; Remove NAME from the lexical-lambdas of INFO.
1151 (let ((toplevel-calls (toplevel-procedure-calls info))
1152 (lexical-lambdas (lexical-lambdas info))
1153 (toplevel-lambdas (toplevel-lambdas info)))
1154 (make-arity-info toplevel-calls
1155 (if (vhash-assq name lexical-lambdas)
1156 (vlist-tail lexical-lambdas)
1157 lexical-lambdas)
1158 toplevel-lambdas)))
1159
1160 (let ((toplevel-calls (toplevel-procedure-calls info))
1161 (lexical-lambdas (lexical-lambdas info))
1162 (toplevel-lambdas (toplevel-lambdas info)))
1163 (record-case x
1164 ((<let> gensyms vals)
1165 (fold shrink info gensyms vals))
1166 ((<letrec> gensyms vals)
1167 (fold shrink info gensyms vals))
1168 ((<fix> gensyms vals)
1169 (fold shrink info gensyms vals))
1170
1171 (else info))))
1172
1173 (lambda (result env)
1174 ;; Post-processing: check all top-level procedure calls that have been
1175 ;; encountered.
1176 (let ((toplevel-calls (toplevel-procedure-calls result))
1177 (toplevel-lambdas (toplevel-lambdas result)))
1178 (vlist-for-each
1179 (lambda (name+application)
1180 (let* ((name (car name+application))
1181 (application (cdr name+application))
1182 (proc
1183 (or (and=> (vhash-assq name toplevel-lambdas) cdr)
1184 (and (module? env)
1185 (false-if-exception
1186 (module-ref env name)))))
1187 (proc*
1188 ;; handle toplevel aliases
1189 (if (toplevel-ref? proc)
1190 (let ((name (toplevel-ref-name proc)))
1191 (and (module? env)
1192 (false-if-exception
1193 (module-ref env name))))
1194 proc)))
1195 (if (or (lambda? proc*) (procedure? proc*))
1196 (validate-arity proc* application (lambda? proc*)))))
1197 toplevel-calls)))
1198
1199 (make-arity-info vlist-null vlist-null vlist-null)))
1200
1201 \f
1202 ;;;
1203 ;;; `format' argument analysis.
1204 ;;;
1205
1206 (define &syntax-error
1207 ;; The `throw' key for syntax errors.
1208 (gensym "format-string-syntax-error"))
1209
1210 (define (format-string-argument-count fmt)
1211 ;; Return the minimum and maxium number of arguments that should
1212 ;; follow format string FMT (or, ahem, a good estimate thereof) or
1213 ;; `any' if the format string can be followed by any number of
1214 ;; arguments.
1215
1216 (define (drop-group chars end)
1217 ;; Drop characters from CHARS until "~END" is encountered.
1218 (let loop ((chars chars)
1219 (tilde? #f))
1220 (if (null? chars)
1221 (throw &syntax-error 'unterminated-iteration)
1222 (if tilde?
1223 (if (eq? (car chars) end)
1224 (cdr chars)
1225 (loop (cdr chars) #f))
1226 (if (eq? (car chars) #\~)
1227 (loop (cdr chars) #t)
1228 (loop (cdr chars) #f))))))
1229
1230 (define (digit? char)
1231 ;; Return true if CHAR is a digit, #f otherwise.
1232 (memq char '(#\0 #\1 #\2 #\3 #\4 #\5 #\6 #\7 #\8 #\9)))
1233
1234 (define (previous-number chars)
1235 ;; Return the previous series of digits found in CHARS.
1236 (let ((numbers (take-while digit? chars)))
1237 (and (not (null? numbers))
1238 (string->number (list->string (reverse numbers))))))
1239
1240 (let loop ((chars (string->list fmt))
1241 (state 'literal)
1242 (params '())
1243 (conditions '())
1244 (end-group #f)
1245 (min-count 0)
1246 (max-count 0))
1247 (if (null? chars)
1248 (if end-group
1249 (throw &syntax-error 'unterminated-conditional)
1250 (values min-count max-count))
1251 (case state
1252 ((tilde)
1253 (case (car chars)
1254 ((#\~ #\% #\& #\t #\_ #\newline #\( #\))
1255 (loop (cdr chars) 'literal '()
1256 conditions end-group
1257 min-count max-count))
1258 ((#\0 #\1 #\2 #\3 #\4 #\5 #\6 #\7 #\8 #\9 #\, #\: #\@)
1259 (loop (cdr chars)
1260 'tilde (cons (car chars) params)
1261 conditions end-group
1262 min-count max-count))
1263 ((#\v #\V) (loop (cdr chars)
1264 'tilde (cons (car chars) params)
1265 conditions end-group
1266 (+ 1 min-count)
1267 (+ 1 max-count)))
1268 ((#\[)
1269 (loop chars 'literal '() '()
1270 (let ((selector (previous-number params))
1271 (at? (memq #\@ params)))
1272 (lambda (chars conds)
1273 ;; end of group
1274 (let ((mins (map car conds))
1275 (maxs (map cdr conds))
1276 (sel? (and selector
1277 (< selector (length conds)))))
1278 (if (and (every number? mins)
1279 (every number? maxs))
1280 (loop chars 'literal '() conditions end-group
1281 (+ min-count
1282 (if sel?
1283 (car (list-ref conds selector))
1284 (+ (if at? 0 1)
1285 (if (null? mins)
1286 0
1287 (apply min mins)))))
1288 (+ max-count
1289 (if sel?
1290 (cdr (list-ref conds selector))
1291 (+ (if at? 0 1)
1292 (if (null? maxs)
1293 0
1294 (apply max maxs))))))
1295 (values 'any 'any))))) ;; XXX: approximation
1296 0 0))
1297 ((#\;)
1298 (if end-group
1299 (loop (cdr chars) 'literal '()
1300 (cons (cons min-count max-count) conditions)
1301 end-group
1302 0 0)
1303 (throw &syntax-error 'unexpected-semicolon)))
1304 ((#\])
1305 (if end-group
1306 (end-group (cdr chars)
1307 (reverse (cons (cons min-count max-count)
1308 conditions)))
1309 (throw &syntax-error 'unexpected-conditional-termination)))
1310 ((#\{) (if (memq #\@ params)
1311 (values min-count 'any)
1312 (loop (drop-group (cdr chars) #\})
1313 'literal '()
1314 conditions end-group
1315 (+ 1 min-count) (+ 1 max-count))))
1316 ((#\*) (if (memq #\@ params)
1317 (values 'any 'any) ;; it's unclear what to do here
1318 (loop (cdr chars)
1319 'literal '()
1320 conditions end-group
1321 (+ (or (previous-number params) 1)
1322 min-count)
1323 (+ (or (previous-number params) 1)
1324 max-count))))
1325 ((#\? #\k)
1326 ;; We don't have enough info to determine the exact number
1327 ;; of args, but we could determine a lower bound (TODO).
1328 (values 'any 'any))
1329 (else (loop (cdr chars) 'literal '()
1330 conditions end-group
1331 (+ 1 min-count) (+ 1 max-count)))))
1332 ((literal)
1333 (case (car chars)
1334 ((#\~) (loop (cdr chars) 'tilde '()
1335 conditions end-group
1336 min-count max-count))
1337 (else (loop (cdr chars) 'literal '()
1338 conditions end-group
1339 min-count max-count))))
1340 (else (error "computer bought the farm" state))))))
1341
1342 (define (const-fmt x)
1343 ;; Return the literal format pattern for X, or #f.
1344 (match x
1345 (($ <const> _ exp)
1346 exp)
1347 (($ <application> _
1348 (or ($ <toplevel-ref> _ '_) ($ <module-ref> _ '_))
1349 (($ <const> _ (and (? string?) fmt))))
1350 ;; Gettexted literals, like `(_ "foo")'.
1351 fmt)
1352 (_ #f)))
1353
1354 (define format-analysis
1355 ;; Report arity mismatches in the given tree.
1356 (make-tree-analysis
1357 (lambda (x _ env locs)
1358 ;; X is a leaf.
1359 #t)
1360
1361 (lambda (x _ env locs)
1362 ;; Down into X.
1363 (define (check-format-args args loc)
1364 (pmatch args
1365 ((,port ,fmt . ,rest)
1366 (guard (const-fmt fmt))
1367 (if (and (const? port)
1368 (not (boolean? (const-exp port))))
1369 (warning 'format loc 'wrong-port (const-exp port)))
1370 (let ((fmt (const-fmt fmt))
1371 (count (length rest)))
1372 (if (string? fmt)
1373 (catch &syntax-error
1374 (lambda ()
1375 (let-values (((min max)
1376 (format-string-argument-count fmt)))
1377 (and min max
1378 (or (and (or (eq? min 'any) (>= count min))
1379 (or (eq? max 'any) (<= count max)))
1380 (warning 'format loc 'wrong-format-arg-count
1381 fmt min max count)))))
1382 (lambda (_ key)
1383 (warning 'format loc 'syntax-error key fmt)))
1384 (warning 'format loc 'wrong-format-string fmt))))
1385 ((,port ,fmt . ,rest)
1386 (if (and (const? port)
1387 (not (boolean? (const-exp port))))
1388 (warn 'format loc 'wrong-port (const-exp port)))
1389 ;; Warn on non-literal format strings, unless they refer to a
1390 ;; lexical variable named "fmt".
1391 (if (record-case fmt
1392 ((<lexical-ref> name)
1393 (not (eq? name 'fmt)))
1394 (else #t))
1395 (warning 'format loc 'non-literal-format-string)))
1396 (else
1397 (warning 'format loc 'wrong-num-args (length args)))))
1398
1399 (define (resolve-toplevel name)
1400 (and (module? env)
1401 (false-if-exception (module-ref env name))))
1402
1403 (match x
1404 (($ <application> src ($ <toplevel-ref> _ name) args)
1405 (let ((proc (resolve-toplevel name)))
1406 (and (or (eq? proc format)
1407 (eq? proc (@ (ice-9 format) format)))
1408 (check-format-args args (or src (find pair? locs))))))
1409 (_ #t))
1410 #t)
1411
1412 (lambda (x _ env locs)
1413 ;; Up from X.
1414 #t)
1415
1416 (lambda (_ env)
1417 ;; Post-processing.
1418 #t)
1419
1420 #t))