Disallow inlining failures in self-build.
[sbcl.git] / src / interpreter / sexpr.lisp
blob35e689faa623da6f2b97f948816c1108a971a7d6
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
10 (in-package "SB-INTERPRETER")
12 ;;;; This interpreter is a hybrid of a traditional recursive descent EVAL,
13 ;;;; augmented with some semantic preprocessing. But unlike most other
14 ;;;; preprocessing implementations which produce code which emulates compiled
15 ;;;; code as closely as possible by performing macroexpansion once only,
16 ;;;; we attempt to emulate a non-preprocessing interpreter.
17 ;;;; The motivation for this is parenthetically revealed in the X3J13 issue
18 ;;;; discussing the removal of COMPILER-LET, saying:
19 ;;;; "Some users have indicated they dislike interpreters which do a semantic
20 ;;;; prepass, because they like to be able to dynamically redefine macros
21 ;;;; while debugging."
22 ;;;; In addition, preprocessing of a form is done as late as possible -
23 ;;;; only when a form is reached - and only enough to descend one level.
25 ;;; SEXPRs are the basic building blocks of interpreted code.
26 ;;; We store a function to call (in the HANDLER) as well as the original
27 ;;; list representation of the form in case it has to be re-preprocessed.
28 (defstruct (sexpr (:conc-name sexpr-)
29 (:constructor %make-sexpr (handler %form))
30 (:copier nil))
31 (handler nil :type cons)
32 (%form nil :read-only t)) ; the original source form
34 ;;; A SEXPR's HANDLER is a cons. This constructs a HANDLER.
35 (defun %handler (function payload) (cons function payload))
37 ;;; Not all "sexprs" are actually instances of SEXPR,
38 ;;; because self-evaluating constants are stored as-is.
39 ;;; Get the original source out of a SEXPR-equivalent object.
40 (defun sexpr-form (object)
41 (if (%instancep object)
42 (progn (aver (sexpr-p object)) (sexpr-%form object))
43 object))
45 ;;; Wrapper to hide the argument passing convention.
46 ;;; This is preferable to using a closure over the handler-function and args
47 ;;; because it makes for better inspectability and is often more compact.
48 ;;; The smallest closure requires 4 words; this has a lower bound of 2 words.
49 ;;;
50 ;;; FIXME: the preceding claim about inspectability is no longer true now that
51 ;;; we have STORE-CLOSURE-DEBUG-POINTER which can preserve both the lexical
52 ;;; and dynamic state. And the efficiency claim might never have been true.
53 (defmacro handler (function &rest args)
54 (cond ((not args)
55 `(%handler ,function 0))
56 ((not (cdr args))
57 `(%handler ,function ,(first args)))
58 ((not (cddr args))
59 `(%handler ,function (cons ,(first args) ,(second args))))
61 `(%handler ,function (vector ,@args)))))
63 (defmacro with-form-data (names input &body body)
64 (declare (list names))
65 `(symbol-macrolet
66 ,(case (length names)
67 (1 `((,(first names) ,input)))
68 (2 `((,(car names) (car ,input)) (,(cadr names) (cdr ,input))))
69 (t (loop for name in names for i from 0
70 collect `(,name (svref ,input ,i)))))
71 ,@body))
73 ;;; Wrapper on LAMBDA for writing handlers.
74 ;;; (HLAMBDA NAME (DATA ENV SEXPR) ...)
75 ;;; -> (NAMED-LAMBDA (EVAL NAME) (#:DATA ENV SEXPR)
76 ;;; (WITH-FORM-DATA DATA #:DATA ...)
77 ;;;
78 ;;; If DATA is a symbol, it is used literally as the first formal parameter
79 ;;; in the lambda; if it is a list, the lambda receives one thing which is
80 ;;; destructured according to the argument passing convention.
81 ;;;
82 ;;; If SEXPR is omitted it becomes a gensym which gets declared ignore.
83 ;;; All handlers have identical signature but most don't use the third argument.
84 ;;; Only a handler which can restart by discarding internal state needs it.
85 ;;;
86 (defmacro hlambda (name captured-vars vars &body body)
87 (declare (list captured-vars))
88 (let ((data (gensym "DATA")) (ignore))
89 ;; Allow &AUX vars: (HLAMBDA NAME (DATA ENV &AUX FOO) ...) has no 3rd arg.
90 (let ((aux-vars (member '&aux vars)))
91 (when (= (length (ldiff vars aux-vars)) 1)
92 (let ((sexpr (make-symbol "SEXPR")))
93 (setq vars (nconc (subseq vars 0 1) (list sexpr) aux-vars)
94 ignore `((ignore ,sexpr))))))
95 (setq name (cons '.eval. (if (listp name) name (list name))))
96 `(handler ,(if captured-vars
97 (if (= (length captured-vars) 1)
98 `(named-lambda ,name (,(first captured-vars) ,@vars)
99 (declare ,+handler-optimize+ ,@ignore)
100 ,@body)
101 `(named-lambda ,name (,data ,@vars)
102 (declare ,+handler-optimize+ ,@ignore)
103 (with-form-data ,captured-vars ,data ,@body)))
104 `(named-lambda ,name (,data ,@vars)
105 (declare ,+handler-optimize+ (ignore ,data) ,@ignore)
106 ,@body))
107 ,@captured-vars)))
109 ;;; DISPATCH receives a SEXPR object or sexpr-equivalent object.
110 ;;; If a SEXPR, its handler is called to produce a value. All other Lisp
111 ;;; objects are treated as constants.
112 ;;; N.B.: herein SEXPR sometimes mean either a SEXPR object, or a constant
113 ;;; object that needs no wrapping. The union of those could be envisioned
114 ;;; as a deftype DISPATCHABLE - which is nowise helpful in practice.
116 ;;; It is always ok to call DISPATCH on a SEXPR-equivalent object, but in two
117 ;;; places %DISPATCH is used to avoid a spurious code-deletion note where
118 ;;; SEXPR is known to be a dispatchable instance. This is one of the
119 ;;; "spurious but not wrong" notes that the compiler can emit.
120 (declaim (inline dispatch %dispatch))
121 (defun %dispatch (sexpr env)
122 (declare #.+handler-optimize+)
123 (let ((handler (sexpr-handler sexpr)))
124 (funcall (the function (car handler)) (cdr handler) env sexpr)))
125 (defun dispatch (sexpr env)
126 (declare #.+handler-optimize+)
127 (if (%instancep sexpr) (%dispatch sexpr env) sexpr))
129 ;;; Helper for RETURN-CONSTANT.
130 ;;; Would be a local function except for some uses of LOAD-TIME-VALUE.
131 (defun %const (x env sexpr)
132 (declare (ignore env sexpr) #.+handler-optimize+)
135 ;;; Return a handler that returns a constant.
136 ;;; The %SEXPR constructor elides a handler for constants,
137 ;;; but there are cases where NIL sneaks through and demands a callable handler.
138 ;;; We avoid generating N copies of such handler. Same goes for 0 and T.
139 (defun return-constant (object)
140 (cond ((null object) (load-time-value (handler #'%const nil)))
141 ((eq object t) (load-time-value (handler #'%const t)))
142 ((eql object 0) (load-time-value (handler #'%const 0)))
143 (t (handler #'%const object))))
145 (defun return-constant-values (values env sexpr)
146 (declare (ignore env sexpr) #.+handler-optimize+)
147 (values-list values))
149 ;; Forward defs
150 (declaim (ftype function digest-form %eval eval-setq))
152 ;;; Return a SEXPR object that will, when dispatched, evaluate FORM.
153 ;;; Unlike optimizations on SEXPRS whereby they install the most-specific
154 ;;; applicable handler for a given source form when first dispatched, constants
155 ;;; can't do that because by the time DIGEST-FORM is dispatched, it's too late
156 ;;; to install a function other than #'RETURN-CONSTANT. The goal here is to
157 ;;; avoid funcalling anything on constant forms. Therefore:
158 ;;; 1. For most self-evaluating objects, FORM itself is returned.
159 ;;; Structures are self-evaluating, but have to be wrapped because DISPATCH
160 ;;; assumes that anything satisfying %INSTANCEP is a dispatchable object.
161 ;;; 2. If FORM is a syntactically correct QUOTE form, return the quoted thing
162 ;;; subject to the constraint in condition 1. SEXPRs are prepared in advance
163 ;;; of being EVALed, so no errors may be signaled on malformed QUOTE forms.
165 ;;; Todo: there is still more opportunity for lifting singleton PROGN forms.
166 ;;; Lots of standard macros expand into (PROGN (ONE-THING)), which, if it appears
167 ;;; as the argument to %SEXPR should just become a SEXPR for (ONE-THING).
169 (defun %sexpr (form)
170 (let (cdr obj)
171 (cond ((and (atom form)
172 (not (%instancep form))
173 (or (not (symbolp form))
174 ;; Only builtin constants and keywords are assumed
175 ;; to be written in stone. Others generate a continuable
176 ;; error on redefinition, and this eval will always
177 ;; get the current definition.
178 (and (eq (info :variable :kind form) :constant)
179 (memq (symbol-package form)
180 (load-time-value (list (find-package "KEYWORD")
181 (find-package "CL"))))
182 (progn (setq form (symbol-value form)) t))))
183 form)
184 ((and (consp form)
185 (eq (car form) 'quote)
186 (consp (setq cdr (cdr form)))
187 (null (cdr cdr))
188 (not (%instancep (setq obj (car cdr)))))
189 obj)
190 (t ; DIGEST-FORM is the generic handler
191 (%make-sexpr (handler #'digest-form form) form)))))
193 ;;; Return a SEXPR that will evaluate zero or more FORMS.
194 (defun %progn (forms)
195 ;; The handler for PROGN contains code to handle 0, 1, 2, 3+ subforms
196 ;; but it's worthwhile to special-case 0 and 1 here too
197 ;; because it avoids some consing and preprocessing.
198 (%sexpr (if (and (listp forms) (not (cdr forms)))
199 (first forms) ; ok if (PROGN) or (PROGN form)
200 `(progn ,@forms))))
202 ;;; Return the binding of a lexical function indexed by INDEX in ENV.
203 ;;; INDEX must be the frame-ptr returned from a call to FIND-LEXICAL-FUN.
204 ;;; This is for runtime use by a SEXPR handler.
205 ;;; The name is borrowed from the standard function "FDEFINITION" -
206 ;;; this does not have anything to do with #<fdefn> objects.
207 (defun local-fdefinition (index env)
208 (declare (fixnum index) #.+handler-optimize+)
209 (%cell-ref env index))
211 ;;; Return a frame-pointer for FNAME if it is a local function,
212 ;;; or return :MACRO if it names either a local *or* global macro.
213 ;;; Return NIL if none of the above.
214 (defun local-fn-frame-ptr (fname env)
215 (multiple-value-bind (kind definition frame-ptr) (find-lexical-fun env fname)
216 (if definition
217 (if (eq kind :macro) :macro frame-ptr)
218 (if (and (symbolp fname) (macro-function fname)) :macro nil))))
220 ;;; Fast handlers for lexical var access. This is a speed and space win,
221 ;;; the latter since it avoids some consing for small fixed frame-ptr.
223 ;;; (REF 0 N) -> (SVREF (ENV-VARS ENV) N)
224 ;;; (REF 1 N) -> (SVREF (ENV-VARS (ENV-PARENT ENV)) N)
225 ;;; (REF 2 N) -> (SVREF (ENV-VARS (ENV-PARENT (ENV-PARENT ENV))) N)
226 ;;; etc
227 ;;; A fast assembler could generate accessors on demand - and then I'd cache
228 ;;; them - as the code is entirely boilerplate. Lacking that, hardwire some.
229 (declaim ((simple-array t (4 10)) *fast-lexvar-reffers* *fast-lexvar-setters*))
230 (macrolet ((ref (up across)
231 (declare (optimize (speed 0))) ; silence the generic math note
232 `(svref (env-payload ,(let ((e 'env))
233 (dotimes (i up e)
234 (setq e `(env-parent ,e)))))
235 ,across))
236 (array-of (n-depths n-cells)
237 (declare (optimize (speed 0))) ; silence the generic math note
238 `(make-array
239 ',(list n-depths n-cells)
240 :initial-contents
241 (list ,@(loop for depth below n-depths
242 collect
243 `(list ,@(loop for j below n-cells
244 collect `(access ,depth ,j))))))))
245 (defparameter *fast-lexvar-reffers*
246 (macrolet ((access (up across)
247 `(hlambda GET-VAR () (env) (ref ,up ,across))))
248 (array-of 4 10))) ; for 4 scopes and 10 names per scope you can go fast
249 (defparameter *fast-lexvar-setters* ; These are lambdas, not handlers
250 (macrolet ((access (up across)
251 `(named-lambda (eval SET-VAR) (form env sexpr)
252 (declare #.+handler-optimize+ (ignore sexpr))
253 (setf (ref ,up ,across) (dispatch form env)))))
254 (array-of 4 10))))
256 (declaim (ftype (function (symbol t t) nil) typecheck-fail typecheck-fail/ref)
257 (ftype (function (t &rest t) nil) values-typecheck-fail)
258 (ftype (function (function fixnum) nil)
259 err-too-few-args err-too-many-args))
261 (macrolet ((with-indices (special-case general-case)
262 `(let ((depth (frame-ptr-depth frame-ptr))
263 (slot (frame-ptr-cell-index frame-ptr)))
264 (if (and (< depth (array-dimension *fast-lexvar-reffers* 0))
265 (< slot (array-dimension *fast-lexvar-reffers* 1)))
266 ,special-case
267 ,general-case))))
269 ;; Return a handler that accesses a lexical var given its FRAME-PTR.
270 ;; Anything not in *FAST-LEXVAR-REFFERS* gets a general-purpose routine.
271 (defun lexvar-reffer (frame-ptr type)
272 (if type
273 ;; There are no specialized reffers with type-checking
274 ;; because the check is slow anyway.
275 (hlambda GET-VAR (frame-ptr type) (env)
276 (let ((val (%cell-ref env frame-ptr)))
277 (if (itypep val type)
279 (typecheck-fail/ref (frame-symbol env frame-ptr) val type))))
280 (with-indices (aref *fast-lexvar-reffers* depth slot)
281 (hlambda GET-VAR (frame-ptr) (env) (%cell-ref env frame-ptr)))))
283 (defun lexvar-setter (frame-ptr newval type)
284 (if type
285 ;; There are no no specialized setters with type-checking
286 ;; because the check is slow anyway.
287 (hlambda SET-VAR (newval frame-ptr type) (env)
288 (let ((newval (dispatch newval env)))
289 (if (itypep newval type)
290 (setf (%cell-ref env frame-ptr) newval)
291 (typecheck-fail (frame-symbol env frame-ptr) newval type))))
292 (with-indices (handler (aref *fast-lexvar-setters* depth slot) newval)
293 (hlambda SET-VAR (newval frame-ptr) (env)
294 (setf (%cell-ref env frame-ptr) (dispatch newval env)))))))
296 ;;; Access SYMBOL's dynamic value, enforcing TYPE if non-nil,
297 ;;; and checking for change of its :VARIABLE :KIND if PARANOID,
298 ;;; allowing the possibility that a DEFVAR changed to DEFINE-SYMBOL-MACRO
299 ;;; for example.
300 (defun specvar-reffer (symbol type &optional paranoid)
301 (macrolet ((safe-symbol-value ()
302 ;; HLAMBDA lowers safety because the interpreter itself
303 ;; is (hopefully) free of bugs, but we always want to check
304 ;; that a special variable is BOUNDP.
305 '(locally (declare (optimize (safety 3)))
306 (symbol-value symbol))))
307 (cond ((and type paranoid)
308 (hlambda SYMEVAL (symbol) (env sexpr)
309 (if (member (info :variable :kind symbol) '(:alien :macro))
310 (digest-form symbol env sexpr)
311 (let ((val (safe-symbol-value)))
312 (if (itypep val type)
314 (typecheck-fail/ref symbol val type))))))
315 ((and type (not paranoid))
316 (hlambda SYMEVAL (symbol type) (env)
317 (progn env) ; ignore
318 (let ((val (safe-symbol-value)))
319 (if (itypep val type)
321 (typecheck-fail/ref symbol val type)))))
322 (paranoid
323 (hlambda SYMEVAL (symbol type) (env sexpr)
324 (if (member (info :variable :kind symbol) '(:alien :macro))
325 (digest-form symbol env sexpr)
326 (safe-symbol-value))))
328 (hlambda SYMEVAL (symbol) (env)
329 (progn env) ; ignore
330 (safe-symbol-value))))))
332 (defconstant +mode-mask-shift+ 4)
333 (defconstant +arg-mode-mask+ #b1110)
334 (defconstant +optional-arg+ #b0000)
335 (defconstant +keyword-arg+ #b0010)
336 (defconstant +supplied-p-var+ #b0100)
337 (defconstant +aux-var+ #b0110)
338 (defconstant +rest-arg+ #b1000)
339 ;;; This constant MUST be 1 so it can be used as an index skip count
340 ;;; versus having to write (if (logtest foo +has-default+) (incf thing))
341 (defconstant +has-default+ #b0001)
343 (defmacro argument-keyword-index (encoding)
344 `(ash ,encoding (- +mode-mask-shift+)))
346 ;;; Compress LAMBDA-LIST into a representation that encodes which arguments
347 ;;; have defaulting forms and/or supplied-p variables.
348 (defun encode-lambda-bindings (lambda-list form-converter)
349 (let ((n-optional 0) (n-keys -1) fancy-vars decoder keys)
350 (multiple-value-bind (llks required optional rest keyword-args aux)
351 (parse-lambda-list lambda-list
352 :accept (lambda-list-keyword-mask
353 '(&optional &rest &key &allow-other-keys &aux))
354 :silent t)
355 ;; Do I need more syntax checking? PARSE-LAMBDA-LIST enforces syntactic
356 ;; validity but not that the vars are bindable; however the specialness
357 ;; check enforces the latter, so we're probably ok.
358 (flet ((add-var (x mode)
359 (multiple-value-bind (key var)
360 (if (eq mode +keyword-arg+)
361 (cond ((atom x) (values (keywordicate x) x))
362 ((consp (car x)) (values (caar x) (cadar x)))
363 (t (values (keywordicate (car x))
364 (car x))))
365 (values nil (if (symbolp x) x (car x))))
366 (let* ((default (if (listp x) (funcall form-converter x)))
367 (encoding (logior mode (if default +has-default+ 0))))
368 (push var fancy-vars)
369 (when (eq mode +keyword-arg+)
370 (setq encoding (logior (ash (incf n-keys) +mode-mask-shift+)
371 encoding))
372 (push key keys))
373 (push encoding decoder)
374 (when default
375 (push default decoder)))
376 (when (and (/= mode +aux-var+) (proper-list-of-length-p x 3))
377 (push (third x) fancy-vars)
378 (push +supplied-p-var+ decoder)))))
379 (dolist (x optional)
380 (incf n-optional)
381 (add-var x +optional-arg+))
382 (when rest
383 (push (car rest) fancy-vars)
384 (push +rest-arg+ decoder))
385 (dolist (x keyword-args)
386 (add-var x +keyword-arg+))
387 (dolist (x aux)
388 (add-var x +aux-var+)))
389 (values required (nreverse fancy-vars)
390 ;; compute (length keys) before nreconc smashes them
391 (make-keyword-bits (length keys) rest
392 (ll-kwds-keyp llks) (ll-kwds-allowp llks))
393 (if (or (ll-kwds-keyp llks) decoder)
394 (coerce (nreconc keys (nreverse decoder)) 'vector))
395 n-optional))))
397 ;;; If BODY matches (BLOCK <name> . <forms>) then return the block name, the
398 ;;; forms, and an indicator of whether it is OK to create the block and bind
399 ;;; variables at the same time. If not a block, return 0 and forms unaltered.
401 ;;; The optimization of eliding an extra ENV is performed only if no nontrival
402 ;;; defaulting SEXPRs exist. A "trivial" one is either a constant or a reference
403 ;;; to a variable (not a macro). Absent such a thing, nobody could notice that
404 ;;; there aren't actually two different lexical contours, so creating variable
405 ;;; bindings and a block may occur simultaneously.
406 ;;; [In fact, in such case, there is no difference between parallel and serial
407 ;;; binding, so the LET* part of the binding loop could be absorbed by the LET
408 ;;; part, which would have to be informed how to decode a fancy-arg vector]
409 ;;; The test is extremely paranoid by "wrongly" saying that a form can be a
410 ;;; macro despite the lambda list itself creating a binding for the symbol
411 ;;; in question. LAMBDA can cause fewer symbols to be macros, but never more.
412 ;;; Therefore it is fine to disregard the lambda decoder. For example in:
413 ;;; (symbol-macrolet ((foo (hair))) (lambda (x &optional (foo x)) ...)
414 ;;; FOO is thought to be a macro.
416 (defun extract-lambda-block (body decoder env)
417 (labels ((definitely-var-ref-p (x)
418 (and (symbolp x)
419 (case (nth-value 1 (find-lexical-var env x))
420 ((:normal :special) t)
421 (:macro nil)
422 (t (neq (info :variable :kind x) :macro)))))
423 (trivial-expression-p (x)
424 (or (not (sexpr-p x)) ; a constant
425 (definitely-var-ref-p (sexpr-form x)))))
426 (if (and (listp body)
427 (listp (car body))
428 (eq (caar body) 'block)
429 (not (cdr body))
430 (symbolp (cadar body)))
431 (let ((body (cdar body))) ; = (BLOCK-NAME . FORMS)
432 (values (car body) (cdr body)
433 (every #'trivial-expression-p decoder)))
434 (values 0 body nil))))
436 ;;; Produce a LAMBDA-FRAME for a PROTO-FN.
437 ;;; ENV is for package-lock checks and also to make a quick guess about
438 ;;; whether a block can be created at the same time as the variable bindings.
439 (defun digest-lambda (env proto-fn)
440 (binding*
441 (((required-args other-args keyword-bits decoder n-opt)
442 (encode-lambda-bindings (proto-fn-lambda-list proto-fn)
443 (lambda (x) (%sexpr (second x)))))
444 (decls (proto-fn-decls proto-fn))
445 (n-required (length required-args))
446 (n-other (length other-args))
447 (n-lambda-vars (+ n-required n-other))
448 (declared-specials (declared-specials decls))
449 (free-specials
450 (remove-if (lambda (sym)
451 (or (memq sym required-args) (memq sym other-args)))
452 declared-specials))
453 (symbols
454 (let ((a (make-array (+ n-lambda-vars (length free-specials)))))
455 (replace a required-args)
456 (replace a other-args :start1 n-required)
457 (replace a free-specials :start1 n-lambda-vars)
458 (dotimes (i n-lambda-vars a) ; Unique-ify the binding cells.
459 (setf (svref a i) (list (svref a i))))))
460 (special-b
461 (mark-bound-specials env declared-specials symbols n-lambda-vars))
462 (required-mask (lognot (ash -1 n-required)))
463 (required-specials ; one list for PROGV in WITH-LET-BINDINGS
464 (nreverse ; WITH-LET-BINDINGS uses PUSH to accumulate values
465 (collect-progv-symbols
466 symbols n-lambda-vars (logand special-b required-mask))))
467 (other-specials ; one list per PROGV in WITH-LET*-BINDINGS.
468 (mapcar #'list
469 (collect-progv-symbols
470 symbols n-lambda-vars (logandc2 special-b required-mask))))
471 ((block-name forms block-share-env-p)
472 (extract-lambda-block (proto-fn-forms proto-fn) decoder env))
473 (frame (make-lambda-frame
474 :min-args n-required :n-optional n-opt
475 :n-bound-vars n-lambda-vars :keyword-bits keyword-bits
476 :symbols symbols :values (or decoder #())
477 :special-b special-b
478 :specials (if required-specials
479 (cons required-specials other-specials)
480 other-specials)
481 :declarations decls :%policy (new-policy env decls)
482 :block-name block-name :share-block-p block-share-env-p
483 :sexpr (%progn forms))))
484 (process-typedecls frame env n-lambda-vars symbols)
485 (setf (proto-fn-%frame proto-fn) frame
486 (proto-fn-cookie proto-fn) *globaldb-cookie*)
487 (values frame *globaldb-cookie*)))
489 (defun make-local-fn-scope (decls funs forms env)
490 (let ((specials (free-specials env decls)))
491 (process-typedecls (%make-local-fn-scope
492 decls (new-policy env decls)
493 funs (%progn forms) specials)
494 env 0 specials)))
496 (defun err-too-few-args (fun n-args)
497 (let ((frame (interpreted-function-frame fun)))
498 (ip-error "~S received ~D argument~:P but expects~:[ at least~;~] ~D."
499 (name-for-fun fun) n-args
500 (eql (lambda-frame-min-args frame) (lambda-frame-max-args frame))
501 (lambda-frame-min-args frame))))
503 (defun err-too-many-args (fun n-args)
504 (let ((frame (interpreted-function-frame fun)))
505 (ip-error "~S received ~D argument~:P but expects~:[ at most~;~] ~D"
506 (name-for-fun fun) n-args
507 (eql (lambda-frame-min-args frame) (lambda-frame-max-args frame))
508 (lambda-frame-max-args frame))))
510 (defmacro with-lambda-frame ((frame-var fun if-invalid) &body if-valid)
511 ;; If any global variable has changed its :KIND, this function's lambda
512 ;; variables will be re-checked for specialness, constness, etc.;
513 ;; also, internally cached cached macroexpansions get discarded.
514 `(if (eq (interpreted-function-cookie ,fun) *globaldb-cookie*)
515 (let ((,frame-var (interpreted-function-frame ,fun)))
516 ,@if-valid)
517 (progn (atomic-incf *invalidation-count*) ; for testing cache eviction
518 ,if-invalid)))
520 ;;; LIST is a list of supplied keywords arguments to a function.
521 ;;; CONTROL-BITS are from the lambda frame, and ALLOWED is a vector
522 ;;; of the permitted keywords but has extra stuff after them, so scanning
523 ;;; must restrict itself to strictly the N-KEYS specified by CONTROL-BITS.
524 (defun validate-keywords (list control-bits allowed)
525 (declare (list list) (fixnum control-bits) (simple-vector allowed))
526 (labels ((check-odd-length (tail n-seen)
527 (let ((n-more (length tail))) ; just check for oddness
528 (if (oddp n-more)
529 (fail-odd-length (+ n-seen n-more)))))
530 (fail-odd-length (n)
531 (ip-error "odd number of &KEY arguments: ~D" n))
532 (fail-other-key ()
533 (let ((n-allowed (keyword-bits-n-keys control-bits)) bad)
534 (loop for (key val) on list by #'cddr ; rescan to collect them
535 unless (or (eq key :allow-other-keys)
536 (find key allowed :end n-allowed))
537 do (pushnew key bad))
538 (let ((plural (cdr bad)))
539 (ip-error "Keyword~*~:[~;s~]~2:* ~{~S~^,~} ~:[is~;are~] not ~
540 ~:[allowed.~;in the allowed set ~:*~S~]"
541 (nreverse bad) plural
542 (replace (make-list n-allowed) allowed))))))
543 (if (keyword-bits-allowp control-bits)
544 (check-odd-length list 0)
545 (let ((n-allowed (keyword-bits-n-keys control-bits))
546 (allow-other +none+) ; the observed value of :ALLOW-OTHER-KEYS
547 (n-visited 0)
548 (tail list)
549 (seen-unknown-key-p nil))
550 (loop
551 (when (endp tail)
552 (if seen-unknown-key-p
553 (fail-other-key)
554 (return)))
555 (let ((key (pop tail))
556 (value (if tail (pop tail) (fail-odd-length (1+ n-visited)))))
557 (incf n-visited 2)
558 ;; The code below is designed to pass or fail as soon as possible
559 (cond ((neq key :allow-other-keys)
560 (unless (find key allowed :end n-allowed)
561 (when (eq allow-other nil)
562 (fail-other-key))
563 (setq seen-unknown-key-p t)))
564 ((eq allow-other +none+) ; = unseen so far
565 (if value
566 (return (check-odd-length tail n-visited))
567 (progn
568 (when seen-unknown-key-p
569 (fail-other-key))
570 (setq allow-other nil)))))))))))
572 (declaim (ftype (sfunction (function) function) interpreted-applicator))
573 ;;; Get a parsed LAMBDA-FRAME from the proto-fn, reinstall a more specific
574 ;;; lambda applicator, and jump to it.
575 (defun interpreter-trampoline (fun &rest args)
576 (setf (values (interpreted-function-frame fun)
577 (interpreted-function-cookie fun))
578 (proto-fn-frame (fun-proto-fn fun) (interpreted-function-env fun)))
579 (apply (setf (funcallable-instance-fun fun) (interpreted-applicator fun))
580 args))
582 ;;; The most general case of interpreted function application.
583 ;;; All combinations of fancy args are allowed and any var can be special.
584 ;;; This is a ton of code to inline, but it uses the same concept as for
585 ;;; inlined %%EVAL - there is fast version and a slow version with extra
586 ;;; extra wrapping for when hooks are in use.
588 (define-symbol-macro *absent* (%make-lisp-obj sb-vm:unbound-marker-widetag))
589 (declaim (maybe-inline apply-lambda))
590 (defun apply-lambda (frame fun n-args args)
591 (declare (list args))
592 (let* ((values (make-array (lambda-frame-n-bound-vars frame)))
593 (symbol-cells (cons (lambda-frame-min-args frame)
594 (frame-symbols frame)))
595 (new-env
596 (if (lambda-frame-share-block-p frame)
597 (make-lambda-env
598 (interpreted-function-env fun) values symbol-cells frame
599 (list (lambda-frame-block-name frame)))
600 (make-var-env
601 (interpreted-function-env fun) values symbol-cells frame)))
602 (special-b (frame-special-b frame))
603 (specials (frame-specials frame))
604 (decoder-index
605 (1- (keyword-bits-n-keys (lambda-frame-keyword-bits frame))))
606 (arg-supplied-p)
607 (tail args))
608 (declare (index-or-minus-1 decoder-index) (list tail))
609 (labels ((instruction ()
610 (svref (frame-values frame) (incf decoder-index)))
611 (fancy-arg (&aux (mode (the fixnum (instruction))))
612 (case (logand mode +arg-mode-mask+)
613 (#.+optional-arg+
614 (cond ((setq arg-supplied-p tail)
615 (incf decoder-index (logand mode +has-default+))
616 (pop tail))
617 ((logtest mode +has-default+)
618 (dispatch (instruction) new-env))))
619 (#.+keyword-arg+
620 (let* ((key (svref (frame-values frame)
621 (argument-keyword-index mode)))
622 (val (getf tail key *absent*)))
623 (cond ((setq arg-supplied-p (neq val *absent*))
624 (incf decoder-index (logand mode +has-default+))
625 val)
626 ((logtest mode +has-default+)
627 (dispatch (instruction) new-env)))))
628 (#.+supplied-p-var+ (if arg-supplied-p t nil))
629 (#.+aux-var+
630 (if (logtest mode +has-default+)
631 (dispatch (instruction) new-env)))
632 (#.+rest-arg+ tail))))
633 (declare (inline instruction))
634 (with-let*-binder
635 (values (car symbol-cells)
636 :value (enforce-type
637 (fancy-arg) (binding-typechecks frame)
638 frame-index (frame-symbols frame))
639 :specials (pop specials))
640 ;; form to start with
641 (with-let-bindings
642 (values (lambda-frame-min-args frame)
643 :value (enforce-type
644 (if tail (pop tail) (err-too-few-args fun n-args))
645 (binding-typechecks frame)
646 frame-index (frame-symbols frame))
647 :specials (pop specials))
648 ;; maxargs/keywords should be checked now because it would be
649 ;; strange to eval some defaulting forms and then croak.
650 (cond ((logtest (lambda-frame-keyword-bits frame) +keyp-bit+)
651 (validate-keywords
652 (nthcdr (lambda-frame-n-optional frame) tail)
653 (lambda-frame-keyword-bits frame)
654 (frame-values frame)))
655 ((and (not (logtest (lambda-frame-keyword-bits frame)
656 +restp-bit+))
657 ;; FIXME: this call to LENGTH can be avoided by counting
658 ;; bindings made and subtracting from N-ARGS.
659 (> (length (truly-the list tail))
660 (lambda-frame-n-optional frame)))
661 (err-too-many-args fun n-args)))
662 (let*-bind frame-index (lambda-frame-n-bound-vars frame)))
663 ;; done with sequential bindings
664 (setf (env-symbols new-env) (frame-symbols frame))
665 (enforce-types frame (interpreted-function-env fun))
666 ;; Three cases: no block, block and vars share the ENV,
667 ;; or allocate another ENV
668 (cond ((eql (lambda-frame-block-name frame) 0)
669 (dispatch (lambda-frame-sexpr frame) new-env))
670 ((lambda-frame-share-block-p frame)
671 (catch (lambda-env-block new-env)
672 (dispatch (lambda-frame-sexpr frame) new-env)))
674 (let ((exit (list (lambda-frame-block-name frame))))
675 (catch exit
676 (dispatch (lambda-frame-sexpr frame)
677 (make-block-env new-env exit nil
678 *vacuous-decls*))))))))))
680 (defun applicator/general (fun)
681 (lambda (&rest args)
682 (declare #.+handler-optimize+)
683 (declare (inline apply-lambda))
684 (with-lambda-frame (frame fun (apply #'interpreter-trampoline fun args))
685 (apply-lambda frame fun (length args) args))))
687 ;;; Positional applicator is for lambda-lists that do not use any
688 ;;; lambda-list keyword, perform no type checks and make no special bindings.
689 ;;; Choose the most efficient applicator based on N-args and
690 ;;; whether or not there is a block name. Since there are no defaulting forms,
691 ;;; the block name (if any) and variables can have the same extent.
692 ;;; User-supplied code could not detect the difference.
693 (defun applicator/positional (fun)
694 (macrolet
695 ((new-env (constructor storage-cells &rest more-args)
696 `(,constructor (interpreted-function-env fun) ,storage-cells
697 (frame-symbols frame) frame ,@more-args))
698 (invoke (n &aux (args (subseq '(arg1 arg2 arg3 arg4 arg5) 0 n)))
699 `(if (eql (lambda-frame-block-name (interpreted-function-frame fun))
701 (named-lambda (.apply. ,n) ,args
702 (declare #.+handler-optimize+ (optimize sb-c:verify-arg-count))
703 (with-lambda-frame
704 (frame fun (interpreter-trampoline fun ,@args))
705 (dispatch (lambda-frame-sexpr frame)
706 (new-env make-var-env
707 ,(if (zerop n) nil `(vector ,@args))))))
708 (named-lambda (.apply. ,n) ,args
709 (declare #.+handler-optimize+ (optimize sb-c:verify-arg-count))
710 (with-lambda-frame
711 (frame fun (interpreter-trampoline fun ,@args))
712 (let ((exit (list (lambda-frame-block-name frame))))
713 (catch exit
714 (dispatch (lambda-frame-sexpr frame)
715 (new-env make-lambda-env
716 ,(if (zerop n) nil `(vector ,@args))
717 exit)))))))))
718 (case (lambda-frame-min-args (interpreted-function-frame fun))
719 (5 (invoke 5))
720 (4 (invoke 4))
721 (3 (invoke 3))
722 (2 (invoke 2))
723 (1 (invoke 1))
724 (0 (invoke 0))
726 (macrolet
727 ((with-args (form)
728 `(progn
729 (let* ((n-actual (length args))
730 (excess (- n-actual (lambda-frame-min-args frame))))
731 (cond ((minusp excess) (err-too-few-args fun n-actual))
732 ((plusp excess) (err-too-many-args fun n-actual))))
733 (let ((cells (make-array (lambda-frame-n-bound-vars frame))))
734 (dotimes (i (lambda-frame-min-args frame) ,form)
735 (setf (svref cells i) (nth i args)))))))
736 (if (eql (lambda-frame-block-name (interpreted-function-frame fun)) 0)
737 (named-lambda (.apply.) (&rest args)
738 (declare #.+handler-optimize+)
739 (with-lambda-frame
740 (frame fun (apply #'interpreter-trampoline fun args))
741 (with-args (dispatch (lambda-frame-sexpr frame)
742 (new-env make-var-env cells)))))
743 (named-lambda (.apply.) (&rest args)
744 (declare #.+handler-optimize+)
745 (with-lambda-frame
746 (frame fun (apply #'interpreter-trampoline fun args))
747 (with-args
748 (let ((exit (list (lambda-frame-block-name frame))))
749 (catch exit
750 (dispatch (lambda-frame-sexpr frame)
751 (new-env make-lambda-env cells
752 exit)))))))))))))
754 ;;; /&Optional applicator disallows &REST and &KEY because the stack arguments
755 ;;; are never listified (it's an implicit &MORE arg). I don't want to write code
756 ;;; to manually listify, nor hand-roll GETF. Also no special bindings permitted.
757 (defun applicator/&optional (fun)
758 (named-lambda (.apply. &optional) (&rest args)
759 (declare #.+handler-optimize+)
760 (with-lambda-frame (frame fun (apply #'interpreter-trampoline fun args))
761 (let* ((n-actual (let* ((min (lambda-frame-min-args frame))
762 (max (+ min (lambda-frame-n-optional frame)))
763 (n (length args)))
764 (when (< n min)
765 (err-too-few-args fun n))
766 (when (> n max)
767 (err-too-many-args fun n))
769 (values (make-array (lambda-frame-n-bound-vars frame)))
770 (symbol-cells (cons (lambda-frame-min-args frame)
771 (frame-symbols frame)))
772 (new-env
773 (if (lambda-frame-share-block-p frame)
774 (make-lambda-env
775 (interpreted-function-env fun) values symbol-cells frame
776 (list (lambda-frame-block-name frame)))
777 (make-var-env
778 (interpreted-function-env fun) values symbol-cells frame)))
779 (decoder-index -1)
780 (arg-index -1)
781 (arg-supplied-p))
782 (declare (index-or-minus-1 decoder-index arg-index))
783 (with-let-bindings (values (lambda-frame-min-args frame)
784 :value (nth (incf arg-index) args) :specialp nil)
785 nil) ; empty body. no special bindings, so no PROGV
786 (flet ((instruction ()
787 (svref (frame-values frame) (incf decoder-index))))
788 (declare (inline instruction))
789 (with-let*-binder
790 (values (car symbol-cells)
791 :value
792 (let ((mode (the fixnum (instruction))))
793 (case (logand mode +arg-mode-mask+)
794 (#.+optional-arg+
795 (cond ((setq arg-supplied-p (< (incf arg-index) n-actual))
796 (incf decoder-index (logand mode +has-default+))
797 (nth arg-index args))
798 ((logtest mode +has-default+)
799 (dispatch (instruction) new-env))))
800 (#.+supplied-p-var+ (if arg-supplied-p t nil))
801 (#.+aux-var+ (if (logtest mode +has-default+)
802 (dispatch (instruction) new-env)))))
803 :specialp nil)
804 ;; form to start with
805 (let*-bind (lambda-frame-min-args frame)
806 (lambda-frame-n-bound-vars frame))
807 ;; done with sequential bindings
808 (setf (env-symbols new-env) (frame-symbols frame))
809 ;; Three cases: no block, block and vars share the ENV,
810 ;; or allocate another ENV
811 (cond ((eql (lambda-frame-block-name frame) 0)
812 (dispatch (lambda-frame-sexpr frame) new-env))
813 ((lambda-frame-share-block-p frame)
814 (catch (lambda-env-block new-env)
815 (dispatch (lambda-frame-sexpr frame) new-env)))
817 (let ((exit (list (lambda-frame-block-name frame))))
818 (catch exit
819 (dispatch (lambda-frame-sexpr frame)
820 (make-block-env new-env exit
821 nil *vacuous-decls*))))))))))))
823 (declaim (type (or null compiled-function) *self-applyhook*))
824 (defvar *self-applyhook* nil) ; not quite *applyhook* as outlined in CLtL
826 ;;; A trampoline which never installs a more-specific trampoline,
827 ;;; and checks for a binding of *SELF-APPLYHOOK* on each call.
828 (defun interpreter-hooked-trampoline (fun &rest args)
829 (multiple-value-bind (frame cookie)
830 (proto-fn-frame (fun-proto-fn fun) (interpreted-function-env fun))
831 (setf (values (interpreted-function-frame fun)
832 (interpreted-function-cookie fun)) (values frame cookie))
833 ;; *SELF-APPLYHOOK* isn't the *APPLYHOOK* as described by CLtL.
834 ;; When bound, each hooked function will funcall the hook with
835 ;; itself and the arguments and a continuation of two arguments
836 ;; that the hook should call to actually perform the application.
837 ;; APPLY-LAMBDA is not inlined here. If you're using the hook,
838 ;; things are running at less than top speed anyway.
839 (if *self-applyhook* ; must be a compiled-function
840 (funcall *self-applyhook* fun args
841 (lambda (self args)
842 (apply-lambda (interpreted-function-frame self)
843 self (length args) args)))
844 ;; Assuming the compiler is doing the right thing,
845 ;; this LENGTH is gotten from the passing location.
846 (apply-lambda frame fun (length args) args))))
848 ;;; Compute the function that should be used when applying FUN.
849 ;;; This uses highly specialized code for small fixed N args <= 5,
850 ;;; and slightly more general code for any fixed number of args > 5.
851 ;;; Bound special arguments require the most general entry.
853 (defun interpreted-applicator (fun)
854 (let ((frame (interpreted-function-frame fun)))
855 (if (and (zerop (frame-special-b frame)) ; no bound specials
856 (not (logtest (lambda-frame-keyword-bits frame) ; fixed upper bound
857 (logior +restp-bit+ +keyp-bit+))) ; on arg count
858 (eql (binding-typechecks frame) +none+)
859 (eql (extra-typechecks frame) +none+))
860 (if (zerop (length (frame-values frame)))
861 (applicator/positional fun)
862 (applicator/&optional fun))
863 (applicator/general fun))))
867 Test case.
868 (defun get-thinginator () #'thing)
869 (defun thing () 'the-thing)
870 (funcall (get-thinginator)) ; returns THE-THING
871 (defmacro thing () ''thing-macro) ; system warns about this
872 (get-thinginator) ; errs - it correctly perceives the redefinition
875 ;;; Return T if SYMBOL might get redefined as a macro when it was previously
876 ;;; a function and vice versa. Extra checks are done on every use of the symbol
877 ;;; as a function name.
878 (defun fluid-def-p (symbol)
879 ;; Todo: add most system-internal packages here probably
880 (not (memq (symbol-package symbol)
881 (load-time-value
882 (mapcar #'find-package '("CL" "SB-KERNEL" "SB-INT" "SB-IMPL"
883 "SB-C" "SB-VM" "SB-ALIEN" "SB-ALIEN-INTERNALS"
884 "SB-LOOP"
885 "SB-SYS" #+sb-thread "SB-THREAD"))))))
888 * (defmacro baz (n) `(nth ,n *mumble*))
889 * (define-symbol-macro mumble (cdr (feep)))
890 * (defmacro feep () '(aref *x* 1))
891 * (nth-value 1 (tracing-macroexpand-1 '(shiftf (baz 3) (feep)) nil))
892 => ((#<INTERPRETED-FUNCTION (DEFMACRO BAZ)> . BAZ) (MUMBLE CDR (FEEP))
893 (#<INTERPRETED-FUNCTION (DEFMACRO FEEP)> . FEEP))
896 (defvar *show-macroexpansion* nil)
897 ;;; Expand FORM once, capturing all "interesting" expansions occuring within.
898 ;;; For example (INCF FOO) is a builtin macro whose functional definition is
899 ;;; not considered per se interesting, however if FOO is a symbol macro,
900 ;;; then the meaning of that form changes if FOO gets redefined.
902 ;;; This is still not powerful enough to work all the time - we really need to
903 ;;; know if anything so much as inquired whether a symbol is a macro.
904 ;;; Continuing the above example, if FOO is not a macro, then making it into
905 ;;; a macro later will have no effect, because there is no object that
906 ;;; stands for the identity of FOO as a macro. This is not a problem with
907 ;;; macro functions.
908 ;;; Also note that CLtL2 says
909 ;;; "macro definitions should not depend on the time at which they are expanded"
911 (defun tracing-macroexpand-1 (form env &optional (predicate #'fluid-def-p)
912 &aux (original-hook (valid-macroexpand-hook))
913 expanders)
914 (unless (allow-macro-redefinition env)
915 (return-from tracing-macroexpand-1
916 (values (macroexpand-1 form env) nil)))
917 (flet ((macroexpand-hook (function form env)
918 (let ((expansion (funcall original-hook function form env)))
919 (if (atom form)
920 ;; All global symbol-macros are recorded - there are no builtins
921 ;; which are candidates for removal. symbol-macrolet expansions
922 ;; aren't recorded, unless they happen to be EQ to a global
923 ;; expansion, which is unlikely and nothing to worry about.
924 (if (neq expansion (info :variable :macro-expansion form))
925 nil ; I have no idea what to record
926 (push (cons form expansion) expanders))
927 ;; If the expander is EQ to the global one and the symbol
928 ;; satisfies the interestingness test.
929 (let* ((head (car form)) (global-fn (macro-function head nil)))
930 (if (and (eq function global-fn) (funcall predicate head))
931 (push (cons global-fn head) expanders))))
932 expansion)))
933 (let ((expansion (let ((*macroexpand-hook* #'macroexpand-hook))
934 (macroexpand-1 form env))))
935 (setq expanders (nreverse expanders))
936 ;; condition on #+eval-show also?
937 (when *show-macroexpansion*
938 (format t "~&Expanded ~S~% into ~S~%~@[ using ~S~]~%"
939 form expansion expanders))
940 (values expansion expanders))))
942 ;;; Return T if the evaluator should always consider that macros
943 ;;; might be redefined. If NIL then cached expansions are permanent.
944 (defun allow-macro-redefinition (env)
945 (if (policy env (and (= speed 3) (= debug 0) (= safety 0)))
949 (defun arglist-to-sexprs (args)
950 (let ((argc (or (list-length args)
951 (ip-error "Malformed function call"))))
952 (values (mapcar #'%sexpr args) argc)))
954 ;;; Return a handler which decides whether its supplied SEXPR needs
955 ;;; to have macroexpansion performed again due to changes to global macros.
956 ;;; If not, just dispatch the previously computed expansion.
958 ;;; Just knowing the macroexpander isn't enough. We need to collect _all_
959 ;;; expanders that ran during 1 round of expansion, which can't be determined
960 ;;; without running the outermost and tracing what happens.
962 ;;; EXPANSION is a SEXPR for the overall result of expansion.
963 ;;; FNAME is the symbol at the head of the original form.
964 ;;; Each element of KEYS is (#<FUNCTION> . SYM) or (SYM . SYMBOL-EXPANSION)
965 ;;; The representation is unambiguous because a symbol is not a function,
966 ;;; whereas (SYM . EXPANSION|FUNCTION) is ambigious because through contortions
967 ;;; it is possible to have a symbol's expansion be a function object.
968 ;;; If any key is changed, restart using the original sexpr form.
970 (defun digest-macro-form (expansion fname keys)
971 (if (and (endp (cdr keys)) ; if one key
972 (let ((k (car keys))) ; which is the function that we expect
973 (and (functionp (car k)) (eq (cdr k) fname))))
974 ;; Assume that if MACRO-FUNCTION for the form's head is EQ to what it was
975 ;; previously, that it will produce the same expansion (in this ENV).
976 ;; This can of course is easily violated by nondeterministic macros.
977 (let ((macro-fn (caar keys)))
978 (hlambda MACRO/1 (fname macro-fn expansion) (env old-sexpr)
979 (if (eq (macro-function fname) macro-fn)
980 (dispatch expansion env)
981 (progn
982 #+eval-show
983 (format t "~&Changed expander: ~S~%" fname)
984 (digest-form (sexpr-form old-sexpr) env old-sexpr)))))
985 ;; Same as above but generalized to N keys.
986 (hlambda MACRO+ (keys expansion) (env old-sexpr)
987 (if (every (lambda (k)
988 (if (functionp (car k))
989 (eq (car k) (macro-function (cdr k)))
990 (eq (info :variable :macro-expansion (car k))
991 (cdr k))))
992 (the list keys))
993 (dispatch expansion env)
994 (progn
995 #+eval-show
996 (format t "~&Changed expanders: ~S~%" keys)
997 (digest-form (sexpr-form old-sexpr) env old-sexpr))))))
1000 (CASES n (1 5 frob) (4 (exceptional-case)) (t (fallback-case)))
1001 -> (CASE N
1002 (1 (FROB 1))
1003 (2 (FROB 2))
1004 (3 (FROB 3))
1005 (4 (EXCEPTIONAL-CASE))
1006 (5 (FROB 5))
1007 (T (FALLBACK-CASE)))
1010 (defmacro cases (test-var (min max template) &rest specified-cases)
1011 `(case ,test-var
1012 ,@(loop for i from min to max
1013 collect
1014 (or (assoc i specified-cases)
1015 `(,i (,template ,i))))
1017 ,@(cdr (assoc t specified-cases)))))
1019 ;;; A local-call uses LOCAL-FDEFINITION to obtain the function, which
1020 ;;; is *always* a function, never a macro and never undefined.
1021 ;;; Some clever macrology might share the handler-generator
1022 ;;; with DIGEST-GLOBAL-CALL
1023 (defun digest-local-call (frame-ptr args &aux (n-args 0))
1024 (multiple-value-setq (args n-args) (arglist-to-sexprs args))
1025 (macrolet ((funcall-n (n)
1026 `(hlambda (LOCAL-CALL ,N) (data) (env)
1027 (funcall (local-fdefinition (svref data 0) env)
1028 ,@(loop for i from 1 repeat n
1029 collect `(dispatch (svref data ,i) env))))))
1030 (let ((data (if (> n-args 1) (coerce (cons frame-ptr args) 'vector))))
1031 (cases n-args (0 5 funcall-n)
1032 (0 (hlambda (LOCAL-CALL 0) (frame-ptr) (env)
1033 (funcall (local-fdefinition frame-ptr env))))
1034 (1 (let ((arg (first args)))
1035 (hlambda (LOCAL-CALL 1) (frame-ptr arg) (env)
1036 (funcall (local-fdefinition frame-ptr env) (dispatch arg env)))))
1037 (t (hlambda LOCAL-CALL (data) (env)
1038 (declare (simple-vector data))
1039 (let* ((arglist (make-list (1- (length data))))
1040 (tail arglist))
1041 (dotimes (i (1- (length data))
1042 (apply (local-fdefinition (svref data 0) env)
1043 arglist))
1044 (rplaca tail (dispatch (svref data (1+ i)) env))
1045 (pop tail)))))))))
1047 ;;; Apply what is probably a function - it was when the form was digested.
1048 ;;; This carefully mimics the compiler's behavior of referencing the
1049 ;;; function only after evaluation of its args. In particular, supposing that
1050 ;;; BAZ is not defined, this works in compiled code:
1051 ;;; (DEFUN FOO () (BAZ (SETF (SYMBOL-FUNCTION 'BAZ) (LAMBDA (X) `(HI ,X)))))
1053 ;;; Interpreted code needs an explicit check for NIL in an fdefn-fun.
1054 ;;; Compiled code doesn't because the 'raw-addr' slot is always
1055 ;;; something valid to jump to.
1056 (defun apply-probably-fun (fdefinition args env &aux (n-args 0))
1057 (multiple-value-setq (args n-args) (arglist-to-sexprs args))
1058 (macrolet
1059 ((funcall-n (n)
1060 (let* ((arg-names (subseq '(a b c d e) 0 n))
1061 (bindings
1062 (loop for arg in arg-names for i from 1 repeat n
1063 collect `(,arg
1064 (dispatch
1065 ,(if (= n 1) '(cdr data) `(svref data ,i))
1066 env)))))
1067 `(hlambda (GLOBAL-CALL ,n) (data) (env sexpr)
1068 (symbol-macrolet ((fdefn ,(case n
1069 (0 'data)
1070 (1 '(car data))
1071 (t '(svref data 0)))))
1072 (if (re-expand-p)
1073 (digest-form (sexpr-form sexpr) env sexpr)
1074 (let ,bindings
1075 (funcall (sb-c:safe-fdefn-fun fdefn) ,@arg-names)))))))
1076 (generate-switch ()
1077 `(case n-args
1078 (0 (let ((data fdefinition)) (funcall-n 0)))
1079 (1 (let ((data (cons fdefinition (first args)))) (funcall-n 1)))
1081 (let ((data (coerce (cons fdefinition args) 'vector)))
1082 (cases n-args (2 5 funcall-n)
1083 (t (hlambda GLOBAL-CALL (data) (env sexpr)
1084 (declare (simple-vector data))
1085 (symbol-macrolet ((fdefn (svref data 0)))
1086 (if (re-expand-p)
1087 (digest-form (sexpr-form sexpr) env sexpr)
1088 (let* ((arglist (make-list (1- (length data))))
1089 (tail arglist))
1090 (dotimes (i (1- (length data))
1091 (apply (sb-c:safe-fdefn-fun fdefn) arglist))
1092 (rplaca tail (dispatch (svref data (1+ i)) env))
1093 (pop tail)))))))))))))
1094 (if (allow-macro-redefinition env)
1095 (macrolet ((re-expand-p ()
1096 '(let ((f (fdefn-fun fdefn)))
1097 (and f (sb-impl::macro/special-guard-fun-p f)))))
1098 (generate-switch))
1099 (macrolet ((re-expand-p () nil)) (generate-switch)))))
1101 ;;; Evaluate the arguments to a function that can't be called,
1102 ;;; then call it. Very weird, yes! But this is reached in two situations:
1103 ;;; 1. the user wrote (funcall 'IF ...)
1104 ;;; 2. the user defined a new special operator that the interpreter
1105 ;;; does not know about.
1106 ;;; In either case %LOOKS-LIKE-MACRO-P will return T,
1107 ;;; because it knows that the fdefn-fun is an error-invoking trampoline.
1108 ;;; But there is no macroexpander, so we have to do "something".
1109 ;;; This handler is the way we punt, because the careful handler (above)
1110 ;;; would see that the thing to be applied is a guard trampoline,
1111 ;;; and would start over again at digest-global-call.
1113 ;;; Note also the subtle difference between these two:
1114 ;;; (funcall 'IF 'FOO 'BAR)
1115 ;;; (funcall #'IF ...)
1116 ;;; In the former, the FUNCALL is reached, because every argument
1117 ;;; to the funcall was legally evaluable. But in the latter, it is not
1118 ;;; reached since the first argument to funcall signals an error.
1119 (defun apply-definitely-not-fun (fname args)
1120 (let ((data (coerce (cons fname (arglist-to-sexprs args)) 'vector)))
1121 (hlambda GLOBAL-CALL (data) (env)
1122 (declare (simple-vector data))
1123 (let* ((arglist (make-list (1- (length data))))
1124 (tail arglist))
1125 ;; "unable to optimize apply"
1126 (declare (muffle-conditions compiler-note))
1127 (dotimes (i (1- (length data))
1128 (apply (the symbol (svref data 0)) arglist))
1129 (rplaca tail (dispatch (svref data (1+ i)) env))
1130 (pop tail))))))
1132 ;;; Handler is specialized only if the function is builtin.
1133 ;;; In such cases, reference the function directly, eliding the deref
1134 ;;; through an FDEFINITION.
1135 ;;; It can always be kicked out of the cache by touching the globaldb cookie.
1136 (defun digest-global-call (fname args env)
1137 ;; For user-defined functions declared inline, don't bother
1138 ;; checking for being redefined as a macro.
1139 ;; The globaldb cookie will take care of redefinition.
1140 ;; (neq (info :function :inlinep fname) :inline))
1142 (when (symbolp fname)
1143 (when (eq (info :function :kind fname) :special-form)
1144 (return-from digest-global-call
1145 (apply-definitely-not-fun fname args)))
1147 ;; Structure-accessor: interpreted accessors are *terrible*.
1148 ;; We could use a handler (need to respect NOTINLINE though),
1149 ;; or just COMPILE the accessor, since who's to say
1150 ;; that DEFSTRUCT doesn't somehow magically produce
1151 ;; compiled accessors via closures or a LAP assembler.
1152 ;; Frankly the latter ought to be possible.
1153 ;; And this doesn't fix the problem with SETF.
1154 (when (fboundp fname)
1155 (let ((f (symbol-function fname)))
1156 (when (and (interpreted-function-p f)
1157 (structure-instance-accessor-p fname))
1158 ;: Compile the accessor. If it was defined in a non-null environment,
1159 ;; conversion to a lexenv could say "too complex", so we want to
1160 ;; force it. Passing two arguments to COMPILE achieves this.
1161 ;; We can be confident that the expression doesn't need a lexenv,
1162 ;; because if the function were incompatible with the source-transform,
1163 ;; %DEFUN would have cleared the :source-transform, and fname would not
1164 ;; satisfy STRUCTURE-INSTANCE-ACCESSOR-P.
1165 #+nil (format t "~&; Interpreter: Compiling ~S~%" fname)
1166 ;; FIXME: ensure that the compiled function is safe.
1167 (compile fname (function-lambda-expression f)))))
1169 (when (fluid-def-p fname)
1170 ;; Return a handler that calls FNAME very carefully
1171 (return-from digest-global-call
1172 (apply-probably-fun (find-or-create-fdefn fname) args env))))
1174 ;; Try to recognize (FUNCALL constant-fun ...)
1175 ;; This syntax is required when using SETF functions, and it should
1176 ;; be no less efficient than (F args).
1177 ;; But, [FIXME?] can FUNCALL be rebound lexically?
1178 (when (and (eq fname 'funcall)
1179 (not (endp args)) ; FUNCALL demands at least one arg
1180 (typep (first args)
1181 '(or (cons (eql function)
1182 (cons (satisfies legal-fun-name-p) null))
1183 (cons (eql quote) (cons symbol null)))))
1184 (let* ((function-form (first args))
1185 (fname (second function-form)))
1186 ;; (FUNCALL 'SYMBOL args...) => (SYMBOL args...) without the lexenv.
1187 (when (eq (car function-form) 'quote)
1188 (return-from digest-global-call
1189 (digest-global-call fname (cdr args) env)))
1191 ;; It's (FUNCALL #'FUNCTION ...)
1192 (let ((frame-ptr (local-fn-frame-ptr fname env)))
1193 (case frame-ptr
1194 ((nil) ; global function (or special operator, which will barf on you)
1195 (when (symbolp fname) (coerce fname 'function)) ; for effect
1196 (return-from digest-global-call
1197 (digest-global-call fname (cdr args) env)))
1198 (:macro) ; do not process - let the FUNCTION operator complain
1199 (t (return-from digest-global-call
1200 (digest-local-call frame-ptr (cdr args))))))))
1202 (let ((n-args 0)
1203 (fun (fdefinition fname)))
1204 (multiple-value-setq (args n-args) (arglist-to-sexprs args))
1206 ;; Fold if every arg when trivially constant and the function is foldable.
1207 ;; "trivially" means without needing propagation to decide that.
1208 (when (notany #'sexpr-p args)
1209 (let ((info (info :function :info fname)))
1210 (when (and info (sb-c::ir1-attributep (sb-c::fun-info-attributes info)
1211 sb-c::foldable))
1212 (let ((values (multiple-value-list (apply fname args))))
1213 (return-from digest-global-call
1214 (if (or (cdr values) (null values))
1215 (handler #'return-constant-values values)
1216 (return-constant (first values))))))))
1218 ;; Todo: redefining any function in one of the builtin packages should
1219 ;; increment the globaldb cookie to unmemoized stored #<FUNCTION> objects.
1220 ;; Btw, it's weird that FDEFINITION strips out tracing wrappers
1221 ;; since FDEFINITION is the canonical way to get the function given a
1222 ;; general name, and seems like it's supposed to be just the
1223 ;; straightforward generalization of SYMBOL-FUNCTION.
1224 (macrolet ((funcall-n (n)
1225 `(hlambda (FAST-GLOBAL-CALL ,n) (data) (env)
1226 (funcall (the function (svref data 0))
1227 ,@(loop for i from 1 repeat n collect
1228 `(dispatch (svref data ,i) env))))))
1229 (let ((data (if (> n-args 1) (coerce (cons fun args) 'vector))))
1230 (cases n-args (0 5 funcall-n)
1231 (0 (hlambda (FAST-GLOBAL-CALL 0) (fun) (env)
1232 (declare (ignore env))
1233 (funcall (the function fun))))
1234 (1 (let ((arg (first args))
1235 (handler-fn (gethash fname *unary-functions*)))
1236 (if handler-fn
1237 (handler handler-fn arg)
1238 (hlambda (FAST-GLOBAL-CALL 1) (fun arg) (env)
1239 (funcall (the function fun) (dispatch arg env))))))
1240 (2 (let ((handler-fn (gethash fname *binary-functions*)))
1241 (if handler-fn
1242 (handler handler-fn (cons (first args) (second args)))
1243 (funcall-n 2))))
1245 (hlambda GLOBAL-CALL (data) (env)
1246 (declare (simple-vector data))
1247 (let* ((arglist (make-list (1- (length data)))) (tail arglist))
1248 (dotimes (i (1- (length data))
1249 (apply (the function (svref data 0)) arglist))
1250 (rplaca tail (dispatch (svref data (1+ i)) env))
1251 (pop tail))))))))))
1253 (defmethod print-object ((obj basic-env) stream)
1254 (print-unreadable-object (obj stream :identity t :type t)
1255 #+eval-show
1256 (write-string (env-to-string obj) stream)))
1258 (defmethod print-object ((obj sexpr) stream)
1259 ;; It's very confusing to debug this code if sexprs are visibly indistinct
1260 ;; from their lists, but it looks more pleasing in backtraces.
1261 ;; Maybe need a toggle switch that is not one of the standard ones?
1262 (if *print-escape*
1263 (let ((string (write-to-string (sexpr-form obj))))
1264 (format stream "#<sexpr ~A... #x~X>"
1265 (subseq string 0 (min (length string) 30))
1266 (get-lisp-obj-address obj)))
1267 (write (sexpr-form obj) :stream stream)))