1 ;;;; machinery for reporting errors/warnings/notes/whatnot from
4 ;;;; This software is part of the SBCL system. See the README file for
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.
15 ;;;; compiler error context determination
17 (declaim (special *current-path
*))
19 (defvar *enclosing-source-cutoff
* 1
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
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.
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
))))
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
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
)
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
*)
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
)
99 (define-source-context function
(thing)
100 (if (and (consp thing
) (eq (first thing
) 'lambda
) (consp (rest thing
)))
101 `(lambda ,(second 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
)))
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
121 (list (first form
) (second form
))))
123 (gethash (first form
)
124 *source-context-methods
*
125 context-fun-default
)))
126 (declare (type function context-fun
))
127 (funcall context-fun
(rest form
))))
130 (get-it (or (cdr (assoc form
*source-form-context-alist
* :test
#'eq
))
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
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
146 (defun find-original-source (path)
147 (declare (list path
))
148 (let* ((rpath (reverse (source-path-original-source path
)))
150 (root (find-source-root tlf
*source-info
*)))
153 (current (rest rpath
)))
156 (aver (null current
))
158 (let ((head (first form
)))
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
)))
167 (values form
(context)))
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
))
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
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
)
198 (let* ((path (or (and (node-p context
) (node-source-path context
))
199 (and (boundp '*current-path
*) *current-path
*)))
201 (find (when path
(source-path-original-source path
))
202 (remove-if #'null old-contexts
)
204 :key
#'compiler-error-context-original-source-path
)))
207 (when (and *source-info
* path
)
208 (multiple-value-bind (form src-context
) (find-original-source path
)
209 (collect ((full nil cons
)
211 (let ((forms (source-path-forms path
))
213 (dolist (src (if (member (first forms
) args
)
216 (if (>= n
*enclosing-source-cutoff
*)
217 (short (stringify-form (if (consp src
)
221 (full (stringify-form src
)))
224 (let* ((tlf (source-path-tlf-number path
))
225 (file-info (source-info-file-info *source-info
*)))
227 (make-compiler-error-context
228 :enclosing-source
(short)
230 :original-source
(stringify-form form
)
232 :file-name
(file-info-name file-info
)
234 (multiple-value-bind (ignore pos
)
235 (find-source-root tlf
*source-info
*)
236 (declare (ignore ignore
))
238 :original-source-path
(source-path-original-source path
)
240 (node-lexenv context
)
241 (if (boundp '*lexenv
*) *lexenv
* nil
)))
244 ;;;; printing error messages
246 ;;; We save the context information that we printed out most recently
247 ;;; so that we don't print it out redundantly.
249 ;;; The last COMPILER-ERROR-CONTEXT that we printed.
250 (defvar *last-error-context
* nil
)
251 (declaim (type (or compiler-error-context null
) *last-error-context
*))
253 ;;; The format string and args for the last error we printed.
254 (defvar *last-format-string
* nil
)
255 (defvar *last-format-args
* nil
)
256 (declaim (type (or string null
) *last-format-string
*))
257 (declaim (type list
*last-format-args
*))
259 ;;; The number of times that the last error message has been emitted,
260 ;;; so that we can compress duplicate error messages.
261 (defvar *last-message-count
* 0)
262 (declaim (type index
*last-message-count
*))
264 ;;; If the last message was given more than once, then print out an
265 ;;; indication of how many times it was repeated. We reset the message
266 ;;; count when we are done.
267 (defun note-message-repeats (stream &optional
(terpri t
))
268 (cond ((= *last-message-count
* 1)
271 ((> *last-message-count
* 1)
272 (format stream
"~&; [Last message occurs ~W times.]~2%"
273 *last-message-count
*)))
274 (setq *last-message-count
* 0))
276 ;;; Print out the message, with appropriate context if we can find it.
277 ;;; If the context is different from the context of the last message
278 ;;; we printed, then we print the context. If the original source is
279 ;;; different from the source we are working on, then we print the
280 ;;; current source in addition to the original source.
282 ;;; We suppress printing of messages identical to the previous, but
283 ;;; record the number of times that the message is repeated.
284 (defun print-compiler-message (stream format-string format-args
)
285 (with-compiler-io-syntax
286 (%print-compiler-message stream format-string format-args
)))
288 (defun %print-compiler-message
(stream format-string format-args
)
289 (declare (type simple-string format-string
))
290 (declare (type list format-args
))
291 (let ((context (find-error-context format-args
)))
293 (let ((file (compiler-error-context-file-name context
))
294 (in (compiler-error-context-context context
))
295 (form (compiler-error-context-original-source context
))
296 (enclosing (compiler-error-context-enclosing-source context
))
297 (source (compiler-error-context-source context
))
298 (last *last-error-context
*))
301 (equal file
(compiler-error-context-file-name last
)))
302 (when (pathnamep file
)
303 (note-message-repeats stream
)
305 (format stream
"~2&; file: ~A~%" (namestring file
))))
308 (equal in
(compiler-error-context-context last
)))
309 (note-message-repeats stream
)
311 (pprint-logical-block (stream nil
:per-line-prefix
"; ")
312 (format stream
"in:~{~<~% ~4:;~{ ~:S~}~>~^ =>~}" in
))
317 (compiler-error-context-original-source last
)))
318 (note-message-repeats stream
)
320 (pprint-logical-block (stream nil
:per-line-prefix
"; ")
326 (compiler-error-context-enclosing-source last
)))
328 (note-message-repeats stream
)
330 (format stream
"~&; --> ~{~<~%; --> ~1:;~A~> ~}~%" enclosing
)))
333 (equal source
(compiler-error-context-source last
)))
334 (setq *last-format-string
* nil
)
336 (note-message-repeats stream
)
339 (write-string "; ==>" stream
)
341 (pprint-logical-block (stream nil
:per-line-prefix
"; ")
342 (write-string src stream
)))))))
345 (note-message-repeats stream
)
346 (setq *last-format-string
* nil
)))
348 (setq *last-error-context
* context
))
350 ;; FIXME: this testing for effective equality of compiler messages
351 ;; is ugly, and really ought to be done at a higher level.
352 (unless (and (equal format-string
*last-format-string
*)
353 (tree-equal format-args
*last-format-args
*))
354 (note-message-repeats stream nil
)
355 (setq *last-format-string
* format-string
)
356 (setq *last-format-args
* format-args
)
358 (pprint-logical-block (stream nil
:per-line-prefix
"; ")
359 (format stream
"~&~?" format-string format-args
))
362 (incf *last-message-count
*)
365 (defun print-compiler-condition (condition)
366 (declare (type condition condition
))
367 (let (;; These different classes of conditions have different
368 ;; effects on the return codes of COMPILE-FILE, so it's nice
369 ;; for users to be able to pick them out by lexical search
370 ;; through the output.
371 (what (etypecase condition
372 (style-warning 'style-warning
)
374 ((or error compiler-error
) 'error
))))
375 (print-compiler-message
377 (format nil
"caught ~S:~%~~@< ~~@;~~A~~:>" what
)
378 (list (princ-to-string condition
)))))
380 ;;; The act of signalling one of these beasts must not cause WARNINGSP
381 ;;; (or FAILUREP) to be set from COMPILE or COMPILE-FILE, so we can't
382 ;;; inherit from WARNING or STYLE-WARNING.
384 ;;; FIXME: the handling of compiler-notes could be unified with
385 ;;; warnings and style-warnings (see the various handler functions
387 (define-condition compiler-note
(condition) ()
389 "Root of the hierarchy of conditions representing information discovered
390 by the compiler that the user might wish to know, but which does not merit
391 a STYLE-WARNING (or any more serious condition)."))
392 (define-condition simple-compiler-note
(simple-condition compiler-note
) ())
393 (define-condition code-deletion-note
(simple-compiler-note) ()
395 "A condition type signalled when the compiler deletes code that the user
396 has written, having proved that it is unreachable."))
398 (macrolet ((with-condition ((condition datum args
) &body body
)
399 (with-unique-names (block)
402 (coerce-to-condition ,datum
,args
403 'simple-compiler-note
408 (return-from ,block
(values))))
412 (defun compiler-notify (datum &rest args
)
413 (unless (if *compiler-error-context
*
414 (policy *compiler-error-context
* (= inhibit-warnings
3))
415 (policy *lexenv
* (= inhibit-warnings
3)))
416 (with-condition (condition datum args
)
417 (incf *compiler-note-count
*)
418 (print-compiler-message
420 (format nil
"note: ~~A")
421 (list (princ-to-string condition
)))))
424 ;; Issue a note when we might or might not be in the compiler.
425 (defun maybe-compiler-notify (datum &rest args
)
426 (if (boundp '*lexenv
*) ; if we're in the compiler
427 (apply #'compiler-notify datum args
)
428 (with-condition (condition datum args
)
429 (let ((stream *error-output
*))
430 (pprint-logical-block (stream nil
:per-line-prefix
";")
431 (format stream
" note: ~3I~_")
432 (pprint-logical-block (stream nil
)
433 (format stream
"~A" condition
)))
434 ;; (outside logical block, no per-line-prefix)
435 (fresh-line stream
))))))
437 ;;; The politically correct way to print out progress messages and
438 ;;; such like. We clear the current error context so that we know that
439 ;;; it needs to be reprinted, and we also FORCE-OUTPUT so that the
440 ;;; message gets seen right away.
441 (declaim (ftype (function (string &rest t
) (values)) compiler-mumble
))
442 (defun compiler-mumble (control &rest args
)
443 (let ((stream *standard-output
*))
444 (note-message-repeats stream
)
445 (setq *last-error-context
* nil
)
446 (apply #'format stream control args
)
447 (force-output stream
)
450 ;;; Return a string that somehow names the code in COMPONENT. We use
451 ;;; the source path for the bind node for an arbitrary entry point to
452 ;;; find the source context, then return that as a string.
453 (declaim (ftype (function (component) simple-string
) find-component-name
))
454 (defun find-component-name (component)
455 (let ((ep (first (block-succ (component-head component
)))))
456 (aver ep
) ; else no entry points??
457 (multiple-value-bind (form context
)
458 (find-original-source (node-source-path (block-start-node ep
)))
459 (declare (ignore form
))
460 (let ((*print-level
* 2)
461 (*print-pretty
* nil
))
462 (format nil
"~{~{~S~^ ~}~^ => ~}"
463 #+sb-xc-host
(list (list (caar context
)))
464 #-sb-xc-host context
)))))
466 ;;;; condition system interface
468 ;;; Keep track of how many times each kind of condition happens.
469 (defvar *compiler-error-count
*)
470 (defvar *compiler-warning-count
*)
471 (defvar *compiler-style-warning-count
*)
472 (defvar *compiler-note-count
*)
474 ;;; Keep track of whether any surrounding COMPILE or COMPILE-FILE call
475 ;;; should return WARNINGS-P or FAILURE-P.
477 (defvar *warnings-p
*)
479 ;;; condition handlers established by the compiler. We re-signal the
480 ;;; condition, then if it isn't handled, we increment our warning
481 ;;; counter and print the error message.
482 (defun compiler-error-handler (condition)
484 (incf *compiler-error-count
*)
487 (print-compiler-condition condition
)
488 (continue condition
))
489 (defun compiler-warning-handler (condition)
491 (incf *compiler-warning-count
*)
494 (print-compiler-condition condition
)
495 (muffle-warning condition
))
496 (defun compiler-style-warning-handler (condition)
498 (incf *compiler-style-warning-count
*)
499 (setf *warnings-p
* t
)
500 (print-compiler-condition condition
)
501 (muffle-warning condition
))
503 ;;;; undefined warnings
505 (defvar *undefined-warning-limit
* 3
507 "If non-null, then an upper limit on the number of unknown function or type
508 warnings that the compiler will print for any given name in a single
509 compilation. This prevents excessive amounts of output when the real
510 problem is a missing definition (as opposed to a typo in the use.)")
512 ;;; Make an entry in the *UNDEFINED-WARNINGS* describing a reference
513 ;;; to NAME of the specified KIND. If we have exceeded the warning
514 ;;; limit, then just increment the count, otherwise note the current
517 ;;; Undefined types are noted by a condition handler in
518 ;;; WITH-COMPILATION-UNIT, which can potentially be invoked outside
519 ;;; the compiler, hence the BOUNDP check.
520 (defun note-undefined-reference (name kind
)
522 ;; Check for boundness so we don't blow up if we're called
523 ;; when IR1 conversion isn't going on.
526 ;; FIXME: I'm pretty sure the INHIBIT-WARNINGS test below
527 ;; isn't a good idea; we should have INHIBIT-WARNINGS
528 ;; affect compiler notes, not STYLE-WARNINGs. And I'm not
529 ;; sure what the BOUNDP '*LEXENV* test above is for; it's
530 ;; likely a good idea, but it probably deserves an
531 ;; explanatory comment.
532 (policy *lexenv
* (= inhibit-warnings
3))
533 ;; KLUDGE: weird decoupling between here and where we're
534 ;; going to signal the condition. I don't think we can
535 ;; rewrite this using SIGNAL and RESTART-CASE (to take
536 ;; advantage of the (SATISFIES HANDLE-CONDITION-P)
537 ;; handler, because if that doesn't handle it the ordinary
538 ;; compiler handlers will trigger.
541 (:variable
(make-condition 'warning
))
542 ((:function
:type
) (make-condition 'style-warning
)))
544 (rassoc 'muffle-warning
545 (lexenv-handled-conditions *lexenv
*))))))
546 (let* ((found (dolist (warning *undefined-warnings
* nil
)
547 (when (and (equal (undefined-warning-name warning
) name
)
548 (eq (undefined-warning-kind warning
) kind
))
551 (make-undefined-warning :name name
:kind kind
))))
552 (unless found
(push res
*undefined-warnings
*))
553 (multiple-value-bind (context old
)
554 (find-error-context (list name
) (undefined-warning-warnings res
))
556 (when (or (not *undefined-warning-limit
*)
557 (< (undefined-warning-count res
) *undefined-warning-limit
*))
558 (push context
(undefined-warning-warnings res
)))
559 (incf (undefined-warning-count res
))))))
562 ;; The compiler tracks full calls that were emitted so that it is possible
563 ;; to detect a definition of a compiler-macro occuring after the first
564 ;; compile-time observed use of (vs. actual call of) that function name.
566 ;; The call count is not reset if the function gets redefined (where the
567 ;; macro could briefly be out-of-sync), but this choice is deliberate.
568 ;; We're not trying to find and report all possible ways that users can
569 ;; introduce semantic glitches, only trying to signal something that is
570 ;; otherwise not always obvious in a totally working built-from-scratch
571 ;; user system, absent any interactive changes.
573 ;; Note on implementation: originally I thought about doing something
574 ;; based on whether the name got an APPROXIMATE-FUN-TYPE and the :WHERE-FROM
575 ;; was :ASSUMED - which together imply that the function did not exist *and*
576 ;; that it was not a NOTINLINE call, however that proved to be fragile.
577 ;; The current approach is reliable, at a cost of ~3 words per function.
579 (defun warn-if-compiler-macro-dependency-problem (name)
580 (unless (sb!xc
:compiler-macro-function name
)
581 (let ((status (car (info :function
:emitted-full-calls name
))))
582 (when (and (integerp status
) (oddp status
))
583 ;; Show the total number of calls, because otherwise the warning
584 ;; would be worded rather obliquely: "N calls were compiled
585 ;; not in the scope of a notinline declaration" which is, to me,
586 ;; worse than matter-of-factly stating that N calls were compiled.
587 ;; This is why I don't bother collecting both statistics.
588 ;; It's the tail wagging the dog: the message dictates what to track.
590 ;; Grammar note - starting a sentence with a numeral is wrong.
591 (!uncross-format-control
592 "~@<~@(~D~) call~:P to ~/sb!impl:print-symbol-with-prefix/ ~2:*~[~;was~:;were~] ~
593 compiled before a compiler-macro was defined for it. A declaration of ~
594 NOTINLINE at the call site~:P will eliminate this warning, ~
595 as will defining the compiler-macro before its first potential use.~@:>")
596 (ash status -
2) name
)))))
598 ;; Inlining failure scenario 1 [at time of proclamation]:
599 ;; Full call to F is emitted not in the scope of a NOTINLINE, with no definition
600 ;; of F available, and then it's proclaimed INLINE. If F was defined already,
601 ;; it would have been used, unless the expansion limit was hit.
603 (defun warn-if-inline-failed/proclaim
(name new-inlinep
)
604 (when (eq new-inlinep
:inline
)
605 (let ((warning-count (emitted-full-call-count name
)))
606 (when (and warning-count
607 ;; Warn only if the the compiler did not have the expansion.
608 (not (info :function
:inline-expansion-designator name
))
609 ;; and if nothing was previously known about inline status
610 ;; so that repeated proclamations don't warn. NIL is a valid
611 ;; value for :inlinep in the globaldb so use the 2nd result.
612 (not (nth-value 1 (info :function
:inlinep name
))))
614 'inlining-dependency-failure
616 (!uncross-format-control
617 "~@<Proclaiming ~/sb!impl:print-symbol-with-prefix/ to be INLINE, but ~D call~:P to it ~
618 ~:*~[~;was~:;were~] previously compiled. A declaration of NOTINLINE ~
619 at the call site~:P will eliminate this warning, as will proclaiming ~
620 and defining the function before its first potential use.~@:>")
621 :format-arguments
(list name warning-count
))))))
623 ;; Inlining failure scenario 2 [at time of call]:
624 ;; F is not defined, but either proclaimed INLINE and not declared
625 ;; locally notinline, or expressly declared locally inline.
626 ;; Warn about emitting a full call at that time.
628 ;; It could be friendlier to present this warning as one summary
629 ;; at the end of a compilation unit, but that is not as important as
630 ;; just getting the warning across.
631 ;; [The point of deferring a warning is that some future event can resolve it
632 ;; - like an undefined function becoming defined - but there's nothing
633 ;; that can resolve absence of a definition at a point when it was needed]
635 ;; Should we regard it as more serious if the inline-ness of the global
636 ;; function was lexically declared? Is "Inline F here" stronger than
637 ;; "It would generally be a good idea to inline F everywhere"?
639 ;; Don't be too put off by the above concerns though. It's not customary
640 ;; to write (DECLAIM INLINE) after the function, or so far separated from it
641 ;; that intervening callers know it to be proclaimed inline, and would have
642 ;; liked to have a definition, but didn't.
644 (defun warn-if-inline-failed/call
(name lexenv count-cell
)
645 ;; Do nothing if the inline expansion is known - it wasn't used
646 ;; because of the expansion limit, which is a different problem.
647 (unless (or (logtest 2 (car count-cell
)) ; warn at most once per name
648 (info :function
:inline-expansion-designator name
))
649 ;; This function is only called by PONDER-FULL-CALL when NAME
650 ;; is not lexically NOTINLINE, so therefore if it is globally INLINE,
651 ;; there was no local declaration to the contrary.
652 (when (or (eq (info :function
:inlinep name
) :inline
)
653 (let ((fun (let ((*lexenv
* lexenv
))
654 (lexenv-find name funs
:test
#'equal
))))
657 (eq (defined-fun-inlinep fun
) :inline
))))
658 ;; Set a bit saying that a warning about the call was generated,
659 ;; which suppresses the warning about either a later
660 ;; call or a later proclamation.
661 (setf (car count-cell
) (logior (car count-cell
) 2))
662 ;; While there could be a different style-warning for
663 ;; "You should put the DEFUN after the DECLAIM"
664 ;; if they appeared reversed, it's not ideal to warn as soon as that.
665 ;; It's only a problem if something failed to be inlined in account of it.
667 'inlining-dependency-failure
669 (if (info :function
:assumed-type name
)
670 (!uncross-format-control
671 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because no definition ~
672 for it was seen prior to its first use.~:@>")
673 ;; This message sort of implies that source form is the
674 ;; only reasonable representation in which an inline definition
675 ;; could have been saved, which isn't in general true - it could
676 ;; be saved as a parsed AST - but I don't really know how else to
677 ;; phrase this. And it happens to be true in SBCL, so it's not wrong.
678 (!uncross-format-control
679 "~@<Call to ~/sb!impl:print-symbol-with-prefix/ could not be inlined because its source code ~
680 was not saved. A global INLINE or SB-EXT:MAYBE-INLINE proclamation must be ~
681 in effect to save function definitions for inlining.~:@>"))
682 :format-arguments
(list name
)))))