Delete a ton of cruft from the globaldb initialization logic.
[sbcl.git] / src / compiler / ir1report.lisp
blobf2febf16f1e968628962fff7575974381a0bc2f6
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 (atom form)
156 (aver (null current))
157 (return))
158 (let ((head (first form)))
159 (when (symbolp head)
160 (let ((name (symbol-name head)))
161 (when (and (>= (length name) 3) (string= name "DEF" :end1 3))
162 (context (source-form-context form))))))
163 (when (null current) (return))
164 (setq form (nth (pop current) form)))
166 (cond ((context)
167 (values form (context)))
168 ((and path root)
169 (let ((c (source-form-context root)))
170 (values form (if c (list c) nil))))
172 (values '(unable to locate source)
173 '((some strange place)))))))))
175 ;;; Convert a source form to a string, suitably formatted for use in
176 ;;; compiler warnings.
177 (defun stringify-form (form &optional (pretty t))
178 (with-standard-io-syntax
179 (with-compiler-io-syntax
180 (let ((*print-pretty* pretty))
181 (if pretty
182 (format nil "~<~@; ~S~:>" (list form))
183 (prin1-to-string form))))))
185 ;;; Return a COMPILER-ERROR-CONTEXT structure describing the current
186 ;;; error context, or NIL if we can't figure anything out. ARGS is a
187 ;;; list of things that are going to be printed out in the error
188 ;;; message, and can thus be blown off when they appear in the source
189 ;;; context.
191 ;;; If OLD-CONTEXTS is passed in, and includes a context with the
192 ;;; same original source path as the new context would have, the old
193 ;;; context is reused instead, and a secondary value of T is returned.
194 (defun find-error-context (args &optional old-contexts)
195 (let ((context *compiler-error-context*))
196 (if (compiler-error-context-p context)
197 (values context t)
198 (let* ((path (or (and (node-p context) (node-source-path context))
199 (and (boundp '*current-path*) *current-path*)))
200 (old
201 (find (when path (source-path-original-source path))
202 (remove-if #'null old-contexts)
203 :test #'equal
204 :key #'compiler-error-context-original-source-path)))
205 (if old
206 (values old t)
207 (when (and *source-info* path)
208 (multiple-value-bind (form src-context) (find-original-source path)
209 (collect ((full nil cons)
210 (short nil cons))
211 (let ((forms (source-path-forms path))
212 (n 0))
213 (dolist (src (if (member (first forms) args)
214 (rest forms)
215 forms))
216 (if (>= n *enclosing-source-cutoff*)
217 (short (stringify-form (if (consp src)
218 (car src)
219 src)
220 nil))
221 (full (stringify-form src)))
222 (incf n)))
224 (let* ((tlf (source-path-tlf-number path))
225 (file-info (source-info-file-info *source-info*)))
226 (values
227 (make-compiler-error-context
228 :enclosing-source (short)
229 :source (full)
230 :original-source (stringify-form form)
231 :context src-context
232 :file-name (file-info-name file-info)
233 :file-position
234 (nth-value 1 (find-source-root tlf *source-info*))
235 :original-source-path (source-path-original-source path)
236 :lexenv (if context
237 (node-lexenv context)
238 (if (boundp '*lexenv*) *lexenv* nil)))
239 nil))))))))))
241 ;;;; printing error messages
243 ;;; We save the context information that we printed out most recently
244 ;;; so that we don't print it out redundantly.
246 ;;; The last COMPILER-ERROR-CONTEXT that we printed.
247 (defvar *last-error-context* nil)
248 (declaim (type (or compiler-error-context null) *last-error-context*))
250 ;;; The format string and args for the last error we printed.
251 (defvar *last-format-string* nil)
252 (defvar *last-format-args* nil)
253 (declaim (type (or string null) *last-format-string*))
254 (declaim (type list *last-format-args*))
256 ;;; The number of times that the last error message has been emitted,
257 ;;; so that we can compress duplicate error messages.
258 (defvar *last-message-count* 0)
259 (declaim (type index *last-message-count*))
261 ;;; If the last message was given more than once, then print out an
262 ;;; indication of how many times it was repeated. We reset the message
263 ;;; count when we are done.
264 (defun note-message-repeats (stream &optional (terpri t))
265 (cond ((= *last-message-count* 1)
266 (when terpri
267 (terpri stream)))
268 ((> *last-message-count* 1)
269 (format stream "~&; [Last message occurs ~W times.]~2%"
270 *last-message-count*)))
271 (setq *last-message-count* 0))
273 ;;; Print out the message, with appropriate context if we can find it.
274 ;;; If the context is different from the context of the last message
275 ;;; we printed, then we print the context. If the original source is
276 ;;; different from the source we are working on, then we print the
277 ;;; current source in addition to the original source.
279 ;;; We suppress printing of messages identical to the previous, but
280 ;;; record the number of times that the message is repeated.
281 (defun print-compiler-message (stream format-string format-args)
282 (with-compiler-io-syntax
283 (%print-compiler-message stream format-string format-args)))
285 (defun %print-compiler-message (stream format-string format-args)
286 (declare (type simple-string format-string))
287 (declare (type list format-args))
288 (let ((context (find-error-context format-args)))
289 (cond (context
290 (let ((file (compiler-error-context-file-name context))
291 (in (compiler-error-context-context context))
292 (form (compiler-error-context-original-source context))
293 (enclosing (compiler-error-context-enclosing-source context))
294 (source (compiler-error-context-source context))
295 (last *last-error-context*))
297 (unless (and last
298 (equal file (compiler-error-context-file-name last)))
299 (when (pathnamep file)
300 (note-message-repeats stream)
301 (setq last nil)
302 (format stream "~2&; file: ~A~%" (namestring file))))
304 (unless (and last
305 (equal in (compiler-error-context-context last)))
306 (note-message-repeats stream)
307 (setq last nil)
308 (pprint-logical-block (stream nil :per-line-prefix "; ")
309 (format stream "in:~{~<~% ~4:;~{ ~:S~}~>~^ =>~}" in))
310 (terpri stream))
312 (unless (and last
313 (string= form
314 (compiler-error-context-original-source last)))
315 (note-message-repeats stream)
316 (setq last nil)
317 (pprint-logical-block (stream nil :per-line-prefix "; ")
318 (princ form stream))
319 (fresh-line stream))
321 (unless (and last
322 (equal enclosing
323 (compiler-error-context-enclosing-source last)))
324 (when enclosing
325 (note-message-repeats stream)
326 (setq last nil)
327 (format stream "~&; --> ~{~<~%; --> ~1:;~A~> ~}~%" enclosing)))
329 (unless (and last
330 (equal source (compiler-error-context-source last)))
331 (setq *last-format-string* nil)
332 (when source
333 (note-message-repeats stream)
334 (dolist (src source)
335 (fresh-line stream)
336 (write-string "; ==>" stream)
337 (terpri stream)
338 (pprint-logical-block (stream nil :per-line-prefix "; ")
339 (write-string src stream)))))))
341 (fresh-line stream)
342 (note-message-repeats stream)
343 (setq *last-format-string* nil)))
345 (setq *last-error-context* context))
347 ;; FIXME: this testing for effective equality of compiler messages
348 ;; is ugly, and really ought to be done at a higher level.
349 (unless (and (equal format-string *last-format-string*)
350 (tree-equal format-args *last-format-args*))
351 (note-message-repeats stream nil)
352 (setq *last-format-string* format-string)
353 (setq *last-format-args* format-args)
354 (fresh-line stream)
355 (pprint-logical-block (stream nil :per-line-prefix "; ")
356 (format stream "~&~?" format-string format-args))
357 (fresh-line stream))
359 (incf *last-message-count*)
360 (values))
362 (defun print-compiler-condition (condition)
363 (declare (type condition condition))
364 (let (;; These different classes of conditions have different
365 ;; effects on the return codes of COMPILE-FILE, so it's nice
366 ;; for users to be able to pick them out by lexical search
367 ;; through the output.
368 (what (etypecase condition
369 (style-warning 'style-warning)
370 (warning 'warning)
371 ((or error compiler-error) 'error))))
372 (print-compiler-message
373 *error-output*
374 (format nil "caught ~S:~%~~@< ~~@;~~A~~:>" what)
375 (list (princ-to-string condition)))))
377 ;;; The act of signalling one of these beasts must not cause WARNINGSP
378 ;;; (or FAILUREP) to be set from COMPILE or COMPILE-FILE, so we can't
379 ;;; inherit from WARNING or STYLE-WARNING.
381 ;;; FIXME: the handling of compiler-notes could be unified with
382 ;;; warnings and style-warnings (see the various handler functions
383 ;;; below).
384 (define-condition compiler-note (condition) ()
385 (:documentation
386 "Root of the hierarchy of conditions representing information discovered
387 by the compiler that the user might wish to know, but which does not merit
388 a STYLE-WARNING (or any more serious condition)."))
389 (define-condition simple-compiler-note (simple-condition compiler-note) ())
390 (define-condition code-deletion-note (simple-compiler-note) ()
391 (:documentation
392 "A condition type signalled when the compiler deletes code that the user
393 has written, having proved that it is unreachable."))
395 (macrolet ((with-condition ((condition datum args) &body body)
396 (with-unique-names (block)
397 `(block ,block
398 (let ((,condition
399 (coerce-to-condition ,datum ,args
400 'simple-compiler-note
401 'with-condition)))
402 (restart-case
403 (signal ,condition)
404 (muffle-warning ()
405 (return-from ,block (values))))
406 ,@body
407 (values))))))
409 (defun compiler-notify (datum &rest args)
410 (unless (if *compiler-error-context*
411 (policy *compiler-error-context* (= inhibit-warnings 3))
412 (policy *lexenv* (= inhibit-warnings 3)))
413 (with-condition (condition datum args)
414 (incf *compiler-note-count*)
415 (print-compiler-message
416 *error-output*
417 (format nil "note: ~~A")
418 (list (princ-to-string condition)))))
419 (values))
421 ;; Issue a note when we might or might not be in the compiler.
422 (defun maybe-compiler-notify (datum &rest args)
423 (if (boundp '*lexenv*) ; if we're in the compiler
424 (apply #'compiler-notify datum args)
425 (with-condition (condition datum args)
426 (let ((stream *error-output*))
427 (pprint-logical-block (stream nil :per-line-prefix ";")
428 (format stream " note: ~3I~_")
429 (pprint-logical-block (stream nil)
430 (format stream "~A" condition)))
431 ;; (outside logical block, no per-line-prefix)
432 (fresh-line stream))))))
434 ;;; The politically correct way to print out progress messages and
435 ;;; such like. We clear the current error context so that we know that
436 ;;; it needs to be reprinted, and we also FORCE-OUTPUT so that the
437 ;;; message gets seen right away.
438 (declaim (ftype (function (string &rest t) (values)) compiler-mumble))
439 (defun compiler-mumble (control &rest args)
440 (let ((stream *standard-output*))
441 (note-message-repeats stream)
442 (setq *last-error-context* nil)
443 (apply #'format stream control args)
444 (force-output stream)
445 (values)))
447 ;;; Return a string that somehow names the code in COMPONENT. We use
448 ;;; the source path for the bind node for an arbitrary entry point to
449 ;;; find the source context, then return that as a string.
450 (declaim (ftype (function (component) simple-string) find-component-name))
451 (defun find-component-name (component)
452 (let ((ep (first (block-succ (component-head component)))))
453 (aver ep) ; else no entry points??
454 (multiple-value-bind (form context)
455 (find-original-source (node-source-path (block-start-node ep)))
456 (declare (ignore form))
457 (let ((*print-level* 2)
458 (*print-pretty* nil))
459 (format nil "~{~{~S~^ ~}~^ => ~}"
460 #+sb-xc-host (list (list (caar context)))
461 #-sb-xc-host context)))))
463 ;;;; condition system interface
465 ;;; Keep track of how many times each kind of condition happens.
466 (defvar *compiler-error-count*)
467 (defvar *compiler-warning-count*)
468 (defvar *compiler-style-warning-count*)
469 (defvar *compiler-note-count*)
471 ;;; Keep track of whether any surrounding COMPILE or COMPILE-FILE call
472 ;;; should return WARNINGS-P or FAILURE-P.
473 (defvar *failure-p*)
474 (defvar *warnings-p*)
476 ;;; condition handlers established by the compiler. We re-signal the
477 ;;; condition, then if it isn't handled, we increment our warning
478 ;;; counter and print the error message.
479 (defun compiler-error-handler (condition)
480 (signal condition)
481 (incf *compiler-error-count*)
482 (setf *warnings-p* t
483 *failure-p* t)
484 (print-compiler-condition condition)
485 (continue condition))
486 (defun compiler-warning-handler (condition)
487 (signal condition)
488 (incf *compiler-warning-count*)
489 (setf *warnings-p* t
490 *failure-p* t)
491 (print-compiler-condition condition)
492 (muffle-warning condition))
493 (defun compiler-style-warning-handler (condition)
494 (signal condition)
495 (incf *compiler-style-warning-count*)
496 (setf *warnings-p* t)
497 (print-compiler-condition condition)
498 (muffle-warning condition))
500 ;;;; undefined warnings
502 (defvar *undefined-warning-limit* 3
503 #!+sb-doc
504 "If non-null, then an upper limit on the number of unknown function or type
505 warnings that the compiler will print for any given name in a single
506 compilation. This prevents excessive amounts of output when the real
507 problem is a missing definition (as opposed to a typo in the use.)")
509 ;;; Make an entry in the *UNDEFINED-WARNINGS* describing a reference
510 ;;; to NAME of the specified KIND. If we have exceeded the warning
511 ;;; limit, then just increment the count, otherwise note the current
512 ;;; error context.
514 ;;; Undefined types are noted by a condition handler in
515 ;;; WITH-COMPILATION-UNIT, which can potentially be invoked outside
516 ;;; the compiler, hence the BOUNDP check.
517 (defun note-undefined-reference (name kind)
518 (unless (and
519 ;; Check for boundness so we don't blow up if we're called
520 ;; when IR1 conversion isn't going on.
521 (boundp '*lexenv*)
523 ;; FIXME: I'm pretty sure the INHIBIT-WARNINGS test below
524 ;; isn't a good idea; we should have INHIBIT-WARNINGS
525 ;; affect compiler notes, not STYLE-WARNINGs. And I'm not
526 ;; sure what the BOUNDP '*LEXENV* test above is for; it's
527 ;; likely a good idea, but it probably deserves an
528 ;; explanatory comment.
529 (policy *lexenv* (= inhibit-warnings 3))
530 ;; KLUDGE: weird decoupling between here and where we're
531 ;; going to signal the condition. I don't think we can
532 ;; rewrite this using SIGNAL and RESTART-CASE (to take
533 ;; advantage of the (SATISFIES HANDLE-CONDITION-P)
534 ;; handler, because if that doesn't handle it the ordinary
535 ;; compiler handlers will trigger.
536 (typep
537 (ecase kind
538 (:variable (make-condition 'warning))
539 ((:function :type) (make-condition 'style-warning)))
540 (car
541 (rassoc 'muffle-warning
542 (lexenv-handled-conditions *lexenv*))))))
543 (let* ((found (dolist (warning *undefined-warnings* nil)
544 (when (and (equal (undefined-warning-name warning) name)
545 (eq (undefined-warning-kind warning) kind))
546 (return warning))))
547 (res (or found
548 (make-undefined-warning :name name :kind kind))))
549 (unless found (push res *undefined-warnings*))
550 (multiple-value-bind (context old)
551 (find-error-context (list name) (undefined-warning-warnings res))
552 (unless old
553 (when (or (not *undefined-warning-limit*)
554 (< (undefined-warning-count res) *undefined-warning-limit*))
555 (push context (undefined-warning-warnings res)))
556 (incf (undefined-warning-count res))))))
557 (values))
559 ;; The compiler tracks full calls that were emitted so that it is possible
560 ;; to detect a definition of a compiler-macro occuring after the first
561 ;; compile-time observed use of (vs. actual call of) that function name.
563 ;; The call count is not reset if the function gets redefined (where the
564 ;; macro could briefly be out-of-sync), but this choice is deliberate.
565 ;; We're not trying to find and report all possible ways that users can
566 ;; introduce semantic glitches, only trying to signal something that is
567 ;; otherwise not always obvious in a totally working built-from-scratch
568 ;; user system, absent any interactive changes.
570 ;; Note on implementation: originally I thought about doing something
571 ;; based on whether the name got an APPROXIMATE-FUN-TYPE and the :WHERE-FROM
572 ;; was :ASSUMED - which together imply that the function did not exist *and*
573 ;; that it was not a NOTINLINE call, however that proved to be fragile.
574 ;; The current approach is reliable, at a cost of ~3 words per function.
576 (defun warn-if-compiler-macro-dependency-problem (name)
577 (unless (sb!xc:compiler-macro-function name)
578 (let ((status (car (info :function :emitted-full-calls name))))
579 (when (and (integerp status) (oddp status))
580 ;; Show the total number of calls, because otherwise the warning
581 ;; would be worded rather obliquely: "N calls were compiled
582 ;; not in the scope of a notinline declaration" which is, to me,
583 ;; worse than matter-of-factly stating that N calls were compiled.
584 ;; This is why I don't bother collecting both statistics.
585 ;; It's the tail wagging the dog: the message dictates what to track.
586 (compiler-style-warn
587 ;; Grammar note - starting a sentence with a numeral is wrong.
588 (!uncross-format-control
589 "~@<~@(~D~) call~:P to ~/sb!impl:print-symbol-with-prefix/ ~2:*~[~;was~:;were~] ~
590 compiled before a compiler-macro was defined for it. A declaration of ~
591 NOTINLINE at the call site~:P will eliminate this warning, ~
592 as will defining the compiler-macro before its first potential use.~@:>")
593 (ash status -2) name)))))
595 ;; Inlining failure scenario 1 [at time of proclamation]:
596 ;; Full call to F is emitted not in the scope of a NOTINLINE, with no definition
597 ;; of F available, and then it's proclaimed INLINE. If F was defined already,
598 ;; it would have been used, unless the expansion limit was hit.
600 (defun warn-if-inline-failed/proclaim (name new-inlinep)
601 (when (eq new-inlinep :inline)
602 (let ((warning-count (emitted-full-call-count name)))
603 (when (and warning-count
604 ;; Warn only if the the compiler did not have the expansion.
605 (not (info :function :inline-expansion-designator name))
606 ;; and if nothing was previously known about inline status
607 ;; so that repeated proclamations don't warn. NIL is a valid
608 ;; value for :inlinep in the globaldb so use the 2nd result.
609 (not (nth-value 1 (info :function :inlinep name))))
610 (compiler-style-warn
611 'inlining-dependency-failure
612 :format-control
613 (!uncross-format-control
614 "~@<Proclaiming ~/sb!impl:print-symbol-with-prefix/ to be INLINE, but ~D call~:P to it ~
615 ~:*~[~;was~:;were~] previously compiled. A declaration of NOTINLINE ~
616 at the call site~:P will eliminate this warning, as will proclaiming ~
617 and defining the function before its first potential use.~@:>")
618 :format-arguments (list name warning-count))))))
620 ;; Inlining failure scenario 2 [at time of call]:
621 ;; F is not defined, but either proclaimed INLINE and not declared
622 ;; locally notinline, or expressly declared locally inline.
623 ;; Warn about emitting a full call at that time.
625 ;; It could be friendlier to present this warning as one summary
626 ;; at the end of a compilation unit, but that is not as important as
627 ;; just getting the warning across.
628 ;; [The point of deferring a warning is that some future event can resolve it
629 ;; - like an undefined function becoming defined - but there's nothing
630 ;; that can resolve absence of a definition at a point when it was needed]
632 ;; Should we regard it as more serious if the inline-ness of the global
633 ;; function was lexically declared? Is "Inline F here" stronger than
634 ;; "It would generally be a good idea to inline F everywhere"?
636 ;; Don't be too put off by the above concerns though. It's not customary
637 ;; to write (DECLAIM INLINE) after the function, or so far separated from it
638 ;; that intervening callers know it to be proclaimed inline, and would have
639 ;; liked to have a definition, but didn't.
641 (defun warn-if-inline-failed/call (name lexenv count-cell)
642 ;; Do nothing if the inline expansion is known - it wasn't used
643 ;; because of the expansion limit, which is a different problem.
644 (unless (or (logtest 2 (car count-cell)) ; warn at most once per name
645 (info :function :inline-expansion-designator name))
646 ;; This function is only called by PONDER-FULL-CALL when NAME
647 ;; is not lexically NOTINLINE, so therefore if it is globally INLINE,
648 ;; there was no local declaration to the contrary.
649 (when (or (eq (info :function :inlinep name) :inline)
650 (let ((fun (let ((*lexenv* lexenv))
651 (lexenv-find name funs :test #'equal))))
652 (and fun
653 (defined-fun-p fun)
654 (eq (defined-fun-inlinep fun) :inline))))
655 ;; Set a bit saying that a warning about the call was generated,
656 ;; which suppresses the warning about either a later
657 ;; call or a later proclamation.
658 (setf (car count-cell) (logior (car count-cell) 2))
659 ;; While there could be a different style-warning for
660 ;; "You should put the DEFUN after the DECLAIM"
661 ;; if they appeared reversed, it's not ideal to warn as soon as that.
662 ;; It's only a problem if something failed to be inlined in account of it.
663 (compiler-style-warn
664 'inlining-dependency-failure
665 :format-control
666 (if (info :function :assumed-type name)
667 (!uncross-format-control
668 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because no definition ~
669 for it was seen prior to its first use.~:@>")
670 ;; This message sort of implies that source form is the
671 ;; only reasonable representation in which an inline definition
672 ;; could have been saved, which isn't in general true - it could
673 ;; be saved as a parsed AST - but I don't really know how else to
674 ;; phrase this. And it happens to be true in SBCL, so it's not wrong.
675 (!uncross-format-control
676 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because its source code ~
677 was not saved. A global INLINE or SB-EXT:MAYBE-INLINE proclamation must be ~
678 in effect to save function definitions for inlining.~:@>"))
679 :format-arguments (list name)))))