Replace DEF!METHOD and SB!XC:DEFMETHOD with just DEFMETHOD.
[sbcl.git] / src / code / target-package.lisp
blobde0a24cf5dd12535c1fbac126fa1f77d52643d83
1 ;;;; PACKAGEs and stuff like that
2 ;;;;
3 ;;;; Note: The code in this file signals many correctable errors. This
4 ;;;; is not just an arbitrary aesthetic decision on the part of the
5 ;;;; implementor -- many of these are specified by ANSI 11.1.1.2.5,
6 ;;;; "Prevention of Name Conflicts in Packages":
7 ;;;; Within one package, any particular name can refer to at most one
8 ;;;; symbol. A name conflict is said to occur when there would be more
9 ;;;; than one candidate symbol. Any time a name conflict is about to
10 ;;;; occur, a correctable error is signaled.
11 ;;;;
12 ;;;; FIXME: The code contains a lot of type declarations. Are they
13 ;;;; all really necessary?
15 ;;;; This software is part of the SBCL system. See the README file for
16 ;;;; more information.
17 ;;;;
18 ;;;; This software is derived from the CMU CL system, which was
19 ;;;; written at Carnegie Mellon University and released into the
20 ;;;; public domain. The software is in the public domain and is
21 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
22 ;;;; files for more information.
24 (in-package "SB!IMPL")
26 ;;;; Thread safety
27 ;;;;
28 ;;;; ...this could still use work, but the basic idea is:
29 ;;;;
30 ;;;; *PACKAGE-GRAPH-LOCK* is held via WITH-PACKAGE-GRAPH while working on
31 ;;;; package graph, including package -> package links, and interning and
32 ;;;; uninterning symbols.
33 ;;;;
34 ;;;; Hash-table lock on *PACKAGE-NAMES* is held via WITH-PACKAGE-NAMES while
35 ;;;; frobbing name -> package associations.
36 ;;;;
37 ;;;; There should be no deadlocks due to ordering issues between these two, as
38 ;;;; the latter is only held over operations guaranteed to terminate in finite
39 ;;;; time.
40 ;;;;
41 ;;;; Errors may be signalled while holding on to the *PACKAGE-GRAPH-LOCK*,
42 ;;;; which can still lead to pretty damned inconvenient situations -- but
43 ;;;; since FIND-PACKAGE, FIND-SYMBOL from other threads isn't blocked by this,
44 ;;;; the situation isn't *quite* hopeless.
45 ;;;;
46 ;;;; A better long-term solution seems to be in splitting the granularity of
47 ;;;; the *PACKAGE-GRAPH-LOCK* down: for interning a per-package lock should be
48 ;;;; sufficient, though interaction between parallel intern and use-package
49 ;;;; needs to be considered with some care.
51 (defvar *package-graph-lock*)
53 (defun call-with-package-graph (function)
54 (declare (function function))
55 ;; FIXME: Since name conflicts can be signalled while holding the
56 ;; mutex, user code can be run leading to lock ordering problems.
57 (sb!thread:with-recursive-lock (*package-graph-lock*)
58 (funcall function)))
60 ;;; a map from package names to packages
61 (defvar *package-names*)
62 (declaim (type hash-table *package-names*))
64 (defmacro with-package-names ((names &key) &body body)
65 `(let ((,names *package-names*))
66 (with-locked-system-table (,names)
67 ,@body)))
69 ;;;; PACKAGE-HASHTABLE stuff
71 (defmethod print-object ((table package-hashtable) stream)
72 (declare (type stream stream))
73 (print-unreadable-object (table stream :type t :identity t)
74 (let* ((n-live (%package-hashtable-symbol-count table))
75 (n-deleted (package-hashtable-deleted table))
76 (n-filled (+ n-live n-deleted))
77 (n-cells (1- (length (package-hashtable-cells table)))))
78 (format stream
79 "(~D+~D)/~D [~@[~,3f words/sym,~]load=~,1f%]"
80 n-live n-deleted n-cells
81 (unless (zerop n-live)
82 (/ (* (1+ (/ sb!vm:n-word-bytes)) n-cells) n-live))
83 (* 100 (/ n-filled n-cells))))))
85 ;;; the maximum load factor we allow in a package hashtable
86 (!defparameter *package-rehash-threshold* 3/4)
88 ;;; the load factor desired for a package hashtable when writing a
89 ;;; core image
90 (!defparameter *package-hashtable-image-load-factor* 1/2)
92 ;;; Make a package hashtable having a prime number of entries at least
93 ;;; as great as (/ SIZE *PACKAGE-REHASH-THRESHOLD*). If RES is supplied,
94 ;;; then it is destructively modified to produce the result. This is
95 ;;; useful when changing the size, since there are many pointers to
96 ;;; the hashtable.
97 ;;; Actually, the smallest table built here has three entries. This
98 ;;; is necessary because the double hashing step size is calculated
99 ;;; using a division by the table size minus two.
100 (defun make-package-hashtable (size)
101 (flet ((actual-package-hashtable-size (size)
102 (loop for n of-type fixnum
103 from (logior (ceiling size *package-rehash-threshold*) 1)
104 by 2
105 when (positive-primep n) return n)))
106 (let* ((n (actual-package-hashtable-size size))
107 (size (truncate (* n *package-rehash-threshold*)))
108 (table (make-array (1+ n) :initial-element 0)))
109 (setf (aref table n)
110 (make-array n :element-type '(unsigned-byte 8)
111 :initial-element 0))
112 (%make-package-hashtable table size))))
114 (declaim (inline pkg-symbol-valid-p))
115 (defun pkg-symbol-valid-p (x) (not (fixnump x)))
117 ;;; Destructively resize TABLE to have room for at least SIZE entries
118 ;;; and rehash its existing entries.
119 (defun resize-package-hashtable (table size)
120 (let* ((symvec (package-hashtable-cells table))
121 (len (1- (length symvec)))
122 (temp-table (make-package-hashtable size)))
123 (dotimes (i len)
124 (let ((sym (svref symvec i)))
125 (when (pkg-symbol-valid-p sym)
126 (add-symbol temp-table sym))))
127 (setf (package-hashtable-cells table) (package-hashtable-cells temp-table)
128 (package-hashtable-size table) (package-hashtable-size temp-table)
129 (package-hashtable-free table) (package-hashtable-free temp-table)
130 (package-hashtable-deleted table) 0)))
132 ;;;; package locking operations, built conditionally on :sb-package-locks
134 #!+sb-package-locks
135 (progn
136 (defun package-locked-p (package)
137 #!+sb-doc
138 "Returns T when PACKAGE is locked, NIL otherwise. Signals an error
139 if PACKAGE doesn't designate a valid package."
140 (package-lock (find-undeleted-package-or-lose package)))
142 (defun lock-package (package)
143 #!+sb-doc
144 "Locks PACKAGE and returns T. Has no effect if PACKAGE was already
145 locked. Signals an error if PACKAGE is not a valid package designator"
146 (setf (package-lock (find-undeleted-package-or-lose package)) t))
148 (defun unlock-package (package)
149 #!+sb-doc
150 "Unlocks PACKAGE and returns T. Has no effect if PACKAGE was already
151 unlocked. Signals an error if PACKAGE is not a valid package designator."
152 (setf (package-lock (find-undeleted-package-or-lose package)) nil)
155 (defun package-implemented-by-list (package)
156 #!+sb-doc
157 "Returns a list containing the implementation packages of
158 PACKAGE. Signals an error if PACKAGE is not a valid package designator."
159 (package-%implementation-packages (find-undeleted-package-or-lose package)))
161 (defun package-implements-list (package)
162 #!+sb-doc
163 "Returns the packages that PACKAGE is an implementation package
164 of. Signals an error if PACKAGE is not a valid package designator."
165 (let ((package (find-undeleted-package-or-lose package)))
166 (loop for x in (list-all-packages)
167 when (member package (package-%implementation-packages x))
168 collect x)))
170 (defun add-implementation-package (packages-to-add
171 &optional (package *package*))
172 #!+sb-doc
173 "Adds PACKAGES-TO-ADD as implementation packages of PACKAGE. Signals
174 an error if PACKAGE or any of the PACKAGES-TO-ADD is not a valid
175 package designator."
176 (let ((package (find-undeleted-package-or-lose package))
177 (packages-to-add (package-listify packages-to-add)))
178 (setf (package-%implementation-packages package)
179 (union (package-%implementation-packages package)
180 (mapcar #'find-undeleted-package-or-lose packages-to-add)))))
182 (defun remove-implementation-package (packages-to-remove
183 &optional (package *package*))
184 #!+sb-doc
185 "Removes PACKAGES-TO-REMOVE from the implementation packages of
186 PACKAGE. Signals an error if PACKAGE or any of the PACKAGES-TO-REMOVE
187 is not a valid package designator."
188 (let ((package (find-undeleted-package-or-lose package))
189 (packages-to-remove (package-listify packages-to-remove)))
190 (setf (package-%implementation-packages package)
191 (nset-difference
192 (package-%implementation-packages package)
193 (mapcar #'find-undeleted-package-or-lose packages-to-remove)))))
195 (defmacro with-unlocked-packages ((&rest packages) &body forms)
196 #!+sb-doc
197 "Unlocks PACKAGES for the dynamic scope of the body. Signals an
198 error if any of PACKAGES is not a valid package designator."
199 (with-unique-names (unlocked-packages)
200 `(let (,unlocked-packages)
201 (unwind-protect
202 (progn
203 (dolist (p ',packages)
204 (when (package-locked-p p)
205 (push p ,unlocked-packages)
206 (unlock-package p)))
207 ,@forms)
208 (dolist (p ,unlocked-packages)
209 (when (find-package p)
210 (lock-package p)))))))
212 (defun package-lock-violation (package &key (symbol nil symbol-p)
213 format-control format-arguments)
214 (let* ((restart :continue)
215 (cl-violation-p (eq package *cl-package*))
216 (error-arguments
217 (append (list (if symbol-p
218 'symbol-package-locked-error
219 'package-locked-error)
220 :package package
221 :format-control format-control
222 :format-arguments format-arguments)
223 (when symbol-p (list :symbol symbol))
224 (list :references
225 (append '((:sbcl :node "Package Locks"))
226 (when cl-violation-p
227 '((:ansi-cl :section (11 1 2 1 2)))))))))
228 (restart-case
229 (apply #'cerror "Ignore the package lock." error-arguments)
230 (:ignore-all ()
231 :report "Ignore all package locks in the context of this operation."
232 (setf restart :ignore-all))
233 (:unlock-package ()
234 :report "Unlock the package."
235 (setf restart :unlock-package)))
236 (ecase restart
237 (:continue
238 (pushnew package *ignored-package-locks*))
239 (:ignore-all
240 (setf *ignored-package-locks* t))
241 (:unlock-package
242 (unlock-package package)))))
244 (defun package-lock-violation-p (package &optional (symbol nil symbolp))
245 ;; KLUDGE: (package-lock package) needs to be before
246 ;; comparison to *package*, since during cold init this gets
247 ;; called before *package* is bound -- but no package should
248 ;; be locked at that point.
249 (and package
250 (package-lock package)
251 ;; In package or implementation package
252 (not (or (eq package *package*)
253 (member *package* (package-%implementation-packages package))))
254 ;; Runtime disabling
255 (not (eq t *ignored-package-locks*))
256 (or (eq :invalid *ignored-package-locks*)
257 (not (member package *ignored-package-locks*)))
258 ;; declarations for symbols
259 (not (and symbolp (lexically-unlocked-symbol-p symbol)))))
261 (defun lexically-unlocked-symbol-p (symbol)
262 (member symbol
263 (if (boundp 'sb!c::*lexenv*)
264 (let ((list (sb!c::lexenv-disabled-package-locks sb!c::*lexenv*)))
265 ;; The so-called LIST might be an interpreter env.
266 #!+sb-fasteval
267 (unless (listp list)
268 (return-from lexically-unlocked-symbol-p
269 (sb!interpreter::lexically-unlocked-symbol-p
270 symbol list)))
271 list)
272 sb!c::*disabled-package-locks*)))
274 ) ; progn
276 ;;;; more package-locking these are NOPs unless :sb-package-locks is
277 ;;;; in target features. Cross-compiler NOPs for these are in cross-misc.
279 ;;; The right way to establish a package lock context is
280 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR, defined in early-package.lisp
282 ;;; Must be used inside the dynamic contour established by
283 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR
284 (defun assert-package-unlocked (package &optional format-control
285 &rest format-arguments)
286 #!-sb-package-locks
287 (declare (ignore format-control format-arguments))
288 #!+sb-package-locks
289 (when (package-lock-violation-p package)
290 (package-lock-violation package
291 :format-control format-control
292 :format-arguments format-arguments))
293 package)
295 ;;; Must be used inside the dynamic contour established by
296 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR.
298 ;;; FIXME: Maybe we should establish such contours for he toplevel
299 ;;; and others, so that %set-fdefinition and others could just use
300 ;;; this.
301 (defun assert-symbol-home-package-unlocked (name &optional format-control
302 &rest format-arguments)
303 #!-sb-package-locks
304 (declare (ignore format-control format-arguments))
305 #!+sb-package-locks
306 (let* ((symbol (etypecase name
307 (symbol name)
308 ;; Istm that the right way to declare that you want to allow
309 ;; overriding the lock on (SETF X) is to list (SETF X) in
310 ;; the declaration, not expect that X means itself and SETF.
311 ;; Worse still, the syntax ({ENABLE|DISABLE}-..-locks (SETF X))
312 ;; is broken, and yet we make no indication of it.
313 ((cons (eql setf) cons) (second name))
314 ;; Skip lists of length 1, single conses and
315 ;; (class-predicate foo), etc. FIXME: MOP and
316 ;; package-lock interaction needs to be thought
317 ;; about.
318 (list
319 (return-from assert-symbol-home-package-unlocked
320 name))))
321 (package (symbol-package symbol)))
322 (when (package-lock-violation-p package symbol)
323 (package-lock-violation package
324 :symbol symbol
325 :format-control format-control
326 :format-arguments (cons name format-arguments))))
327 name)
330 ;;;; miscellaneous PACKAGE operations
332 (defmethod print-object ((package package) stream)
333 (let ((name (package-%name package)))
334 (print-unreadable-object (package stream :type t :identity (not name))
335 (if name (prin1 name stream) (write-string "(deleted)" stream)))))
337 ;;; ANSI says (in the definition of DELETE-PACKAGE) that these, and
338 ;;; most other operations, are unspecified for deleted packages. We
339 ;;; just do the easy thing and signal errors in that case.
340 (macrolet ((def (ext real)
341 `(defun ,ext (package-designator)
342 (,real (find-undeleted-package-or-lose package-designator)))))
343 (def package-nicknames package-%nicknames)
344 (def package-use-list package-%use-list)
345 (def package-used-by-list package-%used-by-list)
346 (def package-shadowing-symbols package-%shadowing-symbols))
348 (defun package-local-nicknames (package-designator)
349 #!+sb-doc
350 "Returns an alist of \(local-nickname . actual-package) describing the
351 nicknames local to the designated package.
353 When in the designated package, calls to FIND-PACKAGE with the any of the
354 local-nicknames will return the corresponding actual-package instead. This
355 also affects all implied calls to FIND-PACKAGE, including those performed by
356 the reader.
358 When printing a package prefix for a symbol with a package local nickname, the
359 local nickname is used instead of the real name in order to preserve
360 print-read consistency.
362 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
363 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
365 Experimental: interface subject to change."
366 (copy-tree
367 (package-%local-nicknames
368 (find-undeleted-package-or-lose package-designator))))
370 (defun signal-package-error (package format-control &rest format-args)
371 (error 'simple-package-error
372 :package package
373 :format-control format-control
374 :format-arguments format-args))
376 (defun signal-package-cerror (package continue-string
377 format-control &rest format-args)
378 (cerror continue-string
379 'simple-package-error
380 :package package
381 :format-control format-control
382 :format-arguments format-args))
384 (defun package-locally-nicknamed-by-list (package-designator)
385 #!+sb-doc
386 "Returns a list of packages which have a local nickname for the designated
387 package.
389 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
390 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
392 Experimental: interface subject to change."
393 (copy-list
394 (package-%locally-nicknamed-by
395 (find-undeleted-package-or-lose package-designator))))
397 (defun add-package-local-nickname (local-nickname actual-package
398 &optional (package-designator (sane-package)))
399 #!+sb-doc
400 "Adds LOCAL-NICKNAME for ACTUAL-PACKAGE in the designated package, defaulting
401 to current package. LOCAL-NICKNAME must be a string designator, and
402 ACTUAL-PACKAGE must be a package designator.
404 Returns the designated package.
406 Signals a continuable error if LOCAL-NICKNAME is already a package local
407 nickname for a different package, or if LOCAL-NICKNAME is one of \"CL\",
408 \"COMMON-LISP\", or, \"KEYWORD\", or if LOCAL-NICKNAME is a global name or
409 nickname for the package to which the nickname would be added.
411 When in the designated package, calls to FIND-PACKAGE with the LOCAL-NICKNAME
412 will return the package the designated ACTUAL-PACKAGE instead. This also
413 affects all implied calls to FIND-PACKAGE, including those performed by the
414 reader.
416 When printing a package prefix for a symbol with a package local nickname,
417 local nickname is used instead of the real name in order to preserve
418 print-read consistency.
420 See also: PACKAGE-LOCAL-NICKNAMES, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
421 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
423 Experimental: interface subject to change."
424 (let* ((nick (string local-nickname))
425 (actual (find-package-using-package actual-package nil))
426 (package (find-undeleted-package-or-lose package-designator))
427 (existing (package-%local-nicknames package))
428 (cell (assoc nick existing :test #'string=)))
429 (unless actual
430 (signal-package-error
431 package-designator
432 "The name ~S does not designate any package."
433 actual-package))
434 (unless (package-name actual)
435 (signal-package-error
436 actual
437 "Cannot add ~A as local nickname for a deleted package: ~S"
438 nick actual))
439 (with-single-package-locked-error
440 (:package package "adding ~A as a local nickname for ~A"
441 nick actual))
442 (when (member nick '("CL" "COMMON-LISP" "KEYWORD") :test #'string=)
443 (signal-package-cerror
444 actual
445 "Continue, use it as local nickname anyways."
446 "Attempt to use ~A as a package local nickname (for ~A)."
447 nick (package-name actual)))
448 (when (string= nick (package-name package))
449 (signal-package-cerror
450 package
451 "Continue, use it as a local nickname anyways."
452 "Attempt to use ~A as a package local nickname (for ~A) in ~
453 package named globally ~A."
454 nick (package-name actual) nick))
455 (when (member nick (package-nicknames package) :test #'string=)
456 (signal-package-cerror
457 package
458 "Continue, use it as a local nickname anyways."
459 "Attempt to use ~A as a package local nickname (for ~A) in ~
460 package nicknamed globally ~A."
461 nick (package-name actual) nick))
462 (when (and cell (neq actual (cdr cell)))
463 (restart-case
464 (signal-package-error
465 actual
466 "~@<Cannot add ~A as local nickname for ~A in ~A: ~
467 already nickname for ~A.~:@>"
468 nick (package-name actual)
469 (package-name package) (package-name (cdr cell)))
470 (keep-old ()
471 :report (lambda (s)
472 (format s "Keep ~A as local nicname for ~A."
473 nick (package-name (cdr cell)))))
474 (change-nick ()
475 :report (lambda (s)
476 (format s "Use ~A as local nickname for ~A instead."
477 nick (package-name actual)))
478 (let ((old (cdr cell)))
479 (with-package-graph ()
480 (setf (package-%locally-nicknamed-by old)
481 (delete package (package-%locally-nicknamed-by old)))
482 (push package (package-%locally-nicknamed-by actual))
483 (setf (cdr cell) actual)))))
484 (return-from add-package-local-nickname package))
485 (unless cell
486 (with-package-graph ()
487 (push (cons nick actual) (package-%local-nicknames package))
488 (push package (package-%locally-nicknamed-by actual))))
489 package))
491 (defun remove-package-local-nickname (old-nickname
492 &optional (package-designator (sane-package)))
493 #!+sb-doc
494 "If the designated package had OLD-NICKNAME as a local nickname for
495 another package, it is removed. Returns true if the nickname existed and was
496 removed, and NIL otherwise.
498 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
499 PACKAGE-LOCALLY-NICKNAMED-BY-LIST, and the DEFPACKAGE option :LOCAL-NICKNAMES.
501 Experimental: interface subject to change."
502 (let* ((nick (string old-nickname))
503 (package (find-undeleted-package-or-lose package-designator))
504 (existing (package-%local-nicknames package))
505 (cell (assoc nick existing :test #'string=)))
506 (when cell
507 (with-single-package-locked-error
508 (:package package "removing local nickname ~A for ~A"
509 nick (cdr cell)))
510 (with-package-graph ()
511 (let ((old (cdr cell)))
512 (setf (package-%local-nicknames package) (delete cell existing))
513 (setf (package-%locally-nicknamed-by old)
514 (delete package (package-%locally-nicknamed-by old)))))
515 t)))
517 (defun %package-hashtable-symbol-count (table)
518 (let ((size (the fixnum
519 (- (package-hashtable-size table)
520 (package-hashtable-deleted table)))))
521 (the fixnum
522 (- size (package-hashtable-free table)))))
524 (defun package-internal-symbol-count (package)
525 (%package-hashtable-symbol-count (package-internal-symbols package)))
527 (defun package-external-symbol-count (package)
528 (%package-hashtable-symbol-count (package-external-symbols package)))
530 (defvar *package* (error "*PACKAGE* should be initialized in cold load!")
531 #!+sb-doc "the current package")
533 (define-condition bootstrap-package-not-found (condition)
534 ((name :initarg :name :reader bootstrap-package-name)))
535 (defun debootstrap-package (&optional condition)
536 (invoke-restart
537 (find-restart-or-control-error 'debootstrap-package condition)))
539 (defun find-package (package-designator)
540 #!+sb-doc
541 "If PACKAGE-DESIGNATOR is a package, it is returned. Otherwise PACKAGE-DESIGNATOR
542 must be a string designator, in which case the package it names is located and returned.
544 As an SBCL extension, the current package may affect the way a package name is
545 resolved: if the current package has local nicknames specified, package names
546 matching those are resolved to the packages associated with them instead.
548 Example:
550 (defpackage :a)
551 (defpackage :example (:use :cl) (:local-nicknames (:x :a)))
552 (let ((*package* (find-package :example)))
553 (find-package :x)) => #<PACKAGE A>
555 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
556 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES."
557 (find-package-using-package package-designator
558 (when (boundp '*package*)
559 *package*)))
561 ;;; This is undocumented and unexported for now, but the idea is that by
562 ;;; making this a generic function then packages with custom package classes
563 ;;; could hook into this to provide their own resolution.
564 (defun find-package-using-package (package-designator base)
565 (flet ((find-package-from-string (string)
566 (declare (type string string))
567 (let* ((nicknames (when base
568 (package-%local-nicknames base)))
569 (nicknamed (when nicknames
570 (cdr (assoc string nicknames :test #'string=))))
571 (packageoid (or nicknamed (gethash string *package-names*))))
572 (if (and (null packageoid)
573 ;; FIXME: should never need 'debootstrap' hack
574 (let ((mismatch (mismatch "SB!" string)))
575 (and mismatch (= mismatch 3))))
576 (restart-case
577 (signal 'bootstrap-package-not-found :name string)
578 (debootstrap-package ()
579 (if (string= string "SB!XC")
580 (find-package "COMMON-LISP")
581 (find-package
582 (substitute #\- #\! string :count 1)))))
583 packageoid))))
584 (typecase package-designator
585 (package package-designator)
586 (symbol (find-package-from-string (symbol-name package-designator)))
587 (string (find-package-from-string package-designator))
588 (character (find-package-from-string (string package-designator)))
589 (t (error 'type-error
590 :datum package-designator
591 :expected-type '(or character package string symbol))))))
593 ;;; Return a list of packages given a package designator or list of
594 ;;; package designators, or die trying.
595 (defun package-listify (thing)
596 (if (listp thing)
597 (mapcar #'find-undeleted-package-or-lose thing)
598 (list (find-undeleted-package-or-lose thing))))
600 ;;; ANSI specifies (in the definition of DELETE-PACKAGE) that PACKAGE-NAME
601 ;;; returns NIL (not an error) for a deleted package, so this is a special
602 ;;; case where we want to use bare %FIND-PACKAGE-OR-LOSE instead of
603 ;;; FIND-UNDELETED-PACKAGE-OR-LOSE.
604 (defun package-name (package-designator)
605 (package-%name (%find-package-or-lose package-designator)))
607 ;;;; operations on package hashtables
609 ;;; Compute a number between 1 and 255 based on the sxhash of the
610 ;;; pname and the length thereof.
611 (declaim (inline entry-hash))
612 (defun entry-hash (length sxhash)
613 (declare (index length) ((and fixnum unsigned-byte) sxhash))
614 (1+ (rem (logxor length sxhash
615 (ash sxhash -8) (ash sxhash -16) (ash sxhash -19))
616 255)))
618 ;;; Add a symbol to a package hashtable. The symbol is assumed
619 ;;; not to be present.
620 (defun add-symbol (table symbol)
621 (when (zerop (package-hashtable-free table))
622 ;; The hashtable is full. Resize it to be able to hold twice the
623 ;; amount of symbols than it currently contains. The actual new size
624 ;; can be smaller than twice the current size if the table contained
625 ;; deleted entries.
626 (resize-package-hashtable table
627 (* (- (package-hashtable-size table)
628 (package-hashtable-deleted table))
629 2)))
630 (let* ((symvec (package-hashtable-cells table))
631 (len (1- (length symvec)))
632 (hashvec (the hash-vector (aref symvec len)))
633 (sxhash (truly-the fixnum (ensure-symbol-hash symbol)))
634 (h2 (1+ (rem sxhash (- len 2)))))
635 (declare (fixnum sxhash h2))
636 (do ((i (rem sxhash len) (rem (+ i h2) len)))
637 ((eql (aref hashvec i) 0)
638 (if (eql (svref symvec i) 0)
639 (decf (package-hashtable-free table))
640 (decf (package-hashtable-deleted table)))
641 ;; This order of these two SETFs does not matter.
642 ;; An empty symbol cell is skipped on lookup if the hash cell
643 ;; matches something accidentally. "empty" = any fixnum.
644 (setf (svref symvec i) symbol)
645 (setf (aref hashvec i)
646 (entry-hash (length (symbol-name symbol)) sxhash)))
647 (declare (fixnum i)))))
649 ;;; Resize the package hashtables of all packages so that their load
650 ;;; factor is *PACKAGE-HASHTABLE-IMAGE-LOAD-FACTOR*. Called from
651 ;;; SAVE-LISP-AND-DIE to optimize space usage in the image.
652 (defun tune-hashtable-sizes-of-all-packages ()
653 (flet ((tune-table-size (table)
654 (resize-package-hashtable
655 table
656 (round (* (/ *package-rehash-threshold*
657 *package-hashtable-image-load-factor*)
658 (- (package-hashtable-size table)
659 (package-hashtable-free table)
660 (package-hashtable-deleted table)))))))
661 (dolist (package (list-all-packages))
662 (tune-table-size (package-internal-symbols package))
663 (tune-table-size (package-external-symbols package)))))
665 ;;; Find where the symbol named STRING is stored in TABLE. INDEX-VAR
666 ;;; is bound to the index, or NIL if it is not present. SYMBOL-VAR
667 ;;; is bound to the symbol. LENGTH and HASH are the length and sxhash
668 ;;; of STRING. ENTRY-HASH is the entry-hash of the string and length.
669 ;;; If the symbol is found, then FORMS are executed; otherwise not.
671 (defmacro with-symbol (((symbol-var &optional (index-var (gensym))) table
672 string length sxhash entry-hash) &body forms)
673 (with-unique-names (vec len hash-vec h2 probed-ehash name)
674 `(let* ((,vec (package-hashtable-cells ,table))
675 (,len (1- (length ,vec)))
676 (,hash-vec (the hash-vector (svref ,vec ,len)))
677 (,index-var (rem (the hash ,sxhash) ,len))
678 (,h2 (1+ (the index (rem (the hash ,sxhash)
679 (the index (- ,len 2)))))))
680 (declare (type index ,len ,h2 ,index-var))
681 (loop
682 (let ((,probed-ehash (aref ,hash-vec ,index-var)))
683 (cond
684 ((eql ,probed-ehash ,entry-hash)
685 (let ((,symbol-var (truly-the symbol (svref ,vec ,index-var))))
686 (when (eq (symbol-hash ,symbol-var) ,sxhash)
687 (let ((,name (symbol-name ,symbol-var)))
688 ;; The pre-test for length is kind of an unimportant
689 ;; optimization, but passing it for both :end arguments
690 ;; requires that it be within bounds for the probed symbol.
691 (when (and (= (length ,name) ,length)
692 (string= ,string ,name
693 :end1 ,length :end2 ,length))
694 (return (progn ,@forms)))))))
695 ((eql ,probed-ehash 0)
696 ;; either a never used cell or a tombstone left by UNINTERN
697 (when (eql (svref ,vec ,index-var) 0) ; really never used
698 (return)))))
699 (when (>= (incf ,index-var ,h2) ,len)
700 (decf ,index-var ,len))))))
702 ;;; Delete the entry for STRING in TABLE. The entry must exist.
703 ;;; Deletion stores -1 for the symbol and 0 for the hash tombstone.
704 ;;; Storing NIL for the symbol, as used to be done, is vulnerable to a rare
705 ;;; concurrency bug because many strings have the same ENTRY-HASH as NIL:
706 ;;; (entry-hash 3 (sxhash "NIL")) => 177 and
707 ;;; (entry-hash 2 (sxhash "3M")) => 177
708 ;;; Suppose, in the former approach, that "3M" is interned,
709 ;;; and then the following sequence of events occur:
710 ;;; - thread 1 performs FIND-SYMBOL on "NIL", hits the hash code at
711 ;;; at index I, and is then context-switched out. When this thread
712 ;; resumes, it assumes a valid symbol in (SVREF SYM-VEC I)
713 ;;; - thread 2 uninterns "3M" and fully completes that, storing NIL
714 ;;; in the slot for the symbol that thread 1 will next read.
715 ;;; - thread 1 continues, and test for STRING= to NIL,
716 ;;; wrongly seeing NIL as a present symbol.
717 ;;; It's possible this is harmless, because NIL is usually inherited from CL,
718 ;;; but if the secondary return value mattered to the application,
719 ;;; it is probably wrong. And of course if NIL was not intended to be found
720 ;;; - as in a package that does not use CL - then finding NIL at all is wrong.
721 ;;; The better approach is to treat 'hash' as purely a heuristic without
722 ;;; ill-effect from false positives. No barrier, nor read-consistency
723 ;;; check is required, since a symbol is both its key and value,
724 ;;; and the "absence of a symbol" marker is never mistaken for a symbol.
726 (defun nuke-symbol (table symbol)
727 (let* ((string (symbol-name symbol))
728 (length (length string))
729 (hash (symbol-hash symbol))
730 (ehash (entry-hash length hash)))
731 (declare (type index length)
732 (type hash hash))
733 (with-symbol ((symbol index) table string length hash ehash)
734 ;; It is suboptimal to grab the vectors again, but not broken,
735 ;; because we have exclusive use of the table for writing.
736 (let* ((symvec (package-hashtable-cells table))
737 (hashvec (the hash-vector (aref symvec (1- (length symvec))))))
738 (setf (aref hashvec index) 0)
739 (setf (aref symvec index) -1)) ; any nonzero fixnum will do
740 (incf (package-hashtable-deleted table))))
741 ;; If the table is less than one quarter full, halve its size and
742 ;; rehash the entries.
743 (let* ((size (package-hashtable-size table))
744 (deleted (package-hashtable-deleted table))
745 (used (- size
746 (package-hashtable-free table)
747 deleted)))
748 (declare (type fixnum size deleted used))
749 (when (< used (truncate size 4))
750 (resize-package-hashtable table (* used 2)))))
752 ;;; Enter any new NICKNAMES for PACKAGE into *PACKAGE-NAMES*. If there is a
753 ;;; conflict then give the user a chance to do something about it. Caller is
754 ;;; responsible for having acquired the mutex via WITH-PACKAGES.
755 (defun %enter-new-nicknames (package nicknames)
756 (declare (type list nicknames))
757 (dolist (n nicknames)
758 (let* ((n (stringify-package-designator n))
759 (found (with-package-names (names)
760 (or (gethash n names)
761 (progn
762 (setf (gethash n names) package)
763 (push n (package-%nicknames package))
764 package)))))
765 (cond ((eq found package))
766 ((string= (the string (package-%name found)) n)
767 (signal-package-cerror
768 package
769 "Ignore this nickname."
770 "~S is a package name, so it cannot be a nickname for ~S."
771 n (package-%name package)))
773 (signal-package-cerror
774 package
775 "Leave this nickname alone."
776 "~S is already a nickname for ~S."
777 n (package-%name found)))))))
779 (defun make-package (name &key
780 (use '#.*default-package-use-list*)
781 nicknames
782 (internal-symbols 10)
783 (external-symbols 10))
784 #!+sb-doc
785 #.(format nil
786 "Make a new package having the specified NAME, NICKNAMES, and USE
787 list. :INTERNAL-SYMBOLS and :EXTERNAL-SYMBOLS are estimates for the number of
788 internal and external symbols which will ultimately be present in the package.
789 The default value of USE is implementation-dependent, and in this
790 implementation it is ~S." *default-package-use-list*)
791 (prog (clobber)
792 :restart
793 (when (find-package name)
794 ;; ANSI specifies that this error is correctable.
795 (signal-package-cerror
796 name
797 "Clobber existing package."
798 "A package named ~S already exists" name)
799 (setf clobber t))
800 (with-package-graph ()
801 ;; Check for race, signal the error outside the lock.
802 (when (and (not clobber) (find-package name))
803 (go :restart))
804 (let* ((name (stringify-package-designator name))
805 (package
806 (%make-package
807 name
808 (make-package-hashtable internal-symbols)
809 (make-package-hashtable external-symbols))))
811 ;; Do a USE-PACKAGE for each thing in the USE list so that checking for
812 ;; conflicting exports among used packages is done.
813 (use-package use package)
815 ;; FIXME: ENTER-NEW-NICKNAMES can fail (ERROR) if nicknames are illegal,
816 ;; which would leave us with possibly-bad side effects from the earlier
817 ;; USE-PACKAGE (e.g. this package on the used-by lists of other packages,
818 ;; but not in *PACKAGE-NAMES*, and possibly import side effects too?).
819 ;; Perhaps this can be solved by just moving ENTER-NEW-NICKNAMES before
820 ;; USE-PACKAGE, but I need to check what kinds of errors can be caused by
821 ;; USE-PACKAGE, too.
822 (%enter-new-nicknames package nicknames)
823 (return (setf (gethash name *package-names*) package))))
824 (bug "never")))
826 ;;; Change the name if we can, blast any old nicknames and then
827 ;;; add in any new ones.
829 ;;; FIXME: ANSI claims that NAME is a package designator (not just a
830 ;;; string designator -- weird). Thus, NAME could
831 ;;; be a package instead of a string. Presumably then we should not change
832 ;;; the package name if NAME is the same package that's referred to by PACKAGE.
833 ;;; If it's a *different* package, we should probably signal an error.
834 ;;; (perhaps (ERROR 'ANSI-WEIRDNESS ..):-)
835 (defun rename-package (package-designator name &optional (nicknames ()))
836 #!+sb-doc
837 "Changes the name and nicknames for a package."
838 (prog () :restart
839 (let ((package (find-undeleted-package-or-lose package-designator))
840 (name (stringify-package-designator name))
841 (found (find-package name))
842 (nicks (mapcar #'string nicknames)))
843 (unless (or (not found) (eq found package))
844 (signal-package-error name
845 "A package named ~S already exists." name))
846 (with-single-package-locked-error ()
847 (unless (and (string= name (package-name package))
848 (null (set-difference nicks (package-nicknames package)
849 :test #'string=)))
850 (assert-package-unlocked
851 package "renaming as ~A~@[ with nickname~*~P ~1@*~{~A~^, ~}~]"
852 name nicks (length nicks)))
853 (with-package-names (names)
854 ;; Check for race conditions now that we have the lock.
855 (unless (eq package (find-package package-designator))
856 (go :restart))
857 ;; Do the renaming.
858 (remhash (package-%name package) names)
859 (dolist (n (package-%nicknames package))
860 (remhash n names))
861 (setf (package-%name package) name
862 (gethash name names) package
863 (package-%nicknames package) ()))
864 (%enter-new-nicknames package nicknames))
865 (return package))))
867 (defun delete-package (package-designator)
868 #!+sb-doc
869 "Delete the package designated by PACKAGE-DESIGNATOR from the package
870 system data structures."
871 (tagbody :restart
872 (let ((package (find-package package-designator)))
873 (cond ((not package)
874 ;; This continuable error is required by ANSI.
875 (signal-package-cerror
876 package-designator
877 "Ignore."
878 "There is no package named ~S." package-designator)
879 (return-from delete-package nil))
880 ((not (package-name package)) ; already deleted
881 (return-from delete-package nil))
883 (with-single-package-locked-error
884 (:package package "deleting package ~A" package)
885 (let ((use-list (package-used-by-list package)))
886 (when use-list
887 ;; This continuable error is specified by ANSI.
888 (signal-package-cerror
889 package
890 "Remove dependency in other packages."
891 "~@<Package ~S is used by package~P:~2I~_~S~@:>"
892 (package-name package)
893 (length use-list)
894 (mapcar #'package-name use-list))
895 (dolist (p use-list)
896 (unuse-package package p))))
897 #!+sb-package-locks
898 (dolist (p (package-implements-list package))
899 (remove-implementation-package package p))
900 (with-package-graph ()
901 ;; Check for races, restart if necessary.
902 (let ((package2 (find-package package-designator)))
903 (when (or (neq package package2) (package-used-by-list package2))
904 (go :restart)))
905 (dolist (used (package-use-list package))
906 (unuse-package used package))
907 (dolist (namer (package-%locally-nicknamed-by package))
908 (setf (package-%local-nicknames namer)
909 (delete package (package-%local-nicknames namer) :key #'cdr)))
910 (setf (package-%locally-nicknamed-by package) nil)
911 (dolist (cell (package-%local-nicknames package))
912 (let ((actual (cdr cell)))
913 (setf (package-%locally-nicknamed-by actual)
914 (delete package (package-%locally-nicknamed-by actual)))))
915 (setf (package-%local-nicknames package) nil)
916 ;; FIXME: lacking a way to advise UNINTERN that this package
917 ;; is pending deletion, a large package conses successively
918 ;; many smaller tables for no good reason.
919 (do-symbols (sym package)
920 (unintern sym package))
921 (with-package-names (names)
922 (remhash (package-name package) names)
923 (dolist (nick (package-nicknames package))
924 (remhash nick names))
925 (setf (package-%name package) nil
926 ;; Setting PACKAGE-%NAME to NIL is required in order to
927 ;; make PACKAGE-NAME return NIL for a deleted package as
928 ;; ANSI requires. Setting the other slots to NIL
929 ;; and blowing away the PACKAGE-HASHTABLES is just done
930 ;; for tidiness and to help the GC.
931 (package-%nicknames package) nil))
932 (setf (package-%use-list package) nil
933 (package-tables package) #()
934 (package-%shadowing-symbols package) nil
935 (package-internal-symbols package)
936 (make-package-hashtable 0)
937 (package-external-symbols package)
938 (make-package-hashtable 0)))
939 (return-from delete-package t)))))))
941 (defun list-all-packages ()
942 #!+sb-doc
943 "Return a list of all existing packages."
944 (let ((res ()))
945 (with-package-names (names)
946 (maphash (lambda (k v)
947 (declare (ignore k))
948 (pushnew v res :test #'eq))
949 names))
950 res))
952 (macrolet ((find/intern (function &rest more-args)
953 ;; Both %FIND-SYMBOL and %INTERN require a SIMPLE-STRING,
954 ;; but accept a LENGTH. Given a non-simple string,
955 ;; we need copy it only if the cumulative displacement
956 ;; into the underlying simple-string is nonzero.
957 ;; There are two things that can be improved
958 ;; about the generated code here:
959 ;; 1. if X is known to satisfy STRINGP (generally any rank-1 array),
960 ;; then testing SIMPLE-<base|character>-STRING-P should not
961 ;; re-test the lowtag. This is constrained by the backends,
962 ;; because there are no type vops that assume a known lowtag.
963 ;; 2. if X is known to satisfy VECTORP, then
964 ;; (NOT (ARRAY-HEADER-P)) implies SIMPLE-P, but the compiler
965 ;; does not actually know that, and generates a check.
966 ;; This is more of a front-end issue.
967 `(multiple-value-bind (name length)
968 (if (simple-string-p name)
969 (values name (length name))
970 (with-array-data ((name name) (start) (end)
971 :check-fill-pointer t)
972 (if (eql start 0)
973 (values name end)
974 (values (subseq name start end)
975 (- end start)))))
976 (truly-the
977 (values symbol (member :internal :external :inherited nil))
978 (,function name length
979 (find-undeleted-package-or-lose package)
980 ,@more-args)))))
982 (defun intern (name &optional (package (sane-package)))
983 #!+sb-doc
984 "Return a symbol in PACKAGE having the specified NAME, creating it
985 if necessary."
986 (find/intern %intern t))
988 (defun find-symbol (name &optional (package (sane-package)))
989 #!+sb-doc
990 "Return the symbol named STRING in PACKAGE. If such a symbol is found
991 then the second value is :INTERNAL, :EXTERNAL or :INHERITED to indicate
992 how the symbol is accessible. If no symbol is found then both values
993 are NIL."
994 (find/intern %find-symbol)))
996 ;;; If the symbol named by the first LENGTH characters of NAME doesn't exist,
997 ;;; then create it, special-casing the keyword package.
998 (defun %intern (name length package copy-p)
999 (declare (simple-string name) (index length))
1000 (multiple-value-bind (symbol where) (%find-symbol name length package)
1001 (cond (where
1002 (values symbol where))
1004 ;; Let's try again with a lock: the common case has the
1005 ;; symbol already interned, handled by the first leg of the
1006 ;; COND, but in case another thread is interning in
1007 ;; parallel we need to check after grabbing the lock.
1008 (with-package-graph ()
1009 (setf (values symbol where) (%find-symbol name length package))
1010 (if where
1011 (values symbol where)
1012 (let ((symbol-name (cond ((not copy-p)
1013 (aver (= (length name) length))
1014 name)
1015 ((typep name '(simple-array nil (*)))
1018 ;; This so that SUBSEQ is inlined,
1019 ;; because we need it fixed for cold init.
1020 (string-dispatch
1021 ((simple-array base-char (*))
1022 (simple-array character (*)))
1023 name
1024 (declare (optimize speed))
1025 (subseq name 0 length))))))
1026 (with-single-package-locked-error
1027 (:package package "interning ~A" symbol-name)
1028 (let ((symbol (make-symbol symbol-name)))
1029 (add-symbol (cond ((eq package *keyword-package*)
1030 (%set-symbol-value symbol symbol)
1031 (package-external-symbols package))
1033 (package-internal-symbols package)))
1034 symbol)
1035 (%set-symbol-package symbol package)
1036 (values symbol nil))))))))))
1038 ;;; Check internal and external symbols, then scan down the list
1039 ;;; of hashtables for inherited symbols.
1040 (defun %find-symbol (string length package)
1041 (declare (simple-string string)
1042 (type index length))
1043 (let* ((hash (compute-symbol-hash string length))
1044 (ehash (entry-hash length hash)))
1045 (declare (type hash hash ehash))
1046 (with-symbol ((symbol) (package-internal-symbols package)
1047 string length hash ehash)
1048 (return-from %find-symbol (values symbol :internal)))
1049 (with-symbol ((symbol) (package-external-symbols package)
1050 string length hash ehash)
1051 (return-from %find-symbol (values symbol :external)))
1052 (let* ((tables (package-tables package))
1053 (n (length tables)))
1054 (unless (eql n 0)
1055 ;; Try the most-recently-used table, then others.
1056 ;; TABLES is treated as circular for this purpose.
1057 (let* ((mru (package-mru-table-index package))
1058 (start (if (< mru n) mru 0))
1059 (i start))
1060 (loop
1061 (with-symbol ((symbol) (locally (declare (optimize (safety 0)))
1062 (svref tables i))
1063 string length hash ehash)
1064 (setf (package-mru-table-index package) i)
1065 (return-from %find-symbol (values symbol :inherited)))
1066 (if (< (decf i) 0) (setq i (1- n)))
1067 (if (= i start) (return)))))))
1068 (values nil nil))
1070 ;;; Similar to FIND-SYMBOL, but only looks for an external symbol.
1071 ;;; Return the symbol and T if found, otherwise two NILs.
1072 ;;; This is used for fast name-conflict checking in this file and symbol
1073 ;;; printing in the printer.
1074 ;;; An optimization is possible here: by accepting either a string or symbol,
1075 ;;; if the symbol's hash slot is nonzero, we can avoid COMPUTE-SYMBOL-HASH.
1076 (defun find-external-symbol (string package)
1077 (declare (simple-string string))
1078 (let* ((length (length string))
1079 (hash (compute-symbol-hash string length))
1080 (ehash (entry-hash length hash)))
1081 (declare (type index length)
1082 (type hash hash))
1083 (with-symbol ((symbol) (package-external-symbols package)
1084 string length hash ehash)
1085 (return-from find-external-symbol (values symbol t))))
1086 (values nil nil))
1088 (define-condition name-conflict (reference-condition package-error)
1089 ((function :initarg :function :reader name-conflict-function)
1090 (datum :initarg :datum :reader name-conflict-datum)
1091 (symbols :initarg :symbols :reader name-conflict-symbols))
1092 (:default-initargs :references (list '(:ansi-cl :section (11 1 1 2 5))))
1093 (:report
1094 (lambda (c s)
1095 (format s "~@<~S ~S causes name-conflicts in ~S between the ~
1096 following symbols:~2I~@:_~
1097 ~{~/sb-impl::print-symbol-with-prefix/~^, ~}~:@>"
1098 (name-conflict-function c)
1099 (name-conflict-datum c)
1100 (package-error-package c)
1101 (name-conflict-symbols c)))))
1103 (defun name-conflict (package function datum &rest symbols)
1104 (flet ((importp (c)
1105 (declare (ignore c))
1106 (eq 'import function))
1107 (use-or-export-p (c)
1108 (declare (ignore c))
1109 (or (eq 'use-package function)
1110 (eq 'export function)))
1111 (old-symbol ()
1112 (car (remove datum symbols))))
1113 (let ((pname (package-name package)))
1114 (restart-case
1115 (error 'name-conflict :package package :symbols symbols
1116 :function function :datum datum)
1117 ;; USE-PACKAGE and EXPORT
1118 (keep-old ()
1119 :report (lambda (s)
1120 (ecase function
1121 (export
1122 (format s "Keep ~S accessible in ~A (shadowing ~S)."
1123 (old-symbol) pname datum))
1124 (use-package
1125 (format s "Keep symbols already accessible ~A (shadowing others)."
1126 pname))))
1127 :test use-or-export-p
1128 (dolist (s (remove-duplicates symbols :test #'string=))
1129 (shadow (symbol-name s) package)))
1130 (take-new ()
1131 :report (lambda (s)
1132 (ecase function
1133 (export
1134 (format s "Make ~S accessible in ~A (uninterning ~S)."
1135 datum pname (old-symbol)))
1136 (use-package
1137 (format s "Make newly exposed symbols accessible in ~A, ~
1138 uninterning old ones."
1139 pname))))
1140 :test use-or-export-p
1141 (dolist (s symbols)
1142 (when (eq s (find-symbol (symbol-name s) package))
1143 (unintern s package))))
1144 ;; IMPORT
1145 (shadowing-import-it ()
1146 :report (lambda (s)
1147 (format s "Shadowing-import ~S, uninterning ~S."
1148 datum (old-symbol)))
1149 :test importp
1150 (shadowing-import datum package))
1151 (dont-import-it ()
1152 :report (lambda (s)
1153 (format s "Don't import ~S, keeping ~S."
1154 datum
1155 (car (remove datum symbols))))
1156 :test importp)
1157 ;; General case. This is exposed via SB-EXT.
1158 (resolve-conflict (chosen-symbol)
1159 :report "Resolve conflict."
1160 :interactive
1161 (lambda ()
1162 (let* ((len (length symbols))
1163 (nlen (length (write-to-string len :base 10)))
1164 (*print-pretty* t))
1165 (format *query-io* "~&~@<Select a symbol to be made accessible in ~
1166 package ~A:~2I~@:_~{~{~V,' D. ~
1167 ~/sb-impl::print-symbol-with-prefix/~}~@:_~}~
1168 ~@:>"
1169 (package-name package)
1170 (loop for s in symbols
1171 for i upfrom 1
1172 collect (list nlen i s)))
1173 (loop
1174 (format *query-io* "~&Enter an integer (between 1 and ~D): " len)
1175 (finish-output *query-io*)
1176 (let ((i (parse-integer (read-line *query-io*) :junk-allowed t)))
1177 (when (and i (<= 1 i len))
1178 (return (list (nth (1- i) symbols))))))))
1179 (multiple-value-bind (package-symbol status)
1180 (find-symbol (symbol-name chosen-symbol) package)
1181 (let* ((accessiblep status) ; never NIL here
1182 (presentp (and accessiblep
1183 (not (eq :inherited status)))))
1184 (ecase function
1185 ((unintern)
1186 (if presentp
1187 (if (eq package-symbol chosen-symbol)
1188 (shadow (list package-symbol) package)
1189 (shadowing-import (list chosen-symbol) package))
1190 (shadowing-import (list chosen-symbol) package)))
1191 ((use-package export)
1192 (if presentp
1193 (if (eq package-symbol chosen-symbol)
1194 (shadow (list package-symbol) package) ; CLHS 11.1.1.2.5
1195 (if (eq (symbol-package package-symbol) package)
1196 (unintern package-symbol package) ; CLHS 11.1.1.2.5
1197 (shadowing-import (list chosen-symbol) package)))
1198 (shadowing-import (list chosen-symbol) package)))
1199 ((import)
1200 (if presentp
1201 (if (eq package-symbol chosen-symbol)
1202 nil ; re-importing the same symbol
1203 (shadowing-import (list chosen-symbol) package))
1204 (shadowing-import (list chosen-symbol) package)))))))))))
1206 ;;; If we are uninterning a shadowing symbol, then a name conflict can
1207 ;;; result, otherwise just nuke the symbol.
1208 (defun unintern (symbol &optional (package (sane-package)))
1209 #!+sb-doc
1210 "Makes SYMBOL no longer present in PACKAGE. If SYMBOL was present then T is
1211 returned, otherwise NIL. If PACKAGE is SYMBOL's home package, then it is made
1212 uninterned."
1213 (with-package-graph ()
1214 (let* ((package (find-undeleted-package-or-lose package))
1215 (name (symbol-name symbol))
1216 (shadowing-symbols (package-%shadowing-symbols package)))
1217 (declare (list shadowing-symbols))
1219 (with-single-package-locked-error ()
1220 (when (find-symbol name package)
1221 (assert-package-unlocked package "uninterning ~A" name))
1223 ;; If a name conflict is revealed, give us a chance to
1224 ;; shadowing-import one of the accessible symbols.
1225 (when (member symbol shadowing-symbols)
1226 (let ((cset ()))
1227 (dolist (p (package-%use-list package))
1228 (multiple-value-bind (s w) (find-external-symbol name p)
1229 ;; S should be derived as SYMBOL so that PUSHNEW can assume #'EQ
1230 ;; as the test, but it's not happening, so restate the obvious.
1231 (when w (pushnew s cset :test #'eq))))
1232 (when (cdr cset)
1233 (apply #'name-conflict package 'unintern symbol cset)
1234 (return-from unintern t)))
1235 (setf (package-%shadowing-symbols package)
1236 (remove symbol shadowing-symbols)))
1238 (multiple-value-bind (s w) (find-symbol name package)
1239 (cond ((not (eq symbol s)) nil)
1240 ((or (eq w :internal) (eq w :external))
1241 (nuke-symbol (if (eq w :internal)
1242 (package-internal-symbols package)
1243 (package-external-symbols package))
1244 symbol)
1245 (if (eq (symbol-package symbol) package)
1246 (%set-symbol-package symbol nil))
1248 (t nil)))))))
1250 ;;; Take a symbol-or-list-of-symbols and return a list, checking types.
1251 (defun symbol-listify (thing)
1252 (cond ((listp thing)
1253 (dolist (s thing)
1254 (unless (symbolp s)
1255 (signal-package-error nil
1256 "~S is not a symbol." s)))
1257 thing)
1258 ((symbolp thing) (list thing))
1260 (signal-package-error nil
1261 "~S is neither a symbol nor a list of symbols."
1262 thing))))
1264 (defun string-listify (thing)
1265 (mapcar #'string (ensure-list thing)))
1267 (defun export (symbols &optional (package (sane-package)))
1268 #!+sb-doc
1269 "Exports SYMBOLS from PACKAGE, checking that no name conflicts result."
1270 (with-package-graph ()
1271 (let ((package (find-undeleted-package-or-lose package))
1272 (symbols (symbol-listify symbols))
1273 (syms ()))
1274 ;; Punt any symbols that are already external.
1275 (dolist (sym symbols)
1276 (multiple-value-bind (s found)
1277 (find-external-symbol (symbol-name sym) package)
1278 (unless (or (and found (eq s sym)) (member sym syms))
1279 (push sym syms))))
1280 (with-single-package-locked-error ()
1281 (when syms
1282 (assert-package-unlocked package "exporting symbol~P ~{~A~^, ~}"
1283 (length syms) syms))
1284 ;; Find symbols and packages with conflicts.
1285 (let ((used-by (package-%used-by-list package)))
1286 (dolist (sym syms)
1287 (let ((name (symbol-name sym)))
1288 (dolist (p used-by)
1289 (multiple-value-bind (s w) (find-symbol name p)
1290 (when (and w
1291 (not (eq s sym))
1292 (not (member s (package-%shadowing-symbols p))))
1293 ;; Beware: the name conflict is in package P, not in
1294 ;; PACKAGE.
1295 (name-conflict p 'export sym sym s)))))))
1296 ;; Check that all symbols are accessible. If not, ask to import them.
1297 (let ((missing ())
1298 (imports ()))
1299 (dolist (sym syms)
1300 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1301 (cond ((not (and w (eq s sym)))
1302 (push sym missing))
1303 ((eq w :inherited)
1304 (push sym imports)))))
1305 (when missing
1306 (signal-package-cerror
1307 package
1308 (format nil "~S these symbols into the ~A package."
1309 'import (package-%name package))
1310 "~@<These symbols are not accessible in the ~A package:~2I~_~S~@:>"
1311 (package-%name package) missing)
1312 (import missing package))
1313 (import imports package))
1315 ;; And now, three pages later, we export the suckers.
1316 (let ((internal (package-internal-symbols package))
1317 (external (package-external-symbols package)))
1318 (dolist (sym syms)
1319 (add-symbol external sym)
1320 (nuke-symbol internal sym))))
1321 t)))
1323 ;;; Check that all symbols are accessible, then move from external to internal.
1324 (defun unexport (symbols &optional (package (sane-package)))
1325 #!+sb-doc
1326 "Makes SYMBOLS no longer exported from PACKAGE."
1327 (with-package-graph ()
1328 (let ((package (find-undeleted-package-or-lose package))
1329 (symbols (symbol-listify symbols))
1330 (syms ()))
1331 (dolist (sym symbols)
1332 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1333 (cond ((or (not w) (not (eq s sym)))
1334 (signal-package-error
1335 package
1336 "~S is not accessible in the ~A package."
1337 sym (package-%name package)))
1338 ((eq w :external) (pushnew sym syms)))))
1339 (with-single-package-locked-error ()
1340 (when syms
1341 (assert-package-unlocked package "unexporting symbol~P ~{~A~^, ~}"
1342 (length syms) syms))
1343 (let ((internal (package-internal-symbols package))
1344 (external (package-external-symbols package)))
1345 (dolist (sym syms)
1346 (add-symbol internal sym)
1347 (nuke-symbol external sym))))
1348 t)))
1350 ;;; Check for name conflict caused by the import and let the user
1351 ;;; shadowing-import if there is.
1352 (defun import (symbols &optional (package (sane-package)))
1353 #!+sb-doc
1354 "Make SYMBOLS accessible as internal symbols in PACKAGE. If a symbol is
1355 already accessible then it has no effect. If a name conflict would result from
1356 the importation, then a correctable error is signalled."
1357 (with-package-graph ()
1358 (let* ((package (find-undeleted-package-or-lose package))
1359 (symbols (symbol-listify symbols))
1360 (homeless (remove-if #'symbol-package symbols))
1361 (syms ()))
1362 (with-single-package-locked-error ()
1363 (dolist (sym symbols)
1364 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1365 (cond ((not w)
1366 (let ((found (member sym syms :test #'string=)))
1367 (if found
1368 (when (not (eq (car found) sym))
1369 (setf syms (remove (car found) syms))
1370 (name-conflict package 'import sym sym (car found)))
1371 (push sym syms))))
1372 ((not (eq s sym))
1373 (name-conflict package 'import sym sym s))
1374 ((eq w :inherited) (push sym syms)))))
1375 (when (or homeless syms)
1376 (let ((union (delete-duplicates (append homeless syms))))
1377 (assert-package-unlocked package "importing symbol~P ~{~A~^, ~}"
1378 (length union) union)))
1379 ;; Add the new symbols to the internal hashtable.
1380 (let ((internal (package-internal-symbols package)))
1381 (dolist (sym syms)
1382 (add-symbol internal sym)))
1383 ;; If any of the symbols are uninterned, make them be owned by PACKAGE.
1384 (dolist (sym homeless)
1385 (%set-symbol-package sym package))
1386 t))))
1388 ;;; If a conflicting symbol is present, unintern it, otherwise just
1389 ;;; stick the symbol in.
1390 (defun shadowing-import (symbols &optional (package (sane-package)))
1391 #!+sb-doc
1392 "Import SYMBOLS into package, disregarding any name conflict. If
1393 a symbol of the same name is present, then it is uninterned."
1394 (with-package-graph ()
1395 (let* ((package (find-undeleted-package-or-lose package))
1396 (internal (package-internal-symbols package))
1397 (symbols (symbol-listify symbols))
1398 (lock-asserted-p nil))
1399 (with-single-package-locked-error ()
1400 (dolist (sym symbols)
1401 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1402 (unless (or lock-asserted-p
1403 (and (eq s sym)
1404 (member s (package-shadowing-symbols package))))
1405 (assert-package-unlocked package "shadowing-importing symbol~P ~
1406 ~{~A~^, ~}" (length symbols) symbols)
1407 (setf lock-asserted-p t))
1408 (unless (and w (not (eq w :inherited)) (eq s sym))
1409 (when (or (eq w :internal) (eq w :external))
1410 ;; If it was shadowed, we don't want UNINTERN to flame out...
1411 (setf (package-%shadowing-symbols package)
1412 (remove s (the list (package-%shadowing-symbols package))))
1413 (unintern s package))
1414 (add-symbol internal sym))
1415 (pushnew sym (package-%shadowing-symbols package)))))))
1418 (defun shadow (symbols &optional (package (sane-package)))
1419 #!+sb-doc
1420 "Make an internal symbol in PACKAGE with the same name as each of the
1421 specified SYMBOLS. If a symbol with the given name is already present in
1422 PACKAGE, then the existing symbol is placed in the shadowing symbols list if
1423 it is not already present."
1424 (with-package-graph ()
1425 (let* ((package (find-undeleted-package-or-lose package))
1426 (internal (package-internal-symbols package))
1427 (symbols (string-listify symbols))
1428 (lock-asserted-p nil))
1429 (flet ((present-p (w)
1430 (and w (not (eq w :inherited)))))
1431 (with-single-package-locked-error ()
1432 (dolist (name symbols)
1433 (multiple-value-bind (s w) (find-symbol name package)
1434 (unless (or lock-asserted-p
1435 (and (present-p w)
1436 (member s (package-shadowing-symbols package))))
1437 (assert-package-unlocked package "shadowing symbol~P ~{~A~^, ~}"
1438 (length symbols) symbols)
1439 (setf lock-asserted-p t))
1440 (unless (present-p w)
1441 (setq s (make-symbol name))
1442 (%set-symbol-package s package)
1443 (add-symbol internal s))
1444 (pushnew s (package-%shadowing-symbols package))))))))
1447 ;;; Do stuff to use a package, with all kinds of fun name-conflict checking.
1448 (defun use-package (packages-to-use &optional (package (sane-package)))
1449 #!+sb-doc
1450 "Add all the PACKAGES-TO-USE to the use list for PACKAGE so that the
1451 external symbols of the used packages are accessible as internal symbols in
1452 PACKAGE."
1453 (with-package-graph ()
1454 (let ((packages (package-listify packages-to-use))
1455 (package (find-undeleted-package-or-lose package)))
1457 ;; Loop over each package, USE'ing one at a time...
1458 (with-single-package-locked-error ()
1459 (dolist (pkg packages)
1460 (unless (member pkg (package-%use-list package))
1461 (assert-package-unlocked package "using package~P ~{~A~^, ~}"
1462 (length packages) packages)
1463 (let ((shadowing-symbols (package-%shadowing-symbols package))
1464 (use-list (package-%use-list package)))
1466 ;; If the number of symbols already accessible is less
1467 ;; than the number to be inherited then it is faster to
1468 ;; run the test the other way. This is particularly
1469 ;; valuable in the case of a new package USEing
1470 ;; COMMON-LISP.
1471 (cond
1472 ((< (+ (package-internal-symbol-count package)
1473 (package-external-symbol-count package)
1474 (let ((res 0))
1475 (dolist (p use-list res)
1476 (incf res (package-external-symbol-count p)))))
1477 (package-external-symbol-count pkg))
1478 (do-symbols (sym package)
1479 (multiple-value-bind (s w)
1480 (find-external-symbol (symbol-name sym) pkg)
1481 (when (and w
1482 (not (eq s sym))
1483 (not (member sym shadowing-symbols)))
1484 (name-conflict package 'use-package pkg sym s))))
1485 (dolist (p use-list)
1486 (do-external-symbols (sym p)
1487 (multiple-value-bind (s w)
1488 (find-external-symbol (symbol-name sym) pkg)
1489 (when (and w
1490 (not (eq s sym))
1491 (not (member
1492 (find-symbol (symbol-name sym) package)
1493 shadowing-symbols)))
1494 (name-conflict package 'use-package pkg sym s))))))
1496 (do-external-symbols (sym pkg)
1497 (multiple-value-bind (s w)
1498 (find-symbol (symbol-name sym) package)
1499 (when (and w
1500 (not (eq s sym))
1501 (not (member s shadowing-symbols)))
1502 (name-conflict package 'use-package pkg sym s)))))))
1504 (push pkg (package-%use-list package))
1505 (setf (package-tables package)
1506 (let ((tbls (package-tables package)))
1507 (replace (make-array (1+ (length tbls))
1508 :initial-element (package-external-symbols pkg))
1509 tbls)))
1510 (push package (package-%used-by-list pkg)))))))
1513 (defun unuse-package (packages-to-unuse &optional (package (sane-package)))
1514 #!+sb-doc
1515 "Remove PACKAGES-TO-UNUSE from the USE list for PACKAGE."
1516 (with-package-graph ()
1517 (let ((package (find-undeleted-package-or-lose package))
1518 (packages (package-listify packages-to-unuse)))
1519 (with-single-package-locked-error ()
1520 (dolist (p packages)
1521 (when (member p (package-use-list package))
1522 (assert-package-unlocked package "unusing package~P ~{~A~^, ~}"
1523 (length packages) packages))
1524 (setf (package-%use-list package)
1525 (remove p (the list (package-%use-list package))))
1526 (setf (package-tables package)
1527 (delete (package-external-symbols p)
1528 (package-tables package)))
1529 (setf (package-%used-by-list p)
1530 (remove package (the list (package-%used-by-list p))))))
1531 t)))
1533 (defun find-all-symbols (string-or-symbol)
1534 #!+sb-doc
1535 "Return a list of all symbols in the system having the specified name."
1536 (let ((string (string string-or-symbol))
1537 (res ()))
1538 (with-package-names (names)
1539 (maphash (lambda (k v)
1540 (declare (ignore k))
1541 (multiple-value-bind (s w) (find-symbol string v)
1542 (when w (pushnew s res))))
1543 names))
1544 res))
1546 ;;;; APROPOS and APROPOS-LIST
1548 (defun briefly-describe-symbol (symbol)
1549 (fresh-line)
1550 (prin1 symbol)
1551 (when (boundp symbol)
1552 (write-string " (bound)"))
1553 (when (fboundp symbol)
1554 (write-string " (fbound)")))
1556 (defun apropos-list (string-designator
1557 &optional
1558 package-designator
1559 external-only)
1560 #!+sb-doc
1561 "Like APROPOS, except that it returns a list of the symbols found instead
1562 of describing them."
1563 (if package-designator
1564 (let ((package (find-undeleted-package-or-lose package-designator))
1565 (string (stringify-string-designator string-designator))
1566 (result nil))
1567 (do-symbols (symbol package)
1568 (when (and (or (not external-only)
1569 (and (eq (symbol-package symbol) package)
1570 (eq (nth-value 1 (find-symbol (symbol-name symbol)
1571 package))
1572 :external)))
1573 (search string (symbol-name symbol) :test #'char-equal))
1574 (pushnew symbol result)))
1575 (sort result #'string-lessp))
1576 (delete-duplicates
1577 (mapcan (lambda (package)
1578 (apropos-list string-designator package external-only))
1579 (sort (list-all-packages) #'string-lessp :key #'package-name)))))
1581 (defun apropos (string-designator &optional package external-only)
1582 #!+sb-doc
1583 "Briefly describe all symbols which contain the specified STRING.
1584 If PACKAGE is supplied then only describe symbols present in
1585 that package. If EXTERNAL-ONLY then only describe
1586 external symbols in the specified package."
1587 ;; Implementing this in terms of APROPOS-LIST keeps things simple at the cost
1588 ;; of some unnecessary consing; and the unnecessary consing shouldn't be an
1589 ;; issue, since this function is is only useful interactively anyway, and
1590 ;; we can cons and GC a lot faster than the typical user can read..
1591 (dolist (symbol (apropos-list string-designator package external-only))
1592 (briefly-describe-symbol symbol))
1593 (values))
1595 ;;;; final initialization
1597 ;;;; Due to the relative difficulty - but not impossibility - of manipulating
1598 ;;;; package-hashtables in the cross-compilation host, all interning operations
1599 ;;;; are delayed until cold-init.
1600 ;;;; The cold loader (GENESIS) set *!INITIAL-SYMBOLS* to the target
1601 ;;;; representation of the hosts's *COLD-PACKAGE-SYMBOLS*.
1602 ;;;; The shape of this list is ((package . (externals . internals)) ...)
1603 (defvar *!initial-symbols*)
1605 (defun !package-cold-init ()
1606 (setf *package-graph-lock* (sb!thread:make-mutex :name "Package Graph Lock")
1607 *package-names* (make-hash-table :test 'equal :synchronized t))
1608 (with-package-names (names)
1609 (dolist (spec *!initial-symbols*)
1610 (let ((pkg (car spec)) (symbols (cdr spec)))
1611 ;; the symbol MAKE-TABLE wouldn't magically disappear,
1612 ;; though its only use be to name an FLET in a function
1613 ;; hanging on an otherwise uninternable symbol. strange but true :-(
1614 (flet ((!make-table (input)
1615 (let ((table (make-package-hashtable
1616 (length (the simple-vector input)))))
1617 (dovector (symbol input table)
1618 (add-symbol table symbol)))))
1619 (setf (package-external-symbols pkg) (!make-table (car symbols))
1620 (package-internal-symbols pkg) (!make-table (cdr symbols))))
1621 (setf (package-%local-nicknames pkg) nil
1622 (package-%locally-nicknamed-by pkg) nil
1623 (package-source-location pkg) nil
1624 (gethash (package-%name pkg) names) pkg)
1625 (let ((nicks (package-%nicknames pkg)))
1626 (setf (package-%nicknames pkg) nil) ; each is pushed in again
1627 (%enter-new-nicknames pkg nicks))
1628 #!+sb-package-locks
1629 (setf (package-lock pkg) nil
1630 (package-%implementation-packages pkg) nil))))
1632 ;; pass 2 - set the 'tables' slots only after all tables have been made
1633 (dolist (spec *!initial-symbols*)
1634 (let ((pkg (car spec)))
1635 (setf (package-tables pkg)
1636 (map 'vector #'package-external-symbols (package-%use-list pkg)))))
1638 (/show0 "about to MAKUNBOUND *!INITIAL-SYMBOLS*")
1639 (%makunbound '*!initial-symbols*) ; (so that it gets GCed)
1641 ;; For the kernel core image wizards, set the package to *CL-PACKAGE*.
1643 ;; FIXME: We should just set this to (FIND-PACKAGE
1644 ;; "COMMON-LISP-USER") once and for all here, instead of setting it
1645 ;; once here and resetting it later.
1646 (setq *package* *cl-package*))
1648 ;;; support for WITH-PACKAGE-ITERATOR
1650 (defun package-iter-init (access-types pkg-designator-list)
1651 (declare (type (integer 1 7) access-types)) ; a nonzero bitmask over types
1652 (values (logior (ash access-types 3) #b11) 0 #()
1653 (package-listify pkg-designator-list)))
1655 ;; The STATE parameter is comprised of 4 packed fields
1656 ;; [0:1] = substate {0=internal,1=external,2=inherited,3=initial}
1657 ;; [2] = package with inherited symbols has shadowing symbols
1658 ;; [3:5] = enabling bits for {internal,external,inherited}
1659 ;; [6:] = index into 'package-tables'
1661 (defconstant +package-iter-check-shadows+ #b000100)
1663 (defun package-iter-step (start-state index sym-vec pkglist)
1664 ;; the defknown isn't enough
1665 (declare (type fixnum start-state) (type index index)
1666 (type simple-vector sym-vec) (type list pkglist))
1667 (declare (optimize speed))
1668 (labels
1669 ((advance (state) ; STATE is the one just completed
1670 (case (logand state #b11)
1671 ;; Test :INHERITED first because the state repeats for a package
1672 ;; as many times as there are packages it uses. There are enough
1673 ;; bits to count up to 2^23 packages if fixnums are 30 bits.
1675 (when (desired-state-p 2)
1676 (let* ((tables (package-tables (this-package)))
1677 (next-state (the fixnum (+ state (ash 1 6))))
1678 (table-idx (ash next-state -6)))
1679 (when (< table-idx (length tables))
1680 (return-from advance ; remain in state 2
1681 (start next-state (svref tables table-idx))))))
1682 (pop pkglist)
1683 (advance 3)) ; start on next package
1684 (1 ; finished externals, switch to inherited if desired
1685 (when (desired-state-p 2)
1686 (let ((tables (package-tables (this-package))))
1687 (when (plusp (length tables)) ; inherited symbols
1688 (return-from advance ; enter state 2
1689 (start (if (package-%shadowing-symbols (this-package))
1690 (logior 2 +package-iter-check-shadows+) 2)
1691 (svref tables 0))))))
1692 (advance 2)) ; skip state 2
1693 (0 ; finished internals, switch to externals if desired
1694 (if (desired-state-p 1) ; enter state 1
1695 (start 1 (package-external-symbols (this-package)))
1696 (advance 1))) ; skip state 1
1697 (t ; initial state
1698 (cond ((endp pkglist) ; latch into returning NIL forever more
1699 (values 0 0 #() '() nil nil))
1700 ((desired-state-p 0) ; enter state 0
1701 (start 0 (package-internal-symbols (this-package))))
1702 (t (advance 0)))))) ; skip state 0
1703 (desired-state-p (target-state)
1704 (logtest start-state (ash 1 (+ target-state 3))))
1705 (this-package ()
1706 (truly-the package (car pkglist)))
1707 (start (next-state new-table)
1708 (let ((symbols (package-hashtable-cells new-table)))
1709 (package-iter-step (logior (mask-field (byte 3 3) start-state)
1710 next-state)
1711 ;; assert that physical length was nonzero
1712 (the index (1- (length symbols)))
1713 symbols pkglist))))
1714 (declare (inline desired-state-p this-package))
1715 (if (zerop index)
1716 (advance start-state)
1717 (macrolet ((scan (&optional (guard t))
1718 `(loop
1719 (let ((sym (aref sym-vec (decf index))))
1720 (when (and (pkg-symbol-valid-p sym) ,guard)
1721 (return (values start-state index sym-vec pkglist sym
1722 (aref #(:internal :external :inherited)
1723 (logand start-state 3))))))
1724 (when (zerop index)
1725 (return (advance start-state))))))
1726 (declare #-sb-xc-host(optimize (sb!c::insert-array-bounds-checks 0)))
1727 (if (logtest start-state +package-iter-check-shadows+)
1728 (let ((shadows (package-%shadowing-symbols (this-package))))
1729 (scan (not (member sym shadows :test #'string=))))
1730 (scan))))))
1732 (defun program-assert-symbol-home-package-unlocked (context symbol control)
1733 #!-sb-package-locks
1734 (declare (ignore context symbol control))
1735 #!+sb-package-locks
1736 (handler-bind ((package-lock-violation
1737 (lambda (condition)
1738 (ecase context
1739 (:compile
1740 ;; FIXME: Code containing a lexically impermissible
1741 ;; violation causes both a warning AND an error.
1742 ;; The warning is enough. It's ugly that both happen.
1743 (warn "Compile-time package lock violation:~% ~A"
1744 condition)
1745 (sb!c:compiler-error condition))
1746 (:eval
1747 (eval-error condition))))))
1748 (with-single-package-locked-error (:symbol symbol control))))