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