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