1 ;;;; This software is part of the SBCL system. See the README file for
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 ;;; The policy in *VACUOUS-DECLS* specifies neither primary nor dependent
13 ;;; qualities. By this we can determine that the env is to be skipped over
14 ;;; when looking for the current policy.
15 (defglobal *vacuous-decls
* (make-decl-scope nil
(sb-c::make-policy
0 0)))
17 ;;; One environment subtype exists for each kind of binding form.
18 ;;; Structurally they are all identical, except that LAMBDA adds
19 ;;; a block name, as an optimization wherein we attempt to elide
20 ;;; creation of two lexical contours - one for the variables and
21 ;;; one for the block - by creating only one contour when there
22 ;;; is no chance that user code could detect that the block's scope
23 ;;; was "widened" to encompass the variable bindings.
25 ;;; LET and LET* use the same ENV type. The major difference with LAMBDA
26 ;;; is that it has a fancy way to compute initial values,
27 ;;; but internally the bindings look like they came from LET*.
29 (macrolet ((def-subtype (type &optional more-slots
)
30 (let ((constructor (symbolicate "MAKE-" type
)))
34 (:include basic-env
) (:copier nil
)
35 (:constructor
,constructor
36 (parent payload symbols contour
,@more-slots
)))
38 (declaim (freeze-type ,type
))
39 (declaim (inline ,constructor
))))))
40 (def-subtype function-env
)
42 (def-subtype macro-env
)
43 (def-subtype symbol-macro-env
)
44 (def-subtype block-env
)
45 (def-subtype tagbody-env
)
46 ;; LAMBDA-ENV is a theoretical subtype of both VAR-ENV and BLOCK-ENV
47 ;; but implementationally all subtypes are pairwise disjoint.
48 ;; Defining them thusly is a small efficiency win for the compiler,
49 ;; because TYPEP has an optimization for sealed classes with no subclass,
50 ;; but not for a sealed class with a fixed number of sealed subclasses.
51 ;; Plus since structs don't support multiple inheritance anyway,
52 ;; it would be arbitrary whether lambda-env were defined as a LET
53 ;; with a block name, or a BLOCK and some bindings.
54 (def-subtype lambda-env
(block)))
56 ;;; This implementation of lexical environments takes a fairly unconvential
57 ;;; approach to dealing with sequential (LET*) binding. [Anything said here
58 ;;; about LET* pertains to LAMBDA as well]. The conceptual model for LET* is
59 ;;; that it is a sequence of nested LET forms, each creating one binding.
60 ;;; This is often implemented by allocating a new environment structure per
61 ;;; variable, exactly as implied by the equivalence with nested LET forms.
63 ;;; An implementation that realizes LET* as such is quite inefficient though,
64 ;;; especially if the LET* did not really need to be a LET* and was
65 ;;; "just written that way". Assuming that the speed overhead is at least
66 ;;; the space overhead - allocating N words takes N time - we can easily
67 ;;; estimate the space overhead alone based on the structures above.
68 ;;; One VAR-ENV takes up 6 words, plus a simple-vector for the variable values.
69 ;;; Binding 10 variables in a LET consumes 18 words: 6 fixed, plus 12 words
70 ;;; for a 10-vector. In contrast, 10 bindings if nested would take 100 words
71 ;;; which is 10 * (6 + 4). This is nearly 6 times more space.
72 ;;; [The smallest non-empty simple-vector is 4 words]
74 ;;; So instead of using nested environments, this interpreter uses a single
75 ;;; vector for storing all the variables of a LET*, and a quasi-fill-pointer
76 ;;; (essentially a fill-pointer, but not stored as part an adjustable vector)
77 ;;; indicating the effective end. Any operation on the vector should simply
78 ;;; pretend that bindings beyond the effective end do not exist. Furthermore
79 ;;; the parts of the environment pertaining to the body forms of the LET*,
80 ;;; such as TYPE declarations for other than the bound variables, and SPECIAL
81 ;;; declarations, do not exist until all variables have been sequentially bound.
82 ;;; This is dealt with by having the declaration accessors return NIL until such
83 ;;; time as the fill-pointer has reached its limit, at which point the extra
84 ;;; declarations in the environment (SPECIAL,OPTIMIZE,etc.) become visible.
86 ;;; An environment is termed "mutable" if it has not reached the end of its
87 ;;; bindings - it is still subject to change by binding additional variables
88 ;;; beyond the last which is currently bound. But once the last variable has
89 ;;; been bound, the environment becomes "immutable" and it exposes all its
90 ;;; variables plus the free declarations and such.
91 ;;; LET (specifically, not LET*) environments are never mutable because
92 ;;; no new environment is materialized until after all variable initialization
93 ;;; values have been computed. Only the value vector is made in the interim.
95 ;;; But mutability causes a problem for lexical closures - a closure needs a
96 ;;; fixed view of the environment. The solution is to place the burden upon
97 ;;; closure allocation to capture the fixed view.
98 ;;; The FUNCTION special operator is responsible for looking at the environment
99 ;;; that it closes over, and deciding whether the environment is in flux.
100 ;;; If it is, then FUNCTION needs to "freeze" the mutable environment by sharing
101 ;;; all value cells and storing a fixed value for the fill-pointer.
102 ;;; This is a recursive operation - you can close over an immutable environment
103 ;;; whose parent is mutable, so that a deep copy occurs "upwardly"
104 ;;; e.g. in (LET* ((f (...)) (g (let ((x 3)) (lambda () ...))) (h ..)))
105 ;;; the LAMBDA's innermost contour contains an immutable environment for X,
106 ;;; whose ancestor is a mutable environment in which F is seen but not G or H.
108 ;;; In practice it makes a lot of sense to place the burden on closure creation.
109 ;;; to avoid work during environment construction. As shown by the example,
110 ;;; you must write fairly contrived code to cause a closure to see only part
111 ;;; of a LET* environment. Contrived as that it though, there is indeed a
112 ;;; use-case for it. The PCL defmethod expander exercises this uncommon
113 ;;; pattern when making its fast method function:
114 ;;; (LET* ((FMF (NAMED-LAMBDA () ...)) (MF (%MAKE-METHOD-FUNCTION FMF NIL))))
115 ;;; This NAMED-LAMBDA should see no symbols in the LET* environment.
116 ;;; But in fact this usage is a degenerate example in which there is no need
117 ;;; to freeze the environment as long as the parent did not need to be frozen.
118 ;;; Since nothing was bound in the LET*, it is as if it had not happened at all,
119 ;;; as far as the closure is concerned. Is is likely that scenarios in which
120 ;;; freezing must do a non-trivial amount of work are quite rare.
122 ;;; All that said, the representation of "mutable" is that instead of
123 ;;; a vector of sybols, we have a cons of a fixnum and a vector, so ...
124 ;;; Return T if the ENV is currently undergoing sequential variable binding.
125 (declaim (inline env-mutable-p
))
126 (defun env-mutable-p (env) (consp (env-symbols env
)))
128 ;;; Code should only inquire of N-VARS when in the midst of a LET*
129 ;;; or LAMBDA sequential binding operation, not LET, and not a completely
130 ;;; bound LET* or LAMBDA. (You can't take CAR of symbols in that case)
131 (declaim (inline env-n-vars
))
132 (defun env-n-vars (env) (car (env-symbols env
)))
134 ;;; Each subtype of ENV points to subtype of a DECL-SCOPE.
136 (defstruct (local-scope (:include decl-scope
)
137 (:constructor %make-local-scope
138 (declarations %policy body specials
))
141 (specials nil
:read-only t
)
142 (body nil
:read-only t
))
144 (defstruct (local-fn-scope
145 (:include local-scope
)
146 (:constructor %make-local-fn-scope
147 (declarations %policy funs body specials
))
150 (funs nil
:type simple-vector
:read-only t
))
152 (defstruct (symbol-macro-scope
153 (:conc-name symbol-macro-
)
154 (:include decl-scope
)
155 (:constructor %make-symbol-macro-scope
156 (declarations %policy symbols expansions body
))
159 (symbols nil
:type simple-vector
:read-only t
)
160 (expansions nil
:type simple-vector
:read-only t
)
161 (body nil
:read-only t
))
163 ;;; "scope" and "frame" are basically synonymous here.
164 ;;; The existence of both terms is a minor accident.
166 ;; Binding frame specification for LET and LET*
167 ;; This is a prototype stack-frame rather than a runtime stack frame in that
168 ;; one exists per syntactic form, not per dynamic invocation of same.
169 (defstruct (frame (:include decl-scope
)
170 (:copier nil
) (:predicate nil
)
171 (:constructor make-let-frame
172 (declarations %policy
173 symbols special-b values sexpr specials
)))
174 ;; If more symbols exist than values, the remainder are free specials.
175 (symbols nil
:read-only t
:type simple-vector
)
176 ;; Bitmask over symbols. 1 in bit N means bind the Nth symbol as special.
177 (special-b nil
:read-only t
:type integer
)
178 ;; A let frame can't have zero values. (It would be converted to LOCALLY)
179 (values nil
:read-only t
:type simple-vector
)
180 (sexpr nil
:read-only t
) ; code to execute
181 ;; To avoid reconstituting the first PROGV operand from the special-b mask
182 ;; and vector of all bound symbols, store the bound specials as follows:
183 ;; for LET - a list of all bound specials
184 ;; for LET* - a list of singleton lists of bound specials
185 ;; for LAMBDA - possibly both of the preceding: a list for mandatory args
186 ;; and lists of singleton lists for &optional/&rest/&key.
187 (specials nil
:read-only t
))
189 (defmethod print-object ((self frame
) stream
)
190 (print-unreadable-object (self stream
:type t
:identity t
)))
192 (declaim (inline frame-size
))
193 (defun frame-size (frame) (length (frame-values frame
)))
195 ;;; A LET* frame is just like a LET frame.
196 (defstruct (let*-frame
197 (:include frame
) (:predicate nil
) (:copier nil
)
198 (:constructor make-let
*-frame
199 (declarations %policy symbols special-b
200 values sexpr specials
))))
202 ;;; BASIC-ENV stores a policy for its body, but if evaluation has not reached
203 ;;; the body forms of a LET*, then the old policy is in effect. This is due to
204 ;;; the need for presenting a consistent view of the policy, but a frozen ENV
205 ;;; does not get a different static environment - it sees the same object
206 ;;; that the body forms see.
207 (defun env-policy (env)
208 (cond ((not env
) sb-c
::*policy
*)
209 ((env-mutable-p env
) (env-policy (env-parent env
)))
210 (t (let ((policy (%policy
(env-contour env
))))
211 ;; If the policy contains no qualities, look to the parent env.
212 ;; This happens with a BLOCK or TAGBODY, as well as the
213 ;; environment in which LABELS are defined.
214 (if (eql (sb-c::policy-presence-bits policy
) 0)
215 (env-policy (env-parent env
))
218 ;; Fancy binding frame specification
219 (defstruct (lambda-frame (:include let
*-frame
) (:predicate nil
) (:copier nil
))
220 ;; Unlike for a LET* frame the count of bound values can not be determined
221 ;; from the length of the VALUES vector, which contains various extra markers
222 ;; dictating how the arguments are to be parsed.
223 (n-bound-vars 0 :read-only t
:type fixnum
)
224 ;; Number of mandatory and optional arguments.
225 (min-args 0 :read-only t
:type fixnum
)
226 (n-optional 0 :read-only t
:type fixnum
)
227 ;; Packed flags indicating presence of &REST/&KEY/&ALLOW-OTHER-KEYS.
228 (keyword-bits 0 :read-only t
:type fixnum
)
229 ;; A BLOCK name in which to wrap the lambda's evaluable forms.
230 ;; This behaves exactly the same as using a block-env around the forms,
231 ;; however a lambda-env consumes only 8 words plus 2 for the freshly consed
232 ;; catch tag; whereas a var-env + block-env would consume 6 + 6 + 2, which
233 ;; entails 40% more overhead to enter the most trivial interpreted function.
234 (block-name 0 :read-only t
:type
(or (eql 0) symbol
))
235 ;; SHARE-BLOCK-P is T if BLOCK-NAME can be created concurrently
236 ;; with variable bindings. If NIL when a block-name is present,
237 ;; then another environment is allocated to enclose the block,
238 ;; which is not as big a win as combining the block-env and var-env,
239 ;; but still beneficial as it avoids separately calling the block handler.
240 (share-block-p nil
:read-only t
:type boolean
))
242 (defconstant +restp-bit
+ #b100
)
243 (defconstant +keyp-bit
+ #b010
)
244 (defconstant +allowp-bit
+ #b001
)
246 (declaim (inline make-keyword-bits keyword-bits-n-keys keyword-bits-allowp
))
247 (defun make-keyword-bits (n-keys restp keyp allowp
)
248 (logior (ash n-keys
3)
249 (if restp
+restp-bit
+ 0)
250 (if keyp
+keyp-bit
+ 0)
251 (if allowp
+allowp-bit
+ 0)))
252 (defun keyword-bits-n-keys (bits) (ash bits -
3))
253 (defun keyword-bits-allowp (bits) (logtest bits
+allowp-bit
+))
255 (defun lambda-frame-max-args (frame) ; NIL if no explicit upper limit
256 (if (logtest (lambda-frame-keyword-bits frame
)
257 (logior +restp-bit
+ +keyp-bit
+))
259 (truly-the index
(+ (lambda-frame-min-args frame
)
260 (lambda-frame-n-optional frame
)))))
262 ;;; Return T if the innermost package-lock-related declaration pertaining
263 ;;; to SYMBOL disables its package lock. Don't scan backwards through
264 ;;; a lambda frame. (See remarks at CAPTURE-TOPLEVEL-ENV)
265 (defun lexically-unlocked-symbol-p (symbol env
)
266 (named-let recurse
((env env
) (globalp t
))
267 (do-decl-spec (declaration
268 (env-declarations env
)
269 (acond ((env-parent env
)
270 (recurse it
(and globalp
(not (lambda-env-p env
)))))
272 (member symbol sb-c
::*disabled-package-locks
*))))
273 ;; Ambigous case: both in the same decl list. Oh well...
274 (case (car declaration
)
275 (disable-package-locks
276 (when (member symbol
(cdr declaration
)) (return t
)))
277 (enable-package-locks
278 (when (member symbol
(cdr declaration
)) (return nil
)))))))
280 ;;; Do like above, but materialize the complete list of unlocked symbols,
281 ;;; including those from sb-c::*disabled-package-locks* if applicable.
282 (defun env-disabled-package-locks (env &aux list
)
283 (named-let recurse
((env env
) (globalp t
))
284 (acond ((env-parent env
)
285 (recurse it
(and globalp
(not (lambda-env-p env
)))))
287 (setq list
(copy-list sb-c
::*disabled-package-locks
*))))
288 (do-decl-spec (declaration (env-declarations env
) list
)
289 (when (member (car declaration
)
290 '(disable-package-locks enable-package-locks
))
291 (setq list
(sb-c::process-package-lock-decl declaration list
))))))
293 ;;; Return the declarations which are currently effective in ENV.
294 ;;; If ENV is a sequential binding environment which has not reached
295 ;;; its body forms, return NIL. This is not recursive,
296 ;;; because declarations are a local aspect of the ENV.
297 (defun env-declarations (env)
298 (if (env-mutable-p env
) nil
(declarations (env-contour env
))))
300 ;;; Everything in the interpreter is compiled without safety,
301 ;;; because when thing work as they should, no mistaken assumptions are made
302 ;;; about the internals. For user code, safety is effectively imparted by the
303 ;;; strict checking of argument list arity in interpreted APPLY,
304 ;;; and all system functions are safe when invoked through their public API.
305 ;;; Whether maximally strict checking of types is performed in user code
306 ;;; has nothing to do with how the interpreter is compiled.
307 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
308 ;; Of course, errors are possible in the interpreter itself,
309 ;; so in that case it helps to define this as '() for debugging.
310 #+nil
(defparameter +handler-optimize
+ '(optimize))
311 (defparameter +handler-optimize
+ '(optimize (speed 2) (debug 2) (safety 0))))
313 ;;; We represent a pointer to a symbol in an environment by a FRAME-PTR
314 ;;; which is a packed integer containing the "up" and "across" indices.
315 (declaim (inline make-frame-ptr frame-ptr-depth frame-ptr-cell-index
))
316 ;;; This provides constant-time access to lexical variables within a frame.
317 (defun make-frame-ptr (across &optional
(up 0))
318 (declare (type (unsigned-byte #.
+frame-depth-bits
+) up
)
319 (type (unsigned-byte #.
+frame-size-bits
+) across
)
320 #.
+handler-optimize
+)
321 (logior (ash across
+frame-depth-bits
+) up
))
323 (defun frame-ptr-depth (frame-ptr) ; "up"
324 (declare (fixnum frame-ptr
))
325 (ldb (byte +frame-depth-bits
+ 0) frame-ptr
))
327 (defun frame-ptr-cell-index (frame-ptr) ; "across"
328 (declare (fixnum frame-ptr
))
329 (ash frame-ptr
(- +frame-depth-bits
+)))
331 ;;; Older frames take O(depth) to locate.
332 (declaim (inline env-ancestor
))
333 (defun env-ancestor (env frame-ptr
)
334 (declare (fixnum frame-ptr
) #.
+handler-optimize
+)
335 (do ((i (frame-ptr-depth frame-ptr
) (1- i
)))
338 (setq env
(env-parent env
))))
340 ;;; Hide an implementation detail of a partially bound environment,
341 ;;; that it is a vector and a count.
342 ;;; END indicates the length of the effective portion of the value vector.
343 ;;; LENGTH of a simple-vector is in the same location as CAR of a cons,
344 ;;; so regardless of whether ENV-SYMBOLS currently hold a cons or a vector
345 ;;; we can always use CAR to read the length.
346 (defmacro with-environment-vars
((symbols end
) env
&body body
)
347 `(awhen (env-symbols ,env
)
348 (let ((,symbols
(truly-the simple-vector
(if (listp it
) (cdr it
) it
)))
349 (,end
(locally (declare (optimize (safety 0))) (car it
))))
350 (declare (index-or-minus-1 ,end
))
352 (eval-when (:compile-toplevel
)
353 ;; Assert that the claims made in the above comment remain true.
354 (assert (= (- (* sb-vm
:n-word-bytes sb-vm
:cons-car-slot
)
355 sb-vm
:list-pointer-lowtag
)
356 (- (* sb-vm
:n-word-bytes sb-vm
:vector-length-slot
)
357 sb-vm
:other-pointer-lowtag
))))
359 (defmacro %cell-ref
(env frame-ptr
)
360 `(svref (env-payload (env-ancestor ,env
,frame-ptr
))
361 (frame-ptr-cell-index ,frame-ptr
)))
363 ;;; Return the symbol that FRAME-PTR represents in ENV (or an ancestor of it).
364 ;;; The symbol vector is a vector of (CONS SYMBOL (OR FUNCTION CTYPE)).
365 (defun frame-symbol (env frame-ptr
)
366 (let ((symbols (env-symbols (env-ancestor env frame-ptr
))))
367 (car (svref (if (listp symbols
) (cdr symbols
) symbols
)
368 (frame-ptr-cell-index frame-ptr
)))))
370 (defun %enforce-types
(typechecks env
)
372 (n (length typechecks
)))
374 (declare (index i n
))
375 (let ((ref (svref typechecks i
)))
378 ((eq i n
) (return-from %enforce-types
))
379 (let* ((frame-ptr (svref typechecks i
))
380 (val (%cell-ref env frame-ptr
))
381 (type (svref typechecks
(logior i
1))))
382 (unless (itypep val type
)
383 (typecheck-fail/ref
(frame-symbol env frame-ptr
) val type
)))))
385 (let ((val (symbol-value ref
))
386 (type (svref typechecks
(logior i
1))))
387 (unless (itypep val type
)
388 (typecheck-fail/ref ref val type
)))))))
390 (defun must-freeze-p (env)
392 (or (env-mutable-p env
)
393 (must-freeze-p (env-parent env
)))))
395 ;; This is an important operation for creation of interpreted lexical closures.
396 ;; It should execute as fast as possible.
397 (defun freeze-env (env)
398 (declare (instance env
)) ; just rule out NIL
399 (labels ((recurse (env)
400 (let* ((parent-copy (awhen (env-parent (truly-the basic-env env
))
402 ;; The reason we're grabbing ENV-SYMBOLS here is
403 ;; to ensure that the slot is accessed exactly once.
404 ;; (CONSP symbols) is the same as (mutable-p env).
405 ;; See comment in 'macros' about figuring out
406 ;; whether this is safe. Maybe I'm just paranoid?
407 ;; Otoh, maybe I'm not, since the concurrency tests
408 ;; are randomly hitting lose("Feh.") in gencgc.
409 (symbols (env-symbols env
))
410 (mutable (consp symbols
)))
411 ;; PARENT-COPY might not actually be a copy
412 (if (or mutable
(neq parent-copy
(env-parent env
)))
413 (let ((new (copy-structure env
)))
414 (setf (env-parent new
) parent-copy
)
416 (setf (env-symbols new
)
417 (cons (car (truly-the list symbols
))
423 ;;; SBCL currently takes declarations affecting policy as if they were "hoisted"
424 ;;; outside the form containing them, so that they apply to initialization forms
425 ;;; as well as body forms. This is in direct contradiction to the X3J13 decision.
426 ;;; This flag says to be conveniently bug-for-bug compatible with the compiler.
427 ;;; See https://bugs.launchpad.net/sbcl/+bug/309125
428 ;;; FIXME: is this used anywhere?
429 (declaim (boolean *hoist-optimize-declarations
*))
430 (defvar *hoist-optimize-declarations
* t
)
432 ;;; Return a new policy based on the existing policy, augmented by DECLS.
433 ;;; FIXME: this looks like it duplicates code that exists elsewhere.
434 ;;; Maybe SB-C::PROCESS-OPTIMIZE-DECL ?
435 (defun new-policy (env decls
)
436 (let ((policy (env-policy env
)) (copy-on-write t
))
437 (do-decl-spec (decl-spec decls policy
)
438 (when (eq (car decl-spec
) 'optimize
)
439 (dolist (qual+val
(cdr decl-spec
))
440 (multiple-value-bind (qual val
)
443 (values (car qual
+val
) (cadr qual
+val
)))
444 (let ((index (sb-c::policy-quality-name-p qual
)))
446 (typep val
'sb-c
::policy-quality
)
447 ;; Read the unadjusted value from the origin policy.
448 ;; If we're not changing that, don't do anything.
449 (/= val
(sb-c::%%policy-quality policy index
)))
451 (setq policy
(copy-structure policy
)
453 (sb-c::alter-policy policy index val
)))))))))
455 ;;;; Function stuff that's not in 'function.lisp'
456 ;;;; because cross-compilation does not need it.
458 ;; If a function's name slot does not hold a proper name,
459 ;; then its name is itself.
460 (defun name-for-fun (fun)
461 (let ((name (fun-name fun
)))
462 (if (and (not (eql name
0)) (legal-fun-name-p name
) (fboundp name
))
466 (defmethod print-object ((obj interpreted-function
) stream
)
467 ;; Do not try to directly print 'NAME-FOR-FUN', which returns OBJ
468 ;; itself if it has no proper name.
469 (let ((name (fun-name obj
)))
471 ;; To avoid an extra space between type and identity, the body must
472 ;; be empty, so we need two cases, because emptiness is compile-time
473 ;; determined, not based on whether the body actually printed anything.
474 (print-unreadable-object (obj stream
:type t
:identity t
))
475 ;; show name whenever NAME it is not 0, even if not OBJ's proper name.
476 (print-unreadable-object (obj stream
:type t
)
477 (prin1 name stream
)))))
479 ;;; Return approximately a type specifier for LAMBDA-LIST.
480 ;;; e.g. after doing (DEFUN FOO (A B) ...), you want (FUNCTION (T T) *)
481 ;;; This is mainly to get accurate information from DESCRIBE
482 ;;; when properly hooked in.
483 ;;; FIXME: this returns T for all &OPTIONAL and &KEY args.
484 (defun approximate-proto-fn-type (lambda-list bound-symbols
)
485 (declare (notinline member cons
))
486 (labels ((recurse (list var-index
&aux
(elt (car list
)))
487 (unless (or (eq elt
'&aux
) (null list
))
488 (let ((ll-keyword-p (member elt lambda-list-keywords
))
490 (cons (cond (ll-keyword-p elt
)
493 (acond ((cdr (svref bound-symbols var-index
))
501 (1+ var-index
))))))))
502 (keys (list &aux
(elt (car list
)))
503 (unless (or (eq elt
'&aux
) (null list
))
504 (cons (cond ((member elt lambda-list-keywords
) elt
)
505 (t `(,(parse-key-arg-spec elt
) t
)))
506 (keys (cdr list
))))))
507 `(function ,(recurse lambda-list
0) *)))
509 (declaim (type boolean
*hook-all-functions
*))
510 (defvar *hook-all-functions-p
* nil
)
512 (declaim (ftype function interpreter-trampoline interpreter-hooked-trampoline
))
514 (defun make-function (proto-fn env
)
515 (declare (type interpreted-fun-prototype proto-fn
))
516 (let ((function (%make-interpreted-function proto-fn env nil nil
)))
517 ;; Hooking all functions, makes them somewhat slower,
518 ;; but allows for really nifty introspection,
519 ;; such as discovering what calls are made by read-time evals.
520 (setf (funcallable-instance-fun function
)
521 (if *hook-all-functions-p
*
523 (apply #'interpreter-hooked-trampoline function args
))
525 (apply #'interpreter-trampoline function args
))))
528 ;; When globaldb info changes, this counter can be bumped to force interpreted
529 ;; functions to discard memoized data on their next application. For example
530 ;; if a function gets called before a global SPECIAL proclamation has been made
531 ;; regarding one of its lambda variables, this can be corrected by touching the
532 ;; globaldb cookie. On-stack functions will not see the change though.
533 ;; What remains is to hook the setting of some of the globaldb info-types.
535 (declaim (fixnum *globaldb-cookie
*))
536 (defglobal *globaldb-cookie
* most-positive-fixnum
)
538 ;; instrumentation of macro cache flushes, mostly for testing
539 (declaim (fixnum *invalidation-count
*))
540 (defglobal *invalidation-count
* 0)
542 ;; Return two values: FRAME and COOKIE, recomputing if cookie doesn't match
543 ;; globaldb, otherwise return the previously computed information.
544 (declaim (inline proto-fn-frame
))
545 (defun proto-fn-frame (proto-fn env
)
546 (if (eq (proto-fn-cookie proto-fn
) *globaldb-cookie
*)
547 (values (proto-fn-%frame proto-fn
) (proto-fn-cookie proto-fn
))
548 (digest-lambda env proto-fn
)))
550 (defun %fun-type
(fun)
551 (let ((proto-fn (fun-proto-fn fun
)))
552 (or (proto-fn-type proto-fn
)
553 (setf (proto-fn-type proto-fn
)
554 (approximate-proto-fn-type
555 (proto-fn-lambda-list proto-fn
)
557 (proto-fn-frame (fun-proto-fn fun
)
558 (interpreted-function-env fun
))))))))
560 ;; This is just a rename of DESTRUCTURING-BIND
561 ;; Should it do anything magic?
562 (defmacro with-subforms
(lambda-list arg-form
&body body
)
563 `(destructuring-bind ,lambda-list
,arg-form
,@body
))
565 ; (let ((arg-list-name (gensym "ARG-LIST-")))
566 ; (multiple-value-bind (body local-decls)
567 ; (parse-defmacro lambda-list arg-list-name body nil
568 ; 'program-destructuring-bind
570 ; :doc-string-allowed nil
572 ; :error-fun 'sb-eval::arg-count-program-error)
573 ; `(let ((,arg-list-name ,arg-list))
577 (declaim (ftype (sfunction (integer t
) function
) local-fdefinition
)
578 (maybe-inline local-fdefinition
))
580 ;; If DECL is a declaration that affects variables, return the kind of
581 ;; variable-affecting declaration it is.
582 (defun applies-to-variables-p (decl)
583 (let ((id (car decl
)))
584 (or (find id
'(ignorable ignore type special
585 dynamic-extent truly-dynamic-extent
))
586 (if (or (listp id
) ; it must be a type-specifier (including NIL)
587 (info :type
:kind id
))
590 (defglobal *unary-functions
* nil
)
591 (defglobal *binary-functions
* nil
)
593 (defun collect-progv-symbols (symbols n mask
)
595 when
(logbitp i mask
)
596 collect
(car (svref symbols i
))))
598 ;;; DECLS-LIST is a list of lists of declarations. The original structure
599 ;;; is preserved, so this necessitates a triply-nested loop.
600 ;;; e.g. (LET () (DECLARE (SPECIAL X) (SPECIAL Y)) (DECLARE (SPECIAL Z W)))
601 ;;; has decls-list (((SPECIAL X) (SPECIAL Y)) ((SPECIAL Z W)))
603 (defun declared-specials (decls-list)
605 (declare (fixnum count
))
606 (collect ((specials))
607 (do-decl-spec (decl-spec decls-list
)
608 (when (eql (car decl-spec
) 'special
)
609 (dolist (var (cdr decl-spec
))
610 (unless (memq var
(specials))
613 (values (specials) count
))))
615 ;;; See if all SYMBOLS can be declare special.
616 ;;; This applies to both free and bound variables.
617 (defun assert-declarable-as-special (env symbols
)
618 (declare (ignore env
))
619 (dolist (name symbols
)
620 (unless (symbolp name
)
621 (ip-error "~A is not a symbol" name
))
622 ;; Same logic as SB-C::PROCESS-SPECIAL-DECL
623 (let ((kind (info :variable
:kind name
)))
624 (unless (member kind
'(:special
:unknown
))
625 (error "Can't declare ~(~A~) variable locally special: ~S" kind name
)))
626 (program-assert-symbol-home-package-unlocked
627 :eval name
"declaring ~A special")))
629 ;; Given that all SPECIAL declarations in DECLS pertain to free specials,
630 ;; return a vector to supply as the SYMBOLS for an environment constructor.
631 ;; This should not be used for LET/LET*/LAMBDA binding handlers,
632 ;; which have their own way of creating the free specials along with
634 (defun free-specials (env decls
)
635 (multiple-value-bind (symbols n
) (declared-specials decls
)
637 (with-package-lock-context (env)
638 (assert-declarable-as-special env symbols
))
639 (let ((a (make-array n
)))
640 ;; If any special declaration exposes a bound special
641 ;; from an enclosing scope, the original binding cell
642 ;; is made visible in this binding scope.
643 ;; This causes any type declaration to be carried forward.
645 (setf (aref a i
) (find-special-binding env
(pop symbols
))))))))
647 (defmacro specially-bind-p
(symbol lexically-special-p
)
648 ;; Don't signal errors here: allow the interpreter to attempt to bind
649 ;; as special if so indicated, and let the native PROGV complain.
650 `(or (memq (info :variable
:kind
,symbol
) '(:constant
:global
:special
))
651 ,lexically-special-p
))
653 (defun mark-bound-specials (env declared-specials symbols n-bound
)
654 (declare (simple-vector symbols
))
655 (with-package-lock-context (env)
656 (assert-declarable-as-special env declared-specials
))
658 ;; Every time I look at this and think that it makes more sense to run the
659 ;; outer loop over declared and the inner loop over bound, so that there
660 ;; are fewer iterations, I have to remember why that is wrong -
661 ;; it would miss global proclamations.
662 (dotimes (i n-bound special-b
)
663 (let ((sym (the symbol
(car (svref symbols i
)))))
664 ;; Given: (let* ((x (foo)) (x (fn x))) (declare (special x)) ...
665 ;; only the second X is special. This mimics the compiler exactly.
666 (when (specially-bind-p
667 sym
(and (memq sym declared-specials
)
668 (not (find sym symbols
:start
(1+ i
) :end n-bound
670 (setf (logbitp i special-b
) t
))))))
672 (defun make-proto-fn (lambda-expression &optional
(silent t
))
673 (multiple-value-bind (name lambda-list body
)
674 (if (eq (car lambda-expression
) 'named-lambda
)
675 (with-subforms (name lambda-list . body
) (cdr lambda-expression
)
676 (values name lambda-list body
))
677 (with-subforms (lambda-list . body
) (cdr lambda-expression
)
678 (values 0 lambda-list body
)))
679 ;; Choke now if the list can't be parsed.
680 ;; If lexical environment is NIL, :silent will be passed as NIL,
681 ;; and we can warn about "suspcious variables" and such.
682 (parse-lambda-list lambda-list
:silent silent
)
683 (multiple-value-bind (forms decls docstring
) (parse-body body t t
)
684 (%make-proto-fn name lambda-list decls forms docstring
685 (do-decl-spec (spec decls lambda-list
)
686 (when (eq (car spec
) 'sb-c
::lambda-list
)
687 (return (cadr spec
))))))))
689 ;; Find function named by FNAME in ENV or an ancestor, returning three values:
690 ;; * KIND = {:MACRO,:FUNCTION}
691 ;; * DEF = the definition
693 (defun find-lexical-fun (env fname
)
694 (flet ((fname (x) (second (fun-name x
))))
695 (do ((test (if (atom fname
) #'eq
#'equal
))
696 (env env
(env-parent env
))
697 (level 0 (1+ level
)))
698 ((null env
) (values nil nil nil
))
699 (declare (type (unsigned-byte #.
+frame-depth-bits
+) level
))
700 (when (and (env-payload env
) ; quick check before using type predicates
701 (or (function-env-p env
) (macro-env-p env
)))
702 (multiple-value-bind (definition index
)
703 (%find-position fname
(the simple-vector
(env-payload env
))
704 nil
0 nil
#'fname test
)
706 (return (values (if (macro-env-p env
) :macro
:function
)
707 definition
(make-frame-ptr index level
)))))))))
709 ;;; Retrieve the function/macro binding of the symbol NAME in
710 ;;; environment ENV, with the global definition as a fallback.
711 ;;; The second return value is T if NAME names a macro.
713 (defun get-function (fname env
)
714 (multiple-value-bind (kind definition
) (find-lexical-fun env fname
)
715 (acond (definition (values definition
(eq kind
:macro
)))
716 ((and (symbolp fname
) (macro-function fname
)) (values it t
))
717 ;; FDEFINITION strips encapsulations, %COERCE-NAME-TO-FUN doesn't.
718 ;; There's a test in 'eval.impure.lisp' asserting that encapsulations
719 ;; aren't stripped, but frankly all bets are off when tracing.
720 (t (values (%coerce-name-to-fun fname
) nil
)))))
722 ;; Find SYM in ENV or an ancestor and return four values:
723 ;; * CELL = a cons of the symbol and its CTYPE
724 ;; * KIND = {:NORMAL,:MACRO,:SPECIAL}
726 ;; * VALUE = the value, if KIND is :NORMAL, else the macroexpansion
728 ;; Bindings are in parallel symbol/value vectors left-to-right as appearing
729 ;; in source. Scanning is right-to-left so that later LET* bindings shadow
730 ;; earlier ones of the same name. The end pointer in a LET* environment
731 ;; constrains the usable length of the symbol vector.
732 ;; Unbound ("free") special variables have no entry in the value vector.
734 (defun find-lexical-var (env sym
)
735 (do ((env env
(env-parent env
))
736 (level 0 (1+ level
)))
737 ((null env
) (values nil nil nil
))
738 (declare (type (unsigned-byte #.
+frame-depth-bits
+) level
))
739 (with-environment-vars (symbols index
) env
; skipped if no symbols
740 ;; Emulate find/position with :FROM-END T here, but faster.
742 (when (minusp (decf index
)) (return))
743 (let ((cell (svref symbols index
)))
744 (when (eq (binding-symbol cell
) sym
)
745 (multiple-value-bind (kind value
)
746 (cond ((or (var-env-p env
) (lambda-env-p env
))
747 (let ((values (the simple-vector
(env-payload env
))))
748 (if (or (>= index
(length values
))
750 (frame-special-b (env-contour env
))))
752 (values :normal
(svref values index
)))))
753 ((symbol-macro-env-p env
)
754 (let ((values (the simple-vector
(env-payload env
))))
755 (if (>= index
(length values
))
757 (values :macro
(svref values index
)))))
758 (t ; function-env, macro-env, basic-env (locally).
759 :special
)) ; no symbol is bound
760 (return-from find-lexical-var
761 (values cell kind
(make-frame-ptr index level
) value
)))))))))
763 ;;; Search ENV for BINDING and return a frame-pointer if the variable
764 ;;; is a lexical var, or :SPECIAL or :MACRO if it is one of those.
765 ;;; Lexically visible special bindings return :SPECIAL.
766 ;;; This is similar to FIND-LEXICAL-VAR in its operation,
767 ;;; but simpler, as bindings are unique objects.
768 (defun find-binding (env binding
)
769 (do ((env env
(env-parent env
))
770 (level 0 (1+ level
)))
772 (declare (type (unsigned-byte #.
+frame-depth-bits
+) level
))
773 (with-environment-vars (bindings index
) env
; skipped if no symbols
774 (declare (ignore index
))
775 (let ((payload (env-payload env
))
776 (index (position binding bindings
)))
779 (cond ((or (var-env-p env
) (lambda-env-p env
))
780 (if (or (>= index
(length (the simple-vector payload
)))
781 (logbitp index
(frame-special-b (env-contour env
))))
783 (make-frame-ptr index level
)))
784 ((symbol-macro-env-p env
)
785 (if (>= index
(length (the simple-vector payload
)))
788 (t ; function-env, macro-env, basic-env (locally).
789 :special
)))))))) ; no symbol is bound
791 ;;; Similar to the above, but only return a lexically visible special binding.
792 ;;; This is required to locate the intended binding in cases such as this:
794 (let ((a 3)) ; special A[1]
795 (declare (special a
))
796 (symbol-macrolet ((a x
)) ; macro A[2]
797 (let ((a (foo))) ; lexical A[3]
798 (macrolet ((foo () ...
))
799 (declare (real a
) (special a
)) ; declares the type of A[1]
800 A
)))) ; references A[1]
802 (defun find-special-binding (env sym
)
803 (do ((env env
(env-parent env
)))
804 ((null env
) sym
) ; Return just SYM if no binding found.
805 ;; Only a LET-like frames can create special bindings.
806 (when (or (var-env-p env
) (lambda-env-p env
))
807 (with-environment-vars (symbols index
) env
; skipped if no symbols
808 (let ((index (position sym symbols
809 :end
(min index
(length (env-payload env
)))
810 :key
#'car
:test
#'eq
:from-end t
)))
811 (when (and index
(logbitp index
(frame-special-b (env-contour env
))))
812 (return (svref symbols index
))))))))
814 ;;; BINDING is either a cell or a symbol (if a free special).
815 (defun find-type-restriction (env binding
)
816 (do ((env env
(env-parent env
)))
819 (or (cdr binding
) *universal-type
*)
821 (unless (env-mutable-p env
)
822 (awhen (assq binding
(type-restrictions (env-contour env
)))
823 (return (cdr it
))))))
825 ;;; Update DECL-SCOPE with type restrictions based on its declarations.
826 ;;; Restrictions are separated into those which apply to bindings made by
827 ;;; this scope - each being pertinent as soon as the variable to which it
828 ;;; applies is bound - and those which apply to the body forms.
829 ;;; Bound lexical and special variables in the new scope have the CTYPE
830 ;;; as stored in the CDR of the binding cell altered to reflect the
831 ;;; restriction, other restrictions go into the TYPE-RESTRICTIONS slot.
832 ;;; A special falls into the latter category if the binding is lexically
833 ;;; visible but did not occur in exactly this scope. This avoids stomping
834 ;;; on the type that was stored in the scope which made the binding.
835 (defun process-typedecls (decl-scope env n-var-bindings symbols
836 &aux new-restrictions
)
837 ;; First compute the effective set of type restrictions.
838 (with-package-lock-context (env)
839 (do-decl-spec (decl (declarations decl-scope
))
841 ((eq (applies-to-variables-p decl
) 'type
)
842 (binding* (((type-spec names
)
843 (if (eq (car decl
) 'type
)
844 (values (cadr decl
) (cddr decl
))
845 (values (car decl
) (cdr decl
))))
846 (ctype (specifier-type type-spec
)))
847 (dolist (symbol names
)
848 (when (and (symbolp symbol
) (boundp symbol
))
849 (program-assert-symbol-home-package-unlocked
850 :eval symbol
"declaring the type of ~A"))
851 (unless (eq ctype
*universal-type
*)
852 (multiple-value-bind (binding index
)
853 (%find-position symbol symbols t
0 nil
#'binding-symbol
#'eq
)
854 (if (and index
(< index n-var-bindings
))
855 ;; Any kind of binding created in directly this frame.
856 ;; Type restrictions aren't pervasive downward,
857 ;; so this case doesn't intersect the new type with a
858 ;; prevailing restriction. Global proclamations are
859 ;; pervasive, but violations are caught by the runtime.
861 (acond ((cdr binding
) (type-intersection it ctype
))
863 ;; Three possibilities now:
864 ;; 1. INDEX was past the number of bindings in this scope.
865 ;; This is either a locally declared free special,
866 ;; or a special declaration that exposes a special
867 ;; var bound in some containing scope, possibly with
868 ;; intervening non-special bindings of the same name.
869 ;; 2. A binding from an earlier scope not covered by case 1.
870 ;; 3. Something global: an assumed or proclaimed special,
871 ;; or a global symbol-macro.
872 (let* ((thing (or binding
; case 1
873 (find-lexical-var env symbol
) ; case 2
875 (restriction (assq thing new-restrictions
)))
878 (type-intersection (cdr restriction
) ctype
))
879 (let* ((old-type (find-type-restriction env thing
))
880 (new-type (type-intersection old-type ctype
)))
881 (unless (type= old-type new-type
)
882 (push (cons thing new-type
)
883 new-restrictions
)))))))))))
884 ((eq (car decl
) 'ftype
)
885 (dolist (name (cddr decl
))
886 (when (and (legal-fun-name-p name
) (fboundp name
))
887 (program-assert-symbol-home-package-unlocked
888 :eval name
"declaring the ftype of ~A")))))))
890 (setf (type-restrictions decl-scope
) new-restrictions
)
891 ;; Done computing effective restrictions.
892 ;; If the enclosing policy - not the new policy - demands typechecks,
893 ;; then insert assertions for all variables bound by this scope.
894 (when (and (policy env
(>= safety
1))
895 (find-if #'cdr symbols
:end n-var-bindings
))
896 (let ((checks (make-array n-var-bindings
)))
897 (dotimes (i n-var-bindings
(setf (binding-typechecks decl-scope
) checks
))
898 (awhen (cdr (svref symbols i
))
899 (setf (svref checks i
) (type-checker it
))))))
900 ;; If a nested scope re-declares a variable to be of a more constrained
901 ;; type "for efficiency" it does not really help the interpreter any,
902 ;; so don't do those checks unless SAFETY exceeds 2.
903 ;; This is a somewhat arbitrary but reasonable stance to take.
904 (when (and (policy env
(>= safety
2)) new-restrictions
)
905 (collect ((lexical-var-checks) (special-var-checks))
906 (dolist (check new-restrictions
)
907 (let ((binding (car check
))
908 (checkfun (type-checker (cdr check
))))
909 (if (consp binding
) ; some kind of binding, not sure what
910 (let ((frame-ptr (find-binding env binding
)))
913 (:special
(special-var-checks (car binding
) checkfun
))
914 (t (lexical-var-checks frame-ptr checkfun
))))
915 (special-var-checks binding checkfun
))))
916 ;; Restrictions could pertain to symbol-macros only,
917 ;; which are not checked on entry to the scope.
918 (when (or (lexical-var-checks) (special-var-checks))
919 (setf (extra-typechecks decl-scope
)
920 (coerce (nconc (special-var-checks) (lexical-var-checks))
924 ;;; Return the thing that should be asserted about VARIABLE's type.
925 ;;; If there is nothing to check - no declared type, or the current policy
926 ;;; does not require type-checking, then return NIL.
927 ;;; These are the distinct things that might want different controls:
928 ;;; - initial bindings
929 ;;; - entrance to new scope with stronger constraint
933 ;;; Only the writes and reads are controlled here,
934 ;;; the others are kind of spread out. It might be nice to consolidate
935 ;;; the policy-related decisions somewhere.
937 (defun var-type-assertion (env symbol binding op
)
938 ;; ** these criteria are subject to change. Not sure they're the best.
940 (:write
(policy env
(>= safety
1)))
941 (:read
(policy env
(and (= safety
3) (= speed
0)))))
942 (let ((type (find-type-restriction env
(or binding symbol
))))
943 (if (eq type
*universal-type
*) nil
(type-checker type
)))))
945 ;;; Convert compiler env to interpreter env if possible,
946 ;;; otherwise return :COMPILE.
947 ;;; A lexical environment which contains only macros and decls is ok.
948 ;;; Locally [not]inline declarations about global functions are ok.
949 (defun env-from-lexenv (lexenv &aux
(compiler-funs (sb-c::lexenv-vars lexenv
))
950 (compiler-vars (sb-c::lexenv-funs lexenv
)))
951 (flet ((harmless-defined-fun-p (thing)
952 (and (typep thing
'sb-c
::defined-fun
)
953 (eq (sb-c::defined-fun-kind thing
) :global-function
)))
955 (typep thing
'(cons (eql sb-sys
:macro
)))))
956 (if (or (sb-c::lexenv-blocks lexenv
)
957 (sb-c::lexenv-tags lexenv
)
958 ;; FIXME: why test -LAMBDA here? Isn't that a book-keeping thing,
959 ;; not a semantics thing? (See also similar code in 'full-eval')
960 (sb-c::lexenv-lambda lexenv
)
961 (sb-c::lexenv-cleanup lexenv
)
962 (sb-c::lexenv-type-restrictions lexenv
)
963 (find-if-not (lambda (x)
964 (or (macro-p x
) (harmless-defined-fun-p x
)))
965 compiler-funs
:key
#'cdr
)
966 (find-if-not #'macro-p compiler-vars
:key
#'cdr
))
969 ((disabled-package-locks
970 `((declare (disabled-package-locks
971 ,@(sb-c::lexenv-disabled-package-locks lexenv
)))))
973 ;; Macros in an interpreter environment must look like interpreted
974 ;; functions due to use of FUN-NAME to extract their name as a key
975 ;; rather than also needing an alist mapping names to objects.
976 ;; For each compiled expander, wrap it in a trivial interpreted fun.
981 (let ((expander (cddr cell
)))
982 (if (interpreted-function-p expander
)
985 (%make-proto-fn
`(macrolet ,(car cell
)) '(form env
)
987 `((funcall ,expander form env
)) nil
)
988 nil
)))) ; environment for the interpreted fun
989 (remove-if-not #'macro-p compiler-funs
:key
#'cdr
))
990 nil
; no free specials vars
991 ;; FIXME: type-restrictions, handled-conditions.
992 (make-decl-scope (if compiler-vars nil disabled-package-locks
)
993 (sb-c::lexenv-policy lexenv
)))))
994 (if (not compiler-vars
)
996 (make-symbol-macro-env
998 (map 'vector
#'cddr compiler-vars
)
999 (map 'vector
(lambda (x) (list (car x
))) compiler-vars
)
1000 (make-decl-scope disabled-package-locks
1001 (sb-c::lexenv-policy lexenv
))))))))
1003 ;;; Enclose PROTO-FN in the environment ENV.
1004 ;;; SEXPR is provided only because this is a HANDLER.
1005 (defun enclose (proto-fn env sexpr
)
1006 (declare (ignore sexpr
))
1007 (make-function proto-fn env
))
1009 ;;; If ENV is a LET* environment that is not yet complete, then make a copy.
1010 ;;; Recurse up and see if copy needs to be done on any parent ENV - so not exactly
1011 ;;; a shallow copy. It boggles the mind to think of reasons a parent ENV would
1012 ;;; be getting sequentially bound and a descendant ENV is captured, but of course
1013 ;;; that must be dealt with properly.
1014 ;;; It seems unlikely that there would be much benefit from memoizing a
1015 ;;; frozen ENV - multiple closures over the same mutable ENV could get the
1016 ;;; same immutable copy, but where would I stash it?
1017 (defun enclose-freeze (proto-fn env sexpr
)
1018 (declare (ignore sexpr
))
1019 (make-function proto-fn
(freeze-env env
)))
1021 ;;; Try to compile an interpreted function. If the environment
1022 ;;; contains local functions we'll punt on compiling it.
1023 ;;; Lexical vars are OK but not specials of either the bound or free variety.
1024 ;;; LEXENV-FROM-ENV fakes up a GLOBAL-VAR which is fine for
1025 ;;; limited kinds of analysis but not for really compiling (at least I
1026 ;;; think it isn't), so must be avoided. This conservatively prevents
1027 ;;; compilation when it shouldn't, but is more liberal than before.
1028 ;;; An example of an environment in which compilation should occur but won't:
1029 ;;; (locally (declare (special x)) (symbol-macrolet ((x 3)) (defun f ...
1031 ;;; Bound specials that were proclaimed special, not locally declared,
1032 ;;; should be allowed because we don't have to inject any SPECIAL declaration
1033 ;;; or otherwise manipulate the lexenv to have the compiler know about
1034 ;;; the specialness.
1035 ;;; Free specials could be made to work fairly easily by inserting
1036 ;;; a (declare (special ...)) into the lambda, provided that there are no
1037 ;;; &optional/&key/&aux arguments. If there any hairy arguments, we don't know
1038 ;;; if some argument's defaulting form would have needed to know about the
1039 ;;; specialness of a symbol.
1041 ;;; Compiled code can access lexical vars in interpreted closures.
1042 ;;; It is achieved by changing each lexical var into a symbol macro
1043 ;;; that accesses its storage location.
1044 ;;; In practice it's likely that an interpreted closure would be "too complex"
1045 ;;; for other reasons, usually due to surrounding BLOCK. It would be somewhat
1046 ;;; nifty to walk the code and find that the block is never used.
1047 (defun prepare-for-compile (function &aux nullify-lexenv
)
1048 (if (named-let too-complex-p
((env (interpreted-function-env function
)))
1050 (return-from too-complex-p nil
))
1051 (when (or (typep env
'(or function-env block-env tagbody-env
))
1052 (and (typep env
'lambda-env
)
1053 ;; a block makes it too complex
1054 (neq (lambda-frame-block-name (env-contour env
)) 0)))
1055 (return-from too-complex-p t
))
1057 (with-environment-vars (symbols end
) env
1058 (when (or (and (= end
(length symbols
)) ; all symbols are accessible
1059 ;; More symbols then values means free specials.
1060 (> (length symbols
) (length (env-payload env
))))
1061 (let ((frame (env-contour env
)))
1062 (and (typep env
'(or var-env lambda-env
))
1063 ;; any bound specials must be proclaimed special
1064 ;; so that we can just drop the binding
1065 (ldb-test (byte end
0) (frame-special-b frame
)))))
1066 (return-from too-complex-p t
)))
1067 ;; Decls inserted into the lambda would give them a scope that is
1068 ;; technically "too small". This is fundamentally a problem in the
1069 ;; NO-HOISTING vote of X3J13. Using syntactic constructs there is
1070 ;; no way to guarantee a safe entry to functions if the prevailing
1071 ;; policy was unsafe:
1072 ;; (declaim (optimize (safety 0)))
1073 ;; (compile nil '(lambda (arg) (declare (optimize safety)) ...))
1074 ;; [They could have voted to hoist OPTIMIZE if nothing else].
1075 ;; But if the only decls in ENV pertain to a POLICY, then simply
1076 ;; propagating that policy into the resulting LEXENV is exactly right.
1077 (do-decl-spec (spec (env-declarations env
))
1078 (unless (member (car spec
) '(optimize))
1079 (return-from too-complex-p t
)))
1080 (too-complex-p (env-parent env
))) ; recurse
1081 ;; KLUDGE: if for no other reason than to make some assertions pass,
1082 ;; we'll recognize the case where the function body does not actually
1083 ;; need its lexical environment.
1084 (let ((forms (proto-fn-forms (fun-proto-fn function
))))
1085 ;; Happily our CONSTANTP is smart enough to look into a BLOCK.
1086 (if (and (singleton-p forms
) (constantp (car forms
)))
1087 (setq nullify-lexenv t
)
1088 (error 'interpreter-environment-too-complex-error
1090 "~@<Lexical environment of ~S is too complex to compile.~:@>"
1091 :format-arguments
(list function
)))))
1092 (values (fun-lambda-expression function
)
1093 (acond ((and (not nullify-lexenv
) (interpreted-function-env function
))
1094 (lexenv-from-env it
'compile
))
1096 (make-null-lexenv)))))
1098 ;;; Convert ENV from an interpreter environment to a compiler environment,
1099 ;;; i.e. one which is acceptable to various environment inquiry functions
1100 ;;; that do not understand interpreter environments.
1101 ;;; (Things like MACROEXPAND do understand interpreter environments)
1102 ;;; If REASON is COMPILE, then symbols which refer to the interpreter's
1103 ;;; lexical variables are changed to symbol-macros which access the
1104 ;;; interpreter variables.
1106 ;;; NB: This is not the only way to attack the problem of having the
1107 ;;; compiler deal with subtypes of ABSTRACT-LEXENV. Another way would
1108 ;;; make all access functions just do the right thing to begin with,
1109 ;;; though it might slow down the compiler a little bit, since it really
1110 ;;; likes to manipulate LEXENVs a lot.
1111 ;;; Also the parts for sb-cltl2 are fairly odious.
1113 (defun lexenv-from-env (env &optional reason
)
1114 (let ((lexenv (%lexenv-from-env
(make-hash-table :test
'eq
) env reason
)))
1115 (setf (sb-c::lexenv-%policy lexenv
) (%policy
(env-contour env
))
1116 (sb-c::lexenv-disabled-package-locks lexenv
)
1117 (env-disabled-package-locks env
))
1120 (defun %lexenv-from-env
(var-map env
&optional reason
)
1121 (let ((lexenv (acond ((env-parent env
) (%lexenv-from-env var-map it reason
))
1122 ;; The null-lexenv has to be copied into a new
1123 ;; lexenv to get a snapshot of *POLICY*.
1124 (t (sb-c::make-lexenv
:default
(make-null-lexenv)))))
1125 (payload (env-payload env
)))
1126 (flet ((specialize (binding) ; = make a global var, not make less general
1127 (let ((sym (binding-symbol binding
)))
1128 (cons sym
(make-global-var :%source-name sym
1130 :where-from
:declared
))))
1131 (macroize (name thing
) (list* name
'sb-sys
:macro thing
))
1132 (fname (f) (second (fun-name f
))))
1133 (multiple-value-bind (vars funs
)
1135 ((or var-env lambda-env
)
1136 (with-environment-vars (symbols end
) env
1137 (loop for i fixnum from
(1- end
) downto
0
1138 for binding
= (svref symbols i
)
1139 for sym
= (binding-symbol binding
)
1141 (cond ((or (>= i
(length payload
))
1142 (logbitp i
(frame-special-b (env-contour env
))))
1143 (specialize binding
))
1144 ((eq reason
'compile
)
1145 ;; access interpreter's lexical vars
1146 (macroize sym
`(svref ,payload
,i
)))
1148 (let ((leaf (make-lambda-var
1150 :type
(or (cdr binding
) *universal-type
*))))
1151 (setf (gethash binding var-map
) leaf
)
1152 (cons sym leaf
)))))))
1155 (lambda (cell expansion
)
1156 (list* (car cell
) 'sb-sys
:macro
1157 (acond ((cdr cell
) `(the ,it
,expansion
))
1159 (env-symbols env
) payload
)
1160 ;; symbols without values are free specials
1161 (map 'list
#'specialize
1162 (subseq (env-symbols env
) (length payload
)))))
1163 ((or function-env macro-env
)
1164 ;; all symbols are free specials
1165 (values (map 'list
#'specialize
(env-symbols env
))
1166 (map 'list
(if (macro-env-p env
)
1167 (lambda (f) (macroize (fname f
) f
))
1168 (lambda (f &aux
(name (fname f
)))
1170 (sb-c::make-functional
1172 ;; LEXENV is given only because of
1173 ;; type-checking. Value is bogus.
1174 :lexenv
(sb-kernel:make-null-lexenv
)))))
1176 (basic-env ; as in (LOCALLY (DECLARE ..))
1177 (values (map 'list
#'specialize
(env-symbols env
)) nil
)))
1178 ;; FIXME: This is a rather inefficient, and particularly ugly.
1179 ;; Since all the data that are needed by SB-CLTL2 are already
1180 ;; present in the interpreter ENV, it should just look there directly.
1181 ;; The saving grace is that most decls don't have a decl handler.
1182 (do-decl-spec (spec (env-declarations env
))
1185 ;; In (LET* ((X (F)) (X (G X))) (declare (ignore x)) ...)
1186 ;; it's the second X that is ignored. Does this code reflect that?
1187 (dolist (sym (cdr spec
))
1188 (let ((var (cdr (assoc sym vars
))))
1189 (when (sb-c::lambda-var-p var
)
1190 (setf (sb-c::lambda-var-flags var
) 1)))))
1192 ;; This is just enough to get sb-cltl2 tests to pass.
1193 (let ((inlinep (case (car spec
)
1195 (notinline :notinline
))))
1196 (dolist (fname (cdr spec
))
1197 (let ((fun (cdr (assoc fname funs
:test
'equal
))))
1200 (setf (sb-c::functional-inlinep fun
) inlinep
))
1203 (sb-c::make-defined-fun
1205 :type
(sb-int:proclaimed-ftype fname
))))
1206 (setf (sb-c::defined-fun-inlinep defined-fun
) inlinep
)
1207 (push (cons fname defined-fun
) funs
))))))))
1209 ;; As usual, just enough to get sb-cltl2 to pass tests.
1210 (let ((ctype (specifier-type (cadr spec
))))
1211 (dolist (fname (cddr spec
))
1212 (let ((fun (cdr (assoc fname funs
:test
'equal
))))
1215 (setf (sb-c::leaf-type fun
) ctype
)))))))
1216 ((ignorable type optimize special dynamic-extent
)
1219 (let ((fn (info :declaration
:handler
(first spec
))))
1224 ;; This is surely wrong. And as the comment above says,
1225 ;; it's ridiculous that these undergo conversion at all.
1228 (let ((thing (cdr x
)))
1230 (cons x
) ; symbol-macro
1231 (sb-c::lambda-var thing
)
1232 (sb-c::global-var
(make-lambda-var
1234 :%source-name
(car x
))))))
1236 ;; And surely this is wrong...
1239 ;; type-restrictions are represented in the same way essentially.
1240 (dolist (restriction (type-restrictions (env-contour env
)))
1241 (let ((binding (car restriction
)))
1243 (push (cons (gethash binding var-map
) (cdr restriction
))
1244 (sb-c::lexenv-type-restrictions lexenv
)))))
1246 (setf (sb-c::lexenv-vars lexenv
) (nconc vars
(sb-c::lexenv-vars lexenv
))
1247 (sb-c::lexenv-funs lexenv
) (nconc funs
(sb-c::lexenv-funs lexenv
))
1248 ;; FIXME: handled conditions
1252 ;;; Produce the source representation expected by :INLINE-EXPANSION-DESIGNATOR.
1253 (defun reconstruct-syntactic-closure-env (env &aux guts
)
1255 (awhen (env-declarations env
)
1256 (setq guts
`((:declare
,(apply 'append
(mapcar 'cdr it
)) ,@guts
))))
1257 (multiple-value-bind (kind data
)
1263 ;; The name of each macro is (MACROLET symbol).
1264 (cons (second (fun-name f
))
1265 (fun-lambda-expression f
)))
1266 (env-payload env
))))
1268 (values :symbol-macro
1269 (map 'list
(lambda (x y
) (list (car x
) y
))
1270 (env-symbols env
) (env-payload env
)))))
1272 (setq guts
`((,kind
,data
,@guts
)))))
1273 (unless (setq env
(env-parent env
))
1274 (return (car guts
)))))
1276 ;;; Return :INLINE or :NOTINLINE if FNAME has a lexical declaration,
1277 ;;; otherwise NIL for no information.
1278 ;;; FIXME: obviously this does nothing
1279 (defun fun-lexically-notinline-p (fname env
)
1280 (declare (ignore fname env
))