Fix comment about *code-coverage-info*.
[sbcl.git] / src / compiler / ir1report.lisp
blob08067c75ba5ab3dda564a4313691d7216177951b
1 ;;;; machinery for reporting errors/warnings/notes/whatnot from
2 ;;;; the compiler
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
13 (in-package "SB!C")
15 ;;;; compiler error context determination
17 (declaim (special *current-path*))
19 (defvar *enclosing-source-cutoff* 1
20 #!+sb-doc
21 "The maximum number of enclosing non-original source forms (i.e. from
22 macroexpansion) that we print in full. For additional enclosing forms, we
23 print only the CAR.")
24 (declaim (type unsigned-byte *enclosing-source-cutoff*))
26 ;;; We separate the determination of compiler error contexts from the
27 ;;; actual signalling of those errors by objectifying the error
28 ;;; context. This allows postponement of the determination of how (and
29 ;;; if) to signal the error.
30 ;;;
31 ;;; We take care not to reference any of the IR1 so that pending
32 ;;; potential error messages won't prevent the IR1 from being GC'd. To
33 ;;; this end, we convert source forms to strings so that source forms
34 ;;; that contain IR1 references (e.g. %DEFUN) don't hold onto the IR.
35 (defstruct (compiler-error-context
36 #-no-ansi-print-object
37 (:print-object (lambda (x stream)
38 (print-unreadable-object (x stream :type t))))
39 (:copier nil))
40 ;; a list of the stringified CARs of the enclosing non-original source forms
41 ;; exceeding the *enclosing-source-cutoff*
42 (enclosing-source nil :type list)
43 ;; a list of stringified enclosing non-original source forms
44 (source nil :type list)
45 ;; the stringified form in the original source that expanded into SOURCE
46 (original-source (missing-arg) :type simple-string)
47 ;; a list of prefixes of "interesting" forms that enclose original-source
48 (context nil :type list)
49 ;; the FILE-INFO-NAME for the relevant FILE-INFO
50 (file-name (missing-arg) :type (or pathname (member :lisp :stream)))
51 ;; the file position at which the top level form starts, if applicable
52 (file-position nil :type (or index null))
53 ;; the original source part of the source path
54 (original-source-path nil :type list)
55 ;; the lexenv active at the time
56 (lexenv nil :type (or null lexenv)))
58 ;;; If true, this is the node which is used as context in compiler warning
59 ;;; messages.
60 (declaim (type (or null compiler-error-context node) *compiler-error-context*))
61 (defvar *compiler-error-context* nil)
63 ;;; a hashtable mapping macro names to source context parsers. Each parser
64 ;;; function returns the source-context list for that form.
65 (defvar *source-context-methods* (make-hash-table))
67 ;;; documentation originally from cmu-user.tex:
68 ;;; This macro defines how to extract an abbreviated source context from
69 ;;; the \var{name}d form when it appears in the compiler input.
70 ;;; \var{lambda-list} is a \code{defmacro} style lambda-list used to
71 ;;; parse the arguments. The \var{body} should return a list of
72 ;;; subforms that can be printed on about one line. There are
73 ;;; predefined methods for \code{defstruct}, \code{defmethod}, etc. If
74 ;;; no method is defined, then the first two subforms are returned.
75 ;;; Note that this facility implicitly determines the string name
76 ;;; associated with anonymous functions.
77 ;;; So even though SBCL itself only uses this macro within this file,
78 ;;; it's a reasonable thing to put in SB-EXT in case some dedicated
79 ;;; user wants to do some heavy tweaking to make SBCL give more
80 ;;; informative output about his code.
81 (defmacro define-source-context (name lambda-list &body body)
82 #!+sb-doc
83 "DEFINE-SOURCE-CONTEXT Name Lambda-List Form*
84 This macro defines how to extract an abbreviated source context from the
85 Named form when it appears in the compiler input. Lambda-List is a DEFMACRO
86 style lambda-list used to parse the arguments. The Body should return a
87 list of subforms suitable for a \"~{~S ~}\" format string."
88 (with-unique-names (whole)
89 `(setf (gethash ',name *source-context-methods*)
90 (lambda (,whole)
91 (destructuring-bind ,lambda-list ,whole ,@body)))))
93 (define-source-context defstruct (name-or-options &rest slots)
94 (declare (ignore slots))
95 `(defstruct ,(if (consp name-or-options)
96 (car name-or-options)
97 name-or-options)))
99 (define-source-context function (thing)
100 (if (and (consp thing) (eq (first thing) 'lambda) (consp (rest thing)))
101 `(lambda ,(second thing))
102 `(function ,thing)))
104 (define-source-context named-lambda (name lambda-list &body forms)
105 (declare (ignore lambda-list forms))
106 (if (and (consp name) (eq 'eval (first name)))
107 (second name)
108 `(named-lambda ,name)))
110 (defvar *source-form-context-alist* nil)
112 ;;; Return the first two elements of FORM if FORM is a list. Take the
113 ;;; CAR of the second form if appropriate.
114 (defun source-form-context (form)
115 (flet ((get-it (form)
116 (cond ((atom form) nil)
117 ((>= (length form) 2)
118 (let* ((context-fun-default
119 (lambda (x)
120 (declare (ignore x))
121 (list (first form) (second form))))
122 (context-fun
123 (gethash (first form)
124 *source-context-methods*
125 context-fun-default)))
126 (declare (type function context-fun))
127 (funcall context-fun (rest form))))
129 form))))
130 (get-it (or (cdr (assoc form *source-form-context-alist* :test #'eq))
131 form))))
133 ;;; Given a source path, return the original source form and a
134 ;;; description of the interesting aspects of the context in which it
135 ;;; appeared. The context is a list of lists, one sublist per context
136 ;;; form. The sublist is a list of some of the initial subforms of the
137 ;;; context form.
139 ;;; For now, we use the first two subforms of each interesting form. A
140 ;;; form is interesting if the first element is a symbol beginning
141 ;;; with "DEF" and it is not the source form. If there is no
142 ;;; DEF-mumble, then we use the outermost containing form. If the
143 ;;; second subform is a list, then in some cases we return the CAR of
144 ;;; that form rather than the whole form (i.e. don't show DEFSTRUCT
145 ;;; options, etc.)
146 (defun find-original-source (path)
147 (declare (list path))
148 (let* ((rpath (reverse (source-path-original-source path)))
149 (tlf (first rpath))
150 (root (find-source-root tlf *source-info*)))
151 (collect ((context))
152 (let ((form root)
153 (current (rest rpath)))
154 (loop
155 (when (sb!int:comma-p form)
156 (setf form (sb!int:comma-expr form)))
157 (when (atom form)
158 (aver (null current))
159 (return))
160 (let ((head (first form)))
161 (when (symbolp head)
162 (let ((name (symbol-name head)))
163 (when (and (>= (length name) 3) (string= name "DEF" :end1 3))
164 (context (source-form-context form))))))
165 (when (null current) (return))
166 (setq form (nth (pop current) form)))
168 (cond ((context)
169 (values form (context)))
170 ((and path root)
171 (let ((c (source-form-context root)))
172 (values form (if c (list c) nil))))
174 (values '(unable to locate source)
175 '((some strange place)))))))))
177 ;;; Convert a source form to a string, suitably formatted for use in
178 ;;; compiler warnings.
179 (defun stringify-form (form &optional (pretty t))
180 (with-standard-io-syntax
181 (with-compiler-io-syntax
182 (let ((*print-pretty* pretty))
183 (if pretty
184 (format nil "~<~@; ~S~:>" (list form))
185 (prin1-to-string form))))))
187 ;;; Return a COMPILER-ERROR-CONTEXT structure describing the current
188 ;;; error context, or NIL if we can't figure anything out. ARGS is a
189 ;;; list of things that are going to be printed out in the error
190 ;;; message, and can thus be blown off when they appear in the source
191 ;;; context.
193 ;;; If OLD-CONTEXTS is passed in, and includes a context with the
194 ;;; same original source path as the new context would have, the old
195 ;;; context is reused instead, and a secondary value of T is returned.
196 (defun find-error-context (args &optional old-contexts)
197 (let ((context *compiler-error-context*))
198 (if (compiler-error-context-p context)
199 (values context t)
200 (let* ((path (or (and (node-p context) (node-source-path context))
201 (and (boundp '*current-path*) *current-path*)))
202 (old
203 (find (when path (source-path-original-source path))
204 (remove-if #'null old-contexts)
205 :test #'equal
206 :key #'compiler-error-context-original-source-path)))
207 (if old
208 (values old t)
209 (when (and *source-info* path)
210 (multiple-value-bind (form src-context) (find-original-source path)
211 (collect ((full nil cons)
212 (short nil cons))
213 (let ((forms (source-path-forms path))
214 (n 0))
215 (dolist (src (if (member (first forms) args)
216 (rest forms)
217 forms))
218 (if (>= n *enclosing-source-cutoff*)
219 (short (stringify-form (if (consp src)
220 (car src)
221 src)
222 nil))
223 (full (stringify-form src)))
224 (incf n)))
226 (let* ((tlf (source-path-tlf-number path))
227 (file-info (source-info-file-info *source-info*)))
228 (values
229 (make-compiler-error-context
230 :enclosing-source (short)
231 :source (full)
232 :original-source (stringify-form form)
233 :context src-context
234 :file-name (file-info-name file-info)
235 :file-position
236 (nth-value 1 (find-source-root tlf *source-info*))
237 :original-source-path (source-path-original-source path)
238 :lexenv (if context
239 (node-lexenv context)
240 (if (boundp '*lexenv*) *lexenv* nil)))
241 nil))))))))))
243 ;;;; printing error messages
245 ;;; We save the context information that we printed out most recently
246 ;;; so that we don't print it out redundantly.
248 ;;; The last COMPILER-ERROR-CONTEXT that we printed.
249 (defvar *last-error-context* nil)
250 (declaim (type (or compiler-error-context null) *last-error-context*))
252 ;;; The format string and args for the last error we printed.
253 (defvar *last-format-string* nil)
254 (defvar *last-format-args* nil)
255 (declaim (type (or string null) *last-format-string*))
256 (declaim (type list *last-format-args*))
258 ;;; The number of times that the last error message has been emitted,
259 ;;; so that we can compress duplicate error messages.
260 (defvar *last-message-count* 0)
261 (declaim (type index *last-message-count*))
263 ;;; If the last message was given more than once, then print out an
264 ;;; indication of how many times it was repeated. We reset the message
265 ;;; count when we are done.
266 (defun note-message-repeats (stream &optional (terpri t))
267 (cond ((= *last-message-count* 1)
268 (when terpri
269 (terpri stream)))
270 ((> *last-message-count* 1)
271 (format stream "~&; [Last message occurs ~W times.]~2%"
272 *last-message-count*)))
273 (setq *last-message-count* 0))
275 ;;; Print out the message, with appropriate context if we can find it.
276 ;;; If the context is different from the context of the last message
277 ;;; we printed, then we print the context. If the original source is
278 ;;; different from the source we are working on, then we print the
279 ;;; current source in addition to the original source.
281 ;;; We suppress printing of messages identical to the previous, but
282 ;;; record the number of times that the message is repeated.
283 (defun print-compiler-message (stream format-string format-args)
284 (with-compiler-io-syntax
285 (%print-compiler-message stream format-string format-args)))
287 (defun %print-compiler-message (stream format-string format-args)
288 (declare (type simple-string format-string))
289 (declare (type list format-args))
290 (let ((context (find-error-context format-args)))
291 (cond (context
292 (let ((file (compiler-error-context-file-name context))
293 (in (compiler-error-context-context context))
294 (form (compiler-error-context-original-source context))
295 (enclosing (compiler-error-context-enclosing-source context))
296 (source (compiler-error-context-source context))
297 (last *last-error-context*))
299 (unless (and last
300 (equal file (compiler-error-context-file-name last)))
301 (when (pathnamep file)
302 (note-message-repeats stream)
303 (setq last nil)
304 (format stream "~2&; file: ~A~%" (namestring file))))
306 (unless (and last
307 (equal in (compiler-error-context-context last)))
308 (note-message-repeats stream)
309 (setq last nil)
310 (pprint-logical-block (stream nil :per-line-prefix "; ")
311 (format stream "in:~{~<~% ~4:;~{ ~:S~}~>~^ =>~}" in))
312 (terpri stream))
314 (unless (and last
315 (string= form
316 (compiler-error-context-original-source last)))
317 (note-message-repeats stream)
318 (setq last nil)
319 (pprint-logical-block (stream nil :per-line-prefix "; ")
320 (princ form stream))
321 (fresh-line stream))
323 (unless (and last
324 (equal enclosing
325 (compiler-error-context-enclosing-source last)))
326 (when enclosing
327 (note-message-repeats stream)
328 (setq last nil)
329 (format stream "~&; --> ~{~<~%; --> ~1:;~A~> ~}~%" enclosing)))
331 (unless (and last
332 (equal source (compiler-error-context-source last)))
333 (setq *last-format-string* nil)
334 (when source
335 (note-message-repeats stream)
336 (dolist (src source)
337 (fresh-line stream)
338 (write-string "; ==>" stream)
339 (terpri stream)
340 (pprint-logical-block (stream nil :per-line-prefix "; ")
341 (write-string src stream)))))))
343 (fresh-line stream)
344 (note-message-repeats stream)
345 (setq *last-format-string* nil)))
347 (setq *last-error-context* context))
349 ;; FIXME: this testing for effective equality of compiler messages
350 ;; is ugly, and really ought to be done at a higher level.
351 (unless (and (equal format-string *last-format-string*)
352 (tree-equal format-args *last-format-args*))
353 (note-message-repeats stream nil)
354 (setq *last-format-string* format-string)
355 (setq *last-format-args* format-args)
356 (fresh-line stream)
357 (pprint-logical-block (stream nil :per-line-prefix "; ")
358 (format stream "~&~?" format-string format-args))
359 (fresh-line stream))
361 (incf *last-message-count*)
362 (values))
364 (defun print-compiler-condition (condition)
365 (declare (type condition condition))
366 (let (;; These different classes of conditions have different
367 ;; effects on the return codes of COMPILE-FILE, so it's nice
368 ;; for users to be able to pick them out by lexical search
369 ;; through the output.
370 (what (etypecase condition
371 (style-warning 'style-warning)
372 (warning 'warning)
373 ((or error compiler-error) 'error))))
374 (print-compiler-message
375 *error-output*
376 (format nil "caught ~S:~%~~@< ~~@;~~A~~:>" what)
377 (list (princ-to-string condition)))))
379 ;;; The act of signalling one of these beasts must not cause WARNINGSP
380 ;;; (or FAILUREP) to be set from COMPILE or COMPILE-FILE, so we can't
381 ;;; inherit from WARNING or STYLE-WARNING.
383 ;;; FIXME: the handling of compiler-notes could be unified with
384 ;;; warnings and style-warnings (see the various handler functions
385 ;;; below).
386 (define-condition compiler-note (condition) ()
387 (:documentation
388 "Root of the hierarchy of conditions representing information discovered
389 by the compiler that the user might wish to know, but which does not merit
390 a STYLE-WARNING (or any more serious condition)."))
391 (define-condition simple-compiler-note (simple-condition compiler-note) ())
392 (define-condition code-deletion-note (simple-compiler-note) ()
393 (:documentation
394 "A condition type signalled when the compiler deletes code that the user
395 has written, having proved that it is unreachable."))
397 (define-condition compiler-macro-application-missed-warning
398 (style-warning)
399 ((count :initarg :count
400 :reader compiler-macro-application-missed-warning-count)
401 (function :initarg :function
402 :reader compiler-macro-application-missed-warning-function))
403 (:default-initargs
404 :count (missing-arg)
405 :function (missing-arg))
406 (:report
407 (lambda (condition stream)
408 ;; Grammar note - starting a sentence with a numeral is wrong.
409 (format stream
410 "~@<~@(~D~) call~:P to ~
411 ~/sb!impl:print-symbol-with-prefix/ ~
412 ~2:*~[~;was~:;were~] compiled before a compiler-macro ~
413 was defined for it. A declaration of NOTINLINE at the ~
414 call site~:P will eliminate this warning, as will ~
415 defining the compiler-macro before its first potential ~
416 use.~@:>"
417 (compiler-macro-application-missed-warning-count condition)
418 (compiler-macro-application-missed-warning-function condition)))))
420 (macrolet ((with-condition ((condition datum args) &body body)
421 (with-unique-names (block)
422 `(block ,block
423 (let ((,condition
424 (coerce-to-condition ,datum ,args
425 'simple-compiler-note
426 'with-condition)))
427 (restart-case
428 (signal ,condition)
429 (muffle-warning ()
430 (return-from ,block (values))))
431 ,@body
432 (values))))))
434 (defun compiler-notify (datum &rest args)
435 (unless (if *compiler-error-context*
436 (policy *compiler-error-context* (= inhibit-warnings 3))
437 (policy *lexenv* (= inhibit-warnings 3)))
438 (with-condition (condition datum args)
439 (incf *compiler-note-count*)
440 (print-compiler-message
441 *error-output*
442 (format nil "note: ~~A")
443 (list (princ-to-string condition)))))
444 (values))
446 ;; Issue a note when we might or might not be in the compiler.
447 (defun maybe-compiler-notify (datum &rest args)
448 (if (boundp '*lexenv*) ; if we're in the compiler
449 (apply #'compiler-notify datum args)
450 (with-condition (condition datum args)
451 (let ((stream *error-output*))
452 (pprint-logical-block (stream nil :per-line-prefix ";")
453 (format stream " note: ~3I~_")
454 (pprint-logical-block (stream nil)
455 (format stream "~A" condition)))
456 ;; (outside logical block, no per-line-prefix)
457 (fresh-line stream))))))
459 ;;; The politically correct way to print out progress messages and
460 ;;; such like. We clear the current error context so that we know that
461 ;;; it needs to be reprinted, and we also FORCE-OUTPUT so that the
462 ;;; message gets seen right away.
463 (declaim (ftype (function (string &rest t) (values)) compiler-mumble))
464 (defun compiler-mumble (control &rest args)
465 (let ((stream *standard-output*))
466 (note-message-repeats stream)
467 (setq *last-error-context* nil)
468 (apply #'format stream control args)
469 (force-output stream)
470 (values)))
472 ;;; Return a string that somehow names the code in COMPONENT. We use
473 ;;; the source path for the bind node for an arbitrary entry point to
474 ;;; find the source context, then return that as a string.
475 (declaim (ftype (function (component) simple-string) find-component-name))
476 (defun find-component-name (component)
477 (let ((ep (first (block-succ (component-head component)))))
478 (aver ep) ; else no entry points??
479 (multiple-value-bind (form context)
480 (find-original-source (node-source-path (block-start-node ep)))
481 (declare (ignore form))
482 (let ((*print-level* 2)
483 (*print-pretty* nil))
484 ;; It's arbitrary how this name is stringified.
485 ;; Using ~A in lieu of ~S prevents "SB!" strings from getting in.
486 (format nil
487 "~{~{~A~^ ~}~^ => ~}"
488 #+sb-xc-host (list (list (caar context)))
489 #-sb-xc-host context)))))
491 ;;;; condition system interface
493 ;;; Keep track of how many times each kind of condition happens.
494 (defvar *compiler-error-count*)
495 (defvar *compiler-warning-count*)
496 (defvar *compiler-style-warning-count*)
497 (defvar *compiler-note-count*)
499 ;;; Keep track of whether any surrounding COMPILE or COMPILE-FILE call
500 ;;; should return WARNINGS-P or FAILURE-P.
501 (defvar *failure-p*)
502 (defvar *warnings-p*)
504 ;;; condition handlers established by the compiler. We re-signal the
505 ;;; condition, then if it isn't handled, we increment our warning
506 ;;; counter and print the error message.
507 (defun compiler-error-handler (condition)
508 (signal condition)
509 (incf *compiler-error-count*)
510 (setf *warnings-p* t
511 *failure-p* t)
512 (print-compiler-condition condition)
513 (continue condition))
514 (defun compiler-warning-handler (condition)
515 (signal condition)
516 (incf *compiler-warning-count*)
517 (setf *warnings-p* t
518 *failure-p* t)
519 (print-compiler-condition condition)
520 (muffle-warning condition))
521 (defun compiler-style-warning-handler (condition)
522 (signal condition)
523 (incf *compiler-style-warning-count*)
524 (setf *warnings-p* t)
525 (print-compiler-condition condition)
526 (muffle-warning condition))
528 ;;;; undefined warnings
530 (defvar *undefined-warning-limit* 3
531 #!+sb-doc
532 "If non-null, then an upper limit on the number of unknown function or type
533 warnings that the compiler will print for any given name in a single
534 compilation. This prevents excessive amounts of output when the real
535 problem is a missing definition (as opposed to a typo in the use.)")
537 ;;; Make an entry in the *UNDEFINED-WARNINGS* describing a reference
538 ;;; to NAME of the specified KIND. If we have exceeded the warning
539 ;;; limit, then just increment the count, otherwise note the current
540 ;;; error context.
542 ;;; Undefined types are noted by a condition handler in
543 ;;; WITH-COMPILATION-UNIT, which can potentially be invoked outside
544 ;;; the compiler, hence the BOUNDP check.
545 (defun note-undefined-reference (name kind)
546 #+sb-xc-host
547 ;; Whitelist functions are looked up prior to UNCROSS,
548 ;; so that we can distinguish CL:SOMEFUN from SB-XC:SOMEFUN.
549 (when (and (eq kind :function)
550 (gethash name sb-cold::*undefined-fun-whitelist*))
551 (return-from note-undefined-reference (values)))
552 (setq name (uncross name))
553 (unless (and
554 ;; Check for boundness so we don't blow up if we're called
555 ;; when IR1 conversion isn't going on.
556 (boundp '*lexenv*)
558 ;; FIXME: I'm pretty sure the INHIBIT-WARNINGS test below
559 ;; isn't a good idea; we should have INHIBIT-WARNINGS
560 ;; affect compiler notes, not STYLE-WARNINGs. And I'm not
561 ;; sure what the BOUNDP '*LEXENV* test above is for; it's
562 ;; likely a good idea, but it probably deserves an
563 ;; explanatory comment.
564 (policy *lexenv* (= inhibit-warnings 3))
565 ;; KLUDGE: weird decoupling between here and where we're
566 ;; going to signal the condition. I don't think we can
567 ;; rewrite this using SIGNAL and RESTART-CASE (to take
568 ;; advantage of the (SATISFIES HANDLE-CONDITION-P)
569 ;; handler, because if that doesn't handle it the ordinary
570 ;; compiler handlers will trigger.
571 (would-muffle-p
572 (ecase kind
573 (:variable (make-condition 'warning))
574 ((:function :type) (make-condition 'style-warning))))))
575 (let* ((found (dolist (warning *undefined-warnings* nil)
576 (when (and (equal (undefined-warning-name warning) name)
577 (eq (undefined-warning-kind warning) kind))
578 (return warning))))
579 (res (or found
580 (make-undefined-warning :name name :kind kind))))
581 (unless found (push res *undefined-warnings*))
582 (multiple-value-bind (context old)
583 (find-error-context (list name) (undefined-warning-warnings res))
584 (unless old
585 (when (or (not *undefined-warning-limit*)
586 (< (undefined-warning-count res) *undefined-warning-limit*))
587 (push context (undefined-warning-warnings res)))
588 (incf (undefined-warning-count res))))))
589 (values))
591 ;; The compiler tracks full calls that were emitted so that it is possible
592 ;; to detect a definition of a compiler-macro occuring after the first
593 ;; compile-time observed use of (vs. actual call of) that function name.
595 ;; The call count is not reset if the function gets redefined (where the
596 ;; macro could briefly be out-of-sync), but this choice is deliberate.
597 ;; We're not trying to find and report all possible ways that users can
598 ;; introduce semantic glitches, only trying to signal something that is
599 ;; otherwise not always obvious in a totally working built-from-scratch
600 ;; user system, absent any interactive changes.
602 ;; Note on implementation: originally I thought about doing something
603 ;; based on whether the name got an APPROXIMATE-FUN-TYPE and the :WHERE-FROM
604 ;; was :ASSUMED - which together imply that the function did not exist *and*
605 ;; that it was not a NOTINLINE call, however that proved to be fragile.
606 ;; The current approach is reliable, at a cost of ~3 words per function.
608 (defun warn-if-compiler-macro-dependency-problem (name)
609 (unless (sb!xc:compiler-macro-function name)
610 (let ((status (car (info :function :emitted-full-calls name)))) ; TODO use emitted-full-call-count?
611 (when (and (integerp status) (oddp status))
612 ;; Show the total number of calls, because otherwise the warning
613 ;; would be worded rather obliquely: "N calls were compiled
614 ;; not in the scope of a notinline declaration" which is, to me,
615 ;; worse than matter-of-factly stating that N calls were compiled.
616 ;; This is why I don't bother collecting both statistics.
617 ;; It's the tail wagging the dog: the message dictates what to track.
618 (compiler-style-warn
619 'compiler-macro-application-missed-warning
620 :count (ash status -2) :function name)))))
622 ;; Inlining failure scenario 1 [at time of proclamation]:
623 ;; Full call to F is emitted not in the scope of a NOTINLINE, with no definition
624 ;; of F available, and then it's proclaimed INLINE. If F was defined already,
625 ;; it would have been used, unless the expansion limit was hit.
627 (defun warn-if-inline-failed/proclaim (name new-inlinep)
628 (when (eq new-inlinep :inline)
629 (let ((warning-count (emitted-full-call-count name)))
630 (when (and warning-count
631 ;; Warn only if the the compiler did not have the expansion.
632 (not (info :function :inline-expansion-designator name))
633 ;; and if nothing was previously known about inline status
634 ;; so that repeated proclamations don't warn. NIL is a valid
635 ;; value for :inlinep in the globaldb so use the 2nd result.
636 (not (nth-value 1 (info :function :inlinep name))))
637 ;; This will be a STYLE-WARNING for the target, but a full warning
638 ;; for the host. There's no constraint to use _only_ STYLE-WARN
639 ;; to signal a (subtype of) STYLE-WARNING. But conversely we enforce
640 ;; that STYLE-WARN not signal things that aren't style-warnings.
641 (compiler-warn
642 'inlining-dependency-failure
643 :format-control
644 "~@<Proclaiming ~/sb!impl:print-symbol-with-prefix/ to be INLINE, but ~D call~:P to it ~
645 ~:*~[~;was~:;were~] previously compiled. A declaration of NOTINLINE ~
646 at the call site~:P will eliminate this warning, as will proclaiming ~
647 and defining the function before its first potential use.~@:>"
648 :format-arguments (list name warning-count))))))
650 ;; Inlining failure scenario 2 [at time of call]:
651 ;; F is not defined, but either proclaimed INLINE and not declared
652 ;; locally notinline, or expressly declared locally inline.
653 ;; Warn about emitting a full call at that time.
655 ;; It could be friendlier to present this warning as one summary
656 ;; at the end of a compilation unit, but that is not as important as
657 ;; just getting the warning across.
658 ;; [The point of deferring a warning is that some future event can resolve it
659 ;; - like an undefined function becoming defined - but there's nothing
660 ;; that can resolve absence of a definition at a point when it was needed]
662 ;; Should we regard it as more serious if the inline-ness of the global
663 ;; function was lexically declared? Is "Inline F here" stronger than
664 ;; "It would generally be a good idea to inline F everywhere"?
666 ;; Don't be too put off by the above concerns though. It's not customary
667 ;; to write (DECLAIM INLINE) after the function, or so far separated from it
668 ;; that intervening callers know it to be proclaimed inline, and would have
669 ;; liked to have a definition, but didn't.
671 (defun warn-if-inline-failed/call (name lexenv count-cell)
672 ;; Do nothing if the inline expansion is known - it wasn't used
673 ;; because of the expansion limit, which is a different problem.
674 (unless (or (logtest 2 (car count-cell)) ; warn at most once per name
675 (info :function :inline-expansion-designator name))
676 ;; This function is only called by PONDER-FULL-CALL when NAME
677 ;; is not lexically NOTINLINE, so therefore if it is globally INLINE,
678 ;; there was no local declaration to the contrary.
679 (when (or (eq (info :function :inlinep name) :inline)
680 (let ((fun (let ((*lexenv* lexenv))
681 (lexenv-find name funs :test #'equal))))
682 (and fun
683 (defined-fun-p fun)
684 (eq (defined-fun-inlinep fun) :inline))))
685 ;; Set a bit saying that a warning about the call was generated,
686 ;; which suppresses the warning about either a later
687 ;; call or a later proclamation.
688 (setf (car count-cell) (logior (car count-cell) 2))
689 ;; While there could be a different style-warning for
690 ;; "You should put the DEFUN after the DECLAIM"
691 ;; if they appeared reversed, it's not ideal to warn as soon as that.
692 ;; It's only a problem if something failed to be inlined in account of it.
693 (compiler-style-warn
694 'inlining-dependency-failure
695 :format-control
696 (if (info :function :assumed-type name)
697 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because no definition ~
698 for it was seen prior to its first use.~:@>"
699 ;; This message sort of implies that source form is the
700 ;; only reasonable representation in which an inline definition
701 ;; could have been saved, which isn't in general true - it could
702 ;; be saved as a parsed AST - but I don't really know how else to
703 ;; phrase this. And it happens to be true in SBCL, so it's not wrong.
704 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because its source code ~
705 was not saved. A global INLINE or SB-EXT:MAYBE-INLINE proclamation must be ~
706 in effect to save function definitions for inlining.~:@>")
707 :format-arguments (list name)))))