fix APROPOS/APROPOS-LIST and inherited symbols
[sbcl.git] / src / code / target-package.lisp
blob76e7df6f4394f6517eae7ecaa8b483e1487800a4
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 (def!method print-object ((table package-hashtable) stream)
72 (declare (type stream stream))
73 (print-unreadable-object (table stream :type t)
74 (format stream
75 ":SIZE ~S :FREE ~S :DELETED ~S"
76 (package-hashtable-size table)
77 (package-hashtable-free table)
78 (package-hashtable-deleted table))))
80 ;;; the maximum load factor we allow in a package hashtable
81 (!defparameter *package-rehash-threshold* 3/4)
83 ;;; the load factor desired for a package hashtable when writing a
84 ;;; core image
85 (!defparameter *package-hashtable-image-load-factor* 1/2)
87 ;;; Make a package hashtable having a prime number of entries at least
88 ;;; as great as (/ SIZE *PACKAGE-REHASH-THRESHOLD*). If RES is supplied,
89 ;;; then it is destructively modified to produce the result. This is
90 ;;; useful when changing the size, since there are many pointers to
91 ;;; the hashtable.
92 ;;; Actually, the smallest table built here has three entries. This
93 ;;; is necessary because the double hashing step size is calculated
94 ;;; using a division by the table size minus two.
95 (defun make-package-hashtable (size)
96 (flet ((actual-package-hashtable-size (size)
97 (loop for n of-type fixnum
98 from (logior (ceiling size *package-rehash-threshold*) 1)
99 by 2
100 when (positive-primep n) return n)))
101 (let* ((n (actual-package-hashtable-size size))
102 (size (truncate (* n *package-rehash-threshold*)))
103 (table (make-array (1+ n) :initial-element 0)))
104 (setf (aref table n)
105 (make-array n :element-type '(unsigned-byte 8)
106 :initial-element 0))
107 (%make-package-hashtable table size))))
109 ;;; Destructively resize TABLE to have room for at least SIZE entries
110 ;;; and rehash its existing entries.
111 (defun resize-package-hashtable (table size)
112 (let* ((symvec (package-hashtable-table table))
113 (len (1- (length symvec)))
114 (temp-table (make-package-hashtable size)))
115 (dotimes (i len)
116 (let ((sym (svref symvec i)))
117 (unless (eql sym 0)
118 (add-symbol temp-table sym))))
119 (setf (package-hashtable-table table) (package-hashtable-table temp-table)
120 (package-hashtable-size table) (package-hashtable-size temp-table)
121 (package-hashtable-free table) (package-hashtable-free temp-table)
122 (package-hashtable-deleted table) 0)))
124 ;;;; package locking operations, built conditionally on :sb-package-locks
126 #!+sb-package-locks
127 (progn
128 (defun package-locked-p (package)
129 #!+sb-doc
130 "Returns T when PACKAGE is locked, NIL otherwise. Signals an error
131 if PACKAGE doesn't designate a valid package."
132 (package-lock (find-undeleted-package-or-lose package)))
134 (defun lock-package (package)
135 #!+sb-doc
136 "Locks PACKAGE and returns T. Has no effect if PACKAGE was already
137 locked. Signals an error if PACKAGE is not a valid package designator"
138 (setf (package-lock (find-undeleted-package-or-lose package)) t))
140 (defun unlock-package (package)
141 #!+sb-doc
142 "Unlocks PACKAGE and returns T. Has no effect if PACKAGE was already
143 unlocked. Signals an error if PACKAGE is not a valid package designator."
144 (setf (package-lock (find-undeleted-package-or-lose package)) nil)
147 (defun package-implemented-by-list (package)
148 #!+sb-doc
149 "Returns a list containing the implementation packages of
150 PACKAGE. Signals an error if PACKAGE is not a valid package designator."
151 (package-%implementation-packages (find-undeleted-package-or-lose package)))
153 (defun package-implements-list (package)
154 #!+sb-doc
155 "Returns the packages that PACKAGE is an implementation package
156 of. Signals an error if PACKAGE is not a valid package designator."
157 (let ((package (find-undeleted-package-or-lose package)))
158 (loop for x in (list-all-packages)
159 when (member package (package-%implementation-packages x))
160 collect x)))
162 (defun add-implementation-package (packages-to-add
163 &optional (package *package*))
164 #!+sb-doc
165 "Adds PACKAGES-TO-ADD as implementation packages of PACKAGE. Signals
166 an error if PACKAGE or any of the PACKAGES-TO-ADD is not a valid
167 package designator."
168 (let ((package (find-undeleted-package-or-lose package))
169 (packages-to-add (package-listify packages-to-add)))
170 (setf (package-%implementation-packages package)
171 (union (package-%implementation-packages package)
172 (mapcar #'find-undeleted-package-or-lose packages-to-add)))))
174 (defun remove-implementation-package (packages-to-remove
175 &optional (package *package*))
176 #!+sb-doc
177 "Removes PACKAGES-TO-REMOVE from the implementation packages of
178 PACKAGE. Signals an error if PACKAGE or any of the PACKAGES-TO-REMOVE
179 is not a valid package designator."
180 (let ((package (find-undeleted-package-or-lose package))
181 (packages-to-remove (package-listify packages-to-remove)))
182 (setf (package-%implementation-packages package)
183 (nset-difference
184 (package-%implementation-packages package)
185 (mapcar #'find-undeleted-package-or-lose packages-to-remove)))))
187 (defmacro with-unlocked-packages ((&rest packages) &body forms)
188 #!+sb-doc
189 "Unlocks PACKAGES for the dynamic scope of the body. Signals an
190 error if any of PACKAGES is not a valid package designator."
191 (with-unique-names (unlocked-packages)
192 `(let (,unlocked-packages)
193 (unwind-protect
194 (progn
195 (dolist (p ',packages)
196 (when (package-locked-p p)
197 (push p ,unlocked-packages)
198 (unlock-package p)))
199 ,@forms)
200 (dolist (p ,unlocked-packages)
201 (when (find-package p)
202 (lock-package p)))))))
204 (defun package-lock-violation (package &key (symbol nil symbol-p)
205 format-control format-arguments)
206 (let* ((restart :continue)
207 (cl-violation-p (eq package *cl-package*))
208 (error-arguments
209 (append (list (if symbol-p
210 'symbol-package-locked-error
211 'package-locked-error)
212 :package package
213 :format-control format-control
214 :format-arguments format-arguments)
215 (when symbol-p (list :symbol symbol))
216 (list :references
217 (append '((:sbcl :node "Package Locks"))
218 (when cl-violation-p
219 '((:ansi-cl :section (11 1 2 1 2)))))))))
220 (restart-case
221 (apply #'cerror "Ignore the package lock." error-arguments)
222 (:ignore-all ()
223 :report "Ignore all package locks in the context of this operation."
224 (setf restart :ignore-all))
225 (:unlock-package ()
226 :report "Unlock the package."
227 (setf restart :unlock-package)))
228 (ecase restart
229 (:continue
230 (pushnew package *ignored-package-locks*))
231 (:ignore-all
232 (setf *ignored-package-locks* t))
233 (:unlock-package
234 (unlock-package package)))))
236 (defun package-lock-violation-p (package &optional (symbol nil symbolp))
237 ;; KLUDGE: (package-lock package) needs to be before
238 ;; comparison to *package*, since during cold init this gets
239 ;; called before *package* is bound -- but no package should
240 ;; be locked at that point.
241 (and package
242 (package-lock package)
243 ;; In package or implementation package
244 (not (or (eq package *package*)
245 (member *package* (package-%implementation-packages package))))
246 ;; Runtime disabling
247 (not (eq t *ignored-package-locks*))
248 (or (eq :invalid *ignored-package-locks*)
249 (not (member package *ignored-package-locks*)))
250 ;; declarations for symbols
251 (not (and symbolp (member symbol (disabled-package-locks))))))
253 (defun disabled-package-locks ()
254 (if (boundp 'sb!c::*lexenv*)
255 (sb!c::lexenv-disabled-package-locks sb!c::*lexenv*)
256 sb!c::*disabled-package-locks*))
258 ) ; progn
260 ;;;; more package-locking these are NOPs unless :sb-package-locks is
261 ;;;; in target features. Cross-compiler NOPs for these are in cross-misc.
263 ;;; The right way to establish a package lock context is
264 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR, defined in early-package.lisp
266 ;;; Must be used inside the dynamic contour established by
267 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR
268 (defun assert-package-unlocked (package &optional format-control
269 &rest format-arguments)
270 #!-sb-package-locks
271 (declare (ignore format-control format-arguments))
272 #!+sb-package-locks
273 (when (package-lock-violation-p package)
274 (package-lock-violation package
275 :format-control format-control
276 :format-arguments format-arguments))
277 package)
279 ;;; Must be used inside the dynamic contour established by
280 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR.
282 ;;; FIXME: Maybe we should establish such contours for he toplevel
283 ;;; and others, so that %set-fdefinition and others could just use
284 ;;; this.
285 (defun assert-symbol-home-package-unlocked (name &optional format-control
286 &rest format-arguments)
287 #!-sb-package-locks
288 (declare (ignore format-control format-arguments))
289 #!+sb-package-locks
290 (let* ((symbol (etypecase name
291 (symbol name)
292 ((cons (eql setf) cons) (second name))
293 ;; Skip lists of length 1, single conses and
294 ;; (class-predicate foo), etc. FIXME: MOP and
295 ;; package-lock interaction needs to be thought
296 ;; about.
297 (list
298 (return-from assert-symbol-home-package-unlocked
299 name))))
300 (package (symbol-package symbol)))
301 (when (package-lock-violation-p package symbol)
302 (package-lock-violation package
303 :symbol symbol
304 :format-control format-control
305 :format-arguments (cons name format-arguments))))
306 name)
309 ;;;; miscellaneous PACKAGE operations
311 (def!method print-object ((package package) stream)
312 (let ((name (package-%name package)))
313 (print-unreadable-object (package stream :type t :identity (not name))
314 (if name (prin1 name stream) (write-string "(deleted)" stream)))))
316 ;;; ANSI says (in the definition of DELETE-PACKAGE) that these, and
317 ;;; most other operations, are unspecified for deleted packages. We
318 ;;; just do the easy thing and signal errors in that case.
319 (macrolet ((def (ext real)
320 `(defun ,ext (package-designator)
321 (,real (find-undeleted-package-or-lose package-designator)))))
322 (def package-nicknames package-%nicknames)
323 (def package-use-list package-%use-list)
324 (def package-used-by-list package-%used-by-list)
325 (def package-shadowing-symbols package-%shadowing-symbols))
327 (defun package-local-nicknames (package-designator)
328 #!+sb-doc
329 "Returns an alist of \(local-nickname . actual-package) describing the
330 nicknames local to the designated package.
332 When in the designated package, calls to FIND-PACKAGE with the any of the
333 local-nicknames will return the corresponding actual-package instead. This
334 also affects all implied calls to FIND-PACKAGE, including those performed by
335 the reader.
337 When printing a package prefix for a symbol with a package local nickname, the
338 local nickname is used instead of the real name in order to preserve
339 print-read consistency.
341 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
342 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
344 Experimental: interface subject to change."
345 (copy-tree
346 (package-%local-nicknames
347 (find-undeleted-package-or-lose package-designator))))
349 (defun signal-package-error (package format-control &rest format-args)
350 (error 'simple-package-error
351 :package package
352 :format-control format-control
353 :format-arguments format-args))
355 (defun signal-package-cerror (package continue-string
356 format-control &rest format-args)
357 (cerror continue-string
358 'simple-package-error
359 :package package
360 :format-control format-control
361 :format-arguments format-args))
363 (defun package-locally-nicknamed-by-list (package-designator)
364 #!+sb-doc
365 "Returns a list of packages which have a local nickname for the designated
366 package.
368 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
369 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
371 Experimental: interface subject to change."
372 (copy-list
373 (package-%locally-nicknamed-by
374 (find-undeleted-package-or-lose package-designator))))
376 (defun add-package-local-nickname (local-nickname actual-package
377 &optional (package-designator (sane-package)))
378 #!+sb-doc
379 "Adds LOCAL-NICKNAME for ACTUAL-PACKAGE in the designated package, defaulting
380 to current package. LOCAL-NICKNAME must be a string designator, and
381 ACTUAL-PACKAGE must be a package designator.
383 Returns the designated package.
385 Signals a continuable error if LOCAL-NICKNAME is already a package local
386 nickname for a different package, or if LOCAL-NICKNAME is one of \"CL\",
387 \"COMMON-LISP\", or, \"KEYWORD\", or if LOCAL-NICKNAME is a global name or
388 nickname for the package to which the nickname would be added.
390 When in the designated package, calls to FIND-PACKAGE with the LOCAL-NICKNAME
391 will return the package the designated ACTUAL-PACKAGE instead. This also
392 affects all implied calls to FIND-PACKAGE, including those performed by the
393 reader.
395 When printing a package prefix for a symbol with a package local nickname,
396 local nickname is used instead of the real name in order to preserve
397 print-read consistency.
399 See also: PACKAGE-LOCAL-NICKNAMES, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
400 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
402 Experimental: interface subject to change."
403 (let* ((nick (string local-nickname))
404 (actual (find-package-using-package actual-package nil))
405 (package (find-undeleted-package-or-lose package-designator))
406 (existing (package-%local-nicknames package))
407 (cell (assoc nick existing :test #'string=)))
408 (unless actual
409 (signal-package-error
410 package-designator
411 "The name ~S does not designate any package."
412 actual-package))
413 (unless (package-name actual)
414 (signal-package-error
415 actual
416 "Cannot add ~A as local nickname for a deleted package: ~S"
417 nick actual))
418 (with-single-package-locked-error
419 (:package package "adding ~A as a local nickname for ~A"
420 nick actual))
421 (when (member nick '("CL" "COMMON-LISP" "KEYWORD") :test #'string=)
422 (signal-package-cerror
423 actual
424 "Continue, use it as local nickname anyways."
425 "Attempt to use ~A as a package local nickname (for ~A)."
426 nick (package-name actual)))
427 (when (string= nick (package-name package))
428 (signal-package-cerror
429 package
430 "Continue, use it as a local nickname anyways."
431 "Attempt to use ~A as a package local nickname (for ~A) in ~
432 package named globally ~A."
433 nick (package-name actual) nick))
434 (when (member nick (package-nicknames package) :test #'string=)
435 (signal-package-cerror
436 package
437 "Continue, use it as a local nickname anyways."
438 "Attempt to use ~A as a package local nickname (for ~A) in ~
439 package nicknamed globally ~A."
440 nick (package-name actual) nick))
441 (when (and cell (neq actual (cdr cell)))
442 (restart-case
443 (signal-package-error
444 actual
445 "~@<Cannot add ~A as local nickname for ~A in ~A: ~
446 already nickname for ~A.~:@>"
447 nick (package-name actual)
448 (package-name package) (package-name (cdr cell)))
449 (keep-old ()
450 :report (lambda (s)
451 (format s "Keep ~A as local nicname for ~A."
452 nick (package-name (cdr cell)))))
453 (change-nick ()
454 :report (lambda (s)
455 (format s "Use ~A as local nickname for ~A instead."
456 nick (package-name actual)))
457 (let ((old (cdr cell)))
458 (with-package-graph ()
459 (setf (package-%locally-nicknamed-by old)
460 (delete package (package-%locally-nicknamed-by old)))
461 (push package (package-%locally-nicknamed-by actual))
462 (setf (cdr cell) actual)))))
463 (return-from add-package-local-nickname package))
464 (unless cell
465 (with-package-graph ()
466 (push (cons nick actual) (package-%local-nicknames package))
467 (push package (package-%locally-nicknamed-by actual))))
468 package))
470 (defun remove-package-local-nickname (old-nickname
471 &optional (package-designator (sane-package)))
472 #!+sb-doc
473 "If the designated package had OLD-NICKNAME as a local nickname for
474 another package, it is removed. Returns true if the nickname existed and was
475 removed, and NIL otherwise.
477 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
478 PACKAGE-LOCALLY-NICKNAMED-BY-LIST, and the DEFPACKAGE option :LOCAL-NICKNAMES.
480 Experimental: interface subject to change."
481 (let* ((nick (string old-nickname))
482 (package (find-undeleted-package-or-lose package-designator))
483 (existing (package-%local-nicknames package))
484 (cell (assoc nick existing :test #'string=)))
485 (when cell
486 (with-single-package-locked-error
487 (:package package "removing local nickname ~A for ~A"
488 nick (cdr cell)))
489 (with-package-graph ()
490 (let ((old (cdr cell)))
491 (setf (package-%local-nicknames package) (delete cell existing))
492 (setf (package-%locally-nicknamed-by old)
493 (delete package (package-%locally-nicknamed-by old)))))
494 t)))
496 (defun %package-hashtable-symbol-count (table)
497 (let ((size (the fixnum
498 (- (package-hashtable-size table)
499 (package-hashtable-deleted table)))))
500 (the fixnum
501 (- size (package-hashtable-free table)))))
503 (defun package-internal-symbol-count (package)
504 (%package-hashtable-symbol-count (package-internal-symbols package)))
506 (defun package-external-symbol-count (package)
507 (%package-hashtable-symbol-count (package-external-symbols package)))
509 (defvar *package* (error "*PACKAGE* should be initialized in cold load!")
510 #!+sb-doc "the current package")
512 (define-condition bootstrap-package-not-found (condition)
513 ((name :initarg :name :reader bootstrap-package-name)))
514 (defun debootstrap-package (&optional condition)
515 (invoke-restart
516 (find-restart-or-control-error 'debootstrap-package condition)))
518 (defun find-package (package-designator)
519 #!+sb-doc
520 "If PACKAGE-DESIGNATOR is a package, it is returned. Otherwise PACKAGE-DESIGNATOR
521 must be a string designator, in which case the package it names is located and returned.
523 As an SBCL extension, the current package may affect the way a package name is
524 resolved: if the current package has local nicknames specified, package names
525 matching those are resolved to the packages associated with them instead.
527 Example:
529 (defpackage :a)
530 (defpackage :example (:use :cl) (:local-nicknames (:x :a)))
531 (let ((*package* (find-package :example)))
532 (find-package :x)) => #<PACKAGE A>
534 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
535 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES."
536 (find-package-using-package package-designator
537 (when (boundp '*package*)
538 *package*)))
540 ;;; This is undocumented and unexported for now, but the idea is that by
541 ;;; making this a generic function then packages with custom package classes
542 ;;; could hook into this to provide their own resolution.
543 (defun find-package-using-package (package-designator base)
544 (flet ((find-package-from-string (string)
545 (declare (type string string))
546 (let* ((nicknames (when base
547 (package-%local-nicknames base)))
548 (nicknamed (when nicknames
549 (cdr (assoc string nicknames :test #'string=))))
550 (packageoid (or nicknamed (gethash string *package-names*))))
551 (if (and (null packageoid)
552 ;; FIXME: should never need 'debootstrap' hack
553 (let ((mismatch (mismatch "SB!" string)))
554 (and mismatch (= mismatch 3))))
555 (restart-case
556 (signal 'bootstrap-package-not-found :name string)
557 (debootstrap-package ()
558 (if (string= string "SB!XC")
559 (find-package "COMMON-LISP")
560 (find-package
561 (substitute #\- #\! string :count 1)))))
562 packageoid))))
563 (typecase package-designator
564 (package package-designator)
565 (symbol (find-package-from-string (symbol-name package-designator)))
566 (string (find-package-from-string package-designator))
567 (character (find-package-from-string (string package-designator)))
568 (t (error 'type-error
569 :datum package-designator
570 :expected-type '(or character package string symbol))))))
572 ;;; Return a list of packages given a package designator or list of
573 ;;; package designators, or die trying.
574 (defun package-listify (thing)
575 (mapcar #'find-undeleted-package-or-lose
576 (if (listp thing) thing (list thing))))
578 ;;; ANSI specifies (in the definition of DELETE-PACKAGE) that PACKAGE-NAME
579 ;;; returns NIL (not an error) for a deleted package, so this is a special
580 ;;; case where we want to use bare %FIND-PACKAGE-OR-LOSE instead of
581 ;;; FIND-UNDELETED-PACKAGE-OR-LOSE.
582 (defun package-name (package-designator)
583 (package-%name (%find-package-or-lose package-designator)))
585 ;;;; operations on package hashtables
587 ;;; Compute a number from the sxhash of the pname and the length which
588 ;;; must be between 2 and 255.
589 (defmacro entry-hash (length sxhash)
590 `(the fixnum
591 (+ (the fixnum
592 (rem (the fixnum
593 (logxor ,length
594 ,sxhash
595 (the fixnum (ash ,sxhash -8))
596 (the fixnum (ash ,sxhash -16))
597 (the fixnum (ash ,sxhash -19))))
598 254))
599 2)))
600 ;;; FIXME: should be wrapped in EVAL-WHEN (COMPILE EXECUTE)
602 ;;; Add a symbol to a package hashtable. The symbol is assumed
603 ;;; not to be present.
604 (defun add-symbol (table symbol)
605 (when (zerop (package-hashtable-free table))
606 ;; The hashtable is full. Resize it to be able to hold twice the
607 ;; amount of symbols than it currently contains. The actual new size
608 ;; can be smaller than twice the current size if the table contained
609 ;; deleted entries.
610 (resize-package-hashtable table
611 (* (- (package-hashtable-size table)
612 (package-hashtable-deleted table))
613 2)))
614 (let* ((symvec (package-hashtable-table table))
615 (len (1- (length symvec)))
616 (hashvec (the hash-vector (aref symvec len)))
617 (sxhash (%sxhash-simple-string (symbol-name symbol)))
618 (h2 (1+ (rem sxhash (- len 2)))))
619 (declare (fixnum sxhash h2))
620 (do ((i (rem sxhash len) (rem (+ i h2) len)))
621 ((< (aref hashvec i) 2)
622 (if (eql (aref hashvec i) 0)
623 (decf (package-hashtable-free table))
624 (decf (package-hashtable-deleted table)))
625 ;; This order of these two SETFs does not matter.
626 ;; A symbol cell of 0 is skipped on lookup if the hash cell
627 ;; matches something accidentally.
628 (setf (svref symvec i) symbol)
629 (setf (aref hashvec i)
630 (entry-hash (length (symbol-name symbol))
631 sxhash)))
632 (declare (fixnum i)))))
634 ;;; Resize the package hashtables of all packages so that their load
635 ;;; factor is *PACKAGE-HASHTABLE-IMAGE-LOAD-FACTOR*. Called from
636 ;;; SAVE-LISP-AND-DIE to optimize space usage in the image.
637 (defun tune-hashtable-sizes-of-all-packages ()
638 (flet ((tune-table-size (table)
639 (resize-package-hashtable
640 table
641 (round (* (/ *package-rehash-threshold*
642 *package-hashtable-image-load-factor*)
643 (- (package-hashtable-size table)
644 (package-hashtable-free table)
645 (package-hashtable-deleted table)))))))
646 (dolist (package (list-all-packages))
647 (tune-table-size (package-internal-symbols package))
648 (tune-table-size (package-external-symbols package)))))
650 ;;; Find where the symbol named STRING is stored in TABLE. INDEX-VAR
651 ;;; is bound to the index, or NIL if it is not present. SYMBOL-VAR
652 ;;; is bound to the symbol. LENGTH and HASH are the length and sxhash
653 ;;; of STRING. ENTRY-HASH is the entry-hash of the string and length.
654 ;;; If the symbol is found, then FORMS are executed; otherwise not.
656 (defmacro with-symbol (((symbol-var &optional (index-var (gensym))) table
657 string length sxhash entry-hash) &body forms)
658 (let ((vec (gensym)) (hash-vec (gensym)) (len (gensym)) (h2 (gensym))
659 (name (gensym)) (ehash (gensym)))
660 `(let* ((,vec (package-hashtable-table ,table))
661 (,len (1- (length ,vec)))
662 (,hash-vec (the hash-vector (svref ,vec ,len)))
663 (,index-var (rem (the hash ,sxhash) ,len))
664 (,h2 (1+ (the index (rem (the hash ,sxhash)
665 (the index (- ,len 2)))))))
666 (declare (type index ,len ,h2 ,index-var))
667 (loop
668 (let ((,ehash (aref ,hash-vec ,index-var)))
669 (cond ((eql ,ehash ,entry-hash)
670 (let ((,symbol-var (svref ,vec ,index-var)))
671 (unless (eql ,symbol-var 0)
672 (let ((,name (symbol-name (truly-the symbol ,symbol-var))))
673 (when (and (= (length ,name) ,length)
674 (string= ,string ,name
675 :end1 ,length :end2 ,length))
676 (return (progn ,@forms)))))))
677 ((zerop ,ehash)
678 (return))))
679 (setq ,index-var (+ ,index-var ,h2))
680 (when (>= ,index-var ,len)
681 (setq ,index-var (- ,index-var ,len)))))))
683 ;;; Delete the entry for STRING in TABLE. The entry must exist.
684 ;;; Deletion stores 0 for the symbol and 1 for the hash tombstone.
685 ;;; Storing NIL for the symbol, as used to be done, is vulnerable to a rare
686 ;;; concurrency bug because many strings have the same ENTRY-HASH as NIL:
687 ;;; (entry-hash 3 (sxhash "NIL")) => 177 and
688 ;;; (entry-hash 2 (sxhash "3M")) => 177
689 ;;; Suppose, in the former approach, that "3M" is interned,
690 ;;; and then the following sequence of events occur:
691 ;;; - thread 1 performs FIND-SYMBOL on "NIL", hits the hash code at
692 ;;; at index I, and is then context-switched out. When this thread
693 ;; resumes, it assumes a valid symbol in (SVREF SYM-VEC I)
694 ;;; - thread 2 uninterns "3M" and fully completes that, storing NIL
695 ;;; in the slot for the symbol that thread 1 will next read.
696 ;;; - thread 1 continues, and test for STRING= to NIL,
697 ;;; wrongly seeing NIL as a present symbol.
698 ;;; It's possible this is harmless, because NIL is usually inherited from CL,
699 ;;; but if the secondary return value mattered to the application,
700 ;;; it is probably wrong. And of course if NIL was not intended to be found
701 ;;; - as in a package that does not use CL - then finding NIL at all is wrong.
702 ;;; The better approach is to treat 'hash' as purely a heuristic without
703 ;;; ill-effect from false positives. No barrier, nor read-consistency
704 ;;; check is required, since a symbol is both its key and value,
705 ;;; and the "absence of a symbol" marker is never mistaken for a symbol.
707 (defun nuke-symbol (table string)
708 (declare (simple-string string))
709 (let* ((length (length string))
710 (hash (%sxhash-simple-string string))
711 (ehash (entry-hash length hash)))
712 (declare (type index length)
713 (type hash hash))
714 (with-symbol ((symbol index) table string length hash ehash)
715 ;; It is suboptimal to grab the vectors again, but not broken,
716 ;; because we have exclusive use of the table for writing.
717 (let* ((symvec (package-hashtable-table table))
718 (hashvec (the hash-vector (aref symvec (1- (length symvec))))))
719 (setf (aref hashvec index) 1)
720 (setf (aref symvec index) 0))
721 (incf (package-hashtable-deleted table))))
722 ;; If the table is less than one quarter full, halve its size and
723 ;; rehash the entries.
724 (let* ((size (package-hashtable-size table))
725 (deleted (package-hashtable-deleted table))
726 (used (- size
727 (package-hashtable-free table)
728 deleted)))
729 (declare (type fixnum size deleted used))
730 (when (< used (truncate size 4))
731 (resize-package-hashtable table (* used 2)))))
733 ;;; Enter any new NICKNAMES for PACKAGE into *PACKAGE-NAMES*. If there is a
734 ;;; conflict then give the user a chance to do something about it. Caller is
735 ;;; responsible for having acquired the mutex via WITH-PACKAGES.
736 (defun %enter-new-nicknames (package nicknames)
737 (declare (type list nicknames))
738 (dolist (n nicknames)
739 (let* ((n (stringify-package-designator n))
740 (found (with-package-names (names)
741 (or (gethash n names)
742 (progn
743 (setf (gethash n names) package)
744 (push n (package-%nicknames package))
745 package)))))
746 (cond ((eq found package))
747 ((string= (the string (package-%name found)) n)
748 (signal-package-cerror
749 package
750 "Ignore this nickname."
751 "~S is a package name, so it cannot be a nickname for ~S."
752 n (package-%name package)))
754 (signal-package-cerror
755 package
756 "Leave this nickname alone."
757 "~S is already a nickname for ~S."
758 n (package-%name found)))))))
760 (defun make-package (name &key
761 (use '#.*default-package-use-list*)
762 nicknames
763 (internal-symbols 10)
764 (external-symbols 10))
765 #!+sb-doc
766 #.(format nil
767 "Make a new package having the specified NAME, NICKNAMES, and USE
768 list. :INTERNAL-SYMBOLS and :EXTERNAL-SYMBOLS are estimates for the number of
769 internal and external symbols which will ultimately be present in the package.
770 The default value of USE is implementation-dependent, and in this
771 implementation it is ~S." *default-package-use-list*)
772 (prog (clobber)
773 :restart
774 (when (find-package name)
775 ;; ANSI specifies that this error is correctable.
776 (signal-package-cerror
777 name
778 "Clobber existing package."
779 "A package named ~S already exists" name)
780 (setf clobber t))
781 (with-package-graph ()
782 ;; Check for race, signal the error outside the lock.
783 (when (and (not clobber) (find-package name))
784 (go :restart))
785 (let* ((name (stringify-package-designator name))
786 (package
787 (internal-make-package
788 :%name name
789 :internal-symbols (make-package-hashtable internal-symbols)
790 :external-symbols (make-package-hashtable external-symbols))))
792 ;; Do a USE-PACKAGE for each thing in the USE list so that checking for
793 ;; conflicting exports among used packages is done.
794 (use-package use package)
796 ;; FIXME: ENTER-NEW-NICKNAMES can fail (ERROR) if nicknames are illegal,
797 ;; which would leave us with possibly-bad side effects from the earlier
798 ;; USE-PACKAGE (e.g. this package on the used-by lists of other packages,
799 ;; but not in *PACKAGE-NAMES*, and possibly import side effects too?).
800 ;; Perhaps this can be solved by just moving ENTER-NEW-NICKNAMES before
801 ;; USE-PACKAGE, but I need to check what kinds of errors can be caused by
802 ;; USE-PACKAGE, too.
803 (%enter-new-nicknames package nicknames)
804 (return (setf (gethash name *package-names*) package))))
805 (bug "never")))
807 ;;; Change the name if we can, blast any old nicknames and then
808 ;;; add in any new ones.
810 ;;; FIXME: ANSI claims that NAME is a package designator (not just a
811 ;;; string designator -- weird). Thus, NAME could
812 ;;; be a package instead of a string. Presumably then we should not change
813 ;;; the package name if NAME is the same package that's referred to by PACKAGE.
814 ;;; If it's a *different* package, we should probably signal an error.
815 ;;; (perhaps (ERROR 'ANSI-WEIRDNESS ..):-)
816 (defun rename-package (package-designator name &optional (nicknames ()))
817 #!+sb-doc
818 "Changes the name and nicknames for a package."
819 (prog () :restart
820 (let ((package (find-undeleted-package-or-lose package-designator))
821 (name (stringify-package-designator name))
822 (found (find-package name))
823 (nicks (mapcar #'string nicknames)))
824 (unless (or (not found) (eq found package))
825 (signal-package-error name
826 "A package named ~S already exists." name))
827 (with-single-package-locked-error ()
828 (unless (and (string= name (package-name package))
829 (null (set-difference nicks (package-nicknames package)
830 :test #'string=)))
831 (assert-package-unlocked package "rename as ~A~@[ with nickname~P ~
832 ~{~A~^, ~}~]"
833 name (length nicks) nicks))
834 (with-package-names (names)
835 ;; Check for race conditions now that we have the lock.
836 (unless (eq package (find-package package-designator))
837 (go :restart))
838 ;; Do the renaming.
839 (remhash (package-%name package) names)
840 (dolist (n (package-%nicknames package))
841 (remhash n names))
842 (setf (package-%name package) name
843 (gethash name names) package
844 (package-%nicknames package) ()))
845 (%enter-new-nicknames package nicknames))
846 (return package))))
848 (defun delete-package (package-designator)
849 #!+sb-doc
850 "Delete the package designated by PACKAGE-DESIGNATOR from the package
851 system data structures."
852 (tagbody :restart
853 (let ((package (find-package package-designator)))
854 (cond ((not package)
855 ;; This continuable error is required by ANSI.
856 (signal-package-cerror
857 package-designator
858 "Ignore."
859 "There is no package named ~S." package-designator)
860 (return-from delete-package nil))
861 ((not (package-name package)) ; already deleted
862 (return-from delete-package nil))
864 (with-single-package-locked-error
865 (:package package "deleting package ~A" package)
866 (let ((use-list (package-used-by-list package)))
867 (when use-list
868 ;; This continuable error is specified by ANSI.
869 (signal-package-cerror
870 package
871 "Remove dependency in other packages."
872 "~@<Package ~S is used by package~P:~2I~_~S~@:>"
873 (package-name package)
874 (length use-list)
875 (mapcar #'package-name use-list))
876 (dolist (p use-list)
877 (unuse-package package p))))
878 #!+sb-package-locks
879 (dolist (p (package-implements-list package))
880 (remove-implementation-package package p))
881 (with-package-graph ()
882 ;; Check for races, restart if necessary.
883 (let ((package2 (find-package package-designator)))
884 (when (or (neq package package2) (package-used-by-list package2))
885 (go :restart)))
886 (dolist (used (package-use-list package))
887 (unuse-package used package))
888 (dolist (namer (package-%locally-nicknamed-by package))
889 (setf (package-%local-nicknames namer)
890 (delete package (package-%local-nicknames namer) :key #'cdr)))
891 (setf (package-%locally-nicknamed-by package) nil)
892 (dolist (cell (package-%local-nicknames package))
893 (let ((actual (cdr cell)))
894 (setf (package-%locally-nicknamed-by actual)
895 (delete package (package-%locally-nicknamed-by actual)))))
896 (setf (package-%local-nicknames package) nil)
897 ;; FIXME: lacking a way to advise UNINTERN that this package
898 ;; is pending deletion, a large package conses successively
899 ;; many smaller tables for no good reason.
900 (do-symbols (sym package)
901 (unintern sym package))
902 (with-package-names (names)
903 (remhash (package-name package) names)
904 (dolist (nick (package-nicknames package))
905 (remhash nick names))
906 (setf (package-%name package) nil
907 ;; Setting PACKAGE-%NAME to NIL is required in order to
908 ;; make PACKAGE-NAME return NIL for a deleted package as
909 ;; ANSI requires. Setting the other slots to NIL
910 ;; and blowing away the PACKAGE-HASHTABLES is just done
911 ;; for tidiness and to help the GC.
912 (package-%nicknames package) nil))
913 (setf (package-%use-list package) nil
914 (package-tables package) #()
915 (package-%shadowing-symbols package) nil
916 (package-internal-symbols package)
917 (make-package-hashtable 0)
918 (package-external-symbols package)
919 (make-package-hashtable 0)))
920 (return-from delete-package t)))))))
922 (defun list-all-packages ()
923 #!+sb-doc
924 "Return a list of all existing packages."
925 (let ((res ()))
926 (with-package-names (names)
927 (maphash (lambda (k v)
928 (declare (ignore k))
929 (pushnew v res))
930 names))
931 res))
933 (macrolet ((find/intern (function)
934 ;; Both FIND-SYMBOL* and INTERN* require a SIMPLE-STRING,
935 ;; but accept a LENGTH. Given a non-simple string,
936 ;; we need copy it only if the cumulative displacement
937 ;; into the underlying simple-string is nonzero.
938 ;; There are two things that can be improved
939 ;; about the generated code here:
940 ;; 1. if X is known to satisfy STRINGP (generally any rank-1 array),
941 ;; then testing SIMPLE-<base|character>-STRING-P should not
942 ;; re-test the lowtag. This is constrained by the backends,
943 ;; because there are no type vops that assume a known lowtag.
944 ;; 2. if X is known to satisfy VECTORP, then
945 ;; (NOT (ARRAY-HEADER-P)) implies SIMPLE-P, but the compiler
946 ;; does not actually know that, and generates a check.
947 ;; This is more of a front-end issue.
948 `(multiple-value-bind (name length)
949 (if (simple-string-p name)
950 (values name (length name))
951 (with-array-data ((name name) (start) (end)
952 :check-fill-pointer t)
953 (if (eql start 0)
954 (values name end)
955 (values (subseq name start end)
956 (- end start)))))
957 (truly-the
958 (values symbol (member :internal :external :inherited nil))
959 (,function name length
960 (find-undeleted-package-or-lose package))))))
962 (defun intern (name &optional (package (sane-package)))
963 #!+sb-doc
964 "Return a symbol in PACKAGE having the specified NAME, creating it
965 if necessary."
966 (find/intern intern*))
968 (defun find-symbol (name &optional (package (sane-package)))
969 #!+sb-doc
970 "Return the symbol named STRING in PACKAGE. If such a symbol is found
971 then the second value is :INTERNAL, :EXTERNAL or :INHERITED to indicate
972 how the symbol is accessible. If no symbol is found then both values
973 are NIL."
974 (find/intern find-symbol*)))
976 ;;; If the symbol named by the first LENGTH characters of NAME doesn't exist,
977 ;;; then create it, special-casing the keyword package.
978 (defun intern* (name length package &key no-copy)
979 (declare (simple-string name))
980 (multiple-value-bind (symbol where) (find-symbol* name length package)
981 (cond (where
982 (values symbol where))
984 ;; Let's try again with a lock: the common case has the
985 ;; symbol already interned, handled by the first leg of the
986 ;; COND, but in case another thread is interning in
987 ;; parallel we need to check after grabbing the lock.
988 (with-package-graph ()
989 (setf (values symbol where) (find-symbol* name length package))
990 (if where
991 (values symbol where)
992 (let ((symbol-name (cond (no-copy
993 (aver (= (length name) length))
994 name)
995 ((typep name '(simple-array nil (*)))
998 ;; This so that SUBSEQ is inlined,
999 ;; because we need it fixed for cold init.
1000 (string-dispatch
1001 ((simple-array base-char (*))
1002 (simple-array character (*)))
1003 name
1004 (declare (optimize speed))
1005 (subseq name 0 length))))))
1006 (with-single-package-locked-error
1007 (:package package "interning ~A" symbol-name)
1008 (let ((symbol (make-symbol symbol-name)))
1009 (%set-symbol-package symbol package)
1010 (cond
1011 ((eq package *keyword-package*)
1012 (%set-symbol-value symbol symbol)
1013 (add-symbol (package-external-symbols package) symbol))
1015 (add-symbol (package-internal-symbols package) symbol)))
1016 (values symbol nil))))))))))
1018 ;;; Check internal and external symbols, then scan down the list
1019 ;;; of hashtables for inherited symbols.
1020 (defun find-symbol* (string length package)
1021 (declare (simple-string string)
1022 (type index length))
1023 (let* ((hash (%sxhash-simple-substring string length))
1024 (ehash (entry-hash length hash)))
1025 (declare (type hash hash ehash))
1026 (with-symbol ((symbol) (package-internal-symbols package)
1027 string length hash ehash)
1028 (return-from find-symbol* (values symbol :internal)))
1029 (with-symbol ((symbol) (package-external-symbols package)
1030 string length hash ehash)
1031 (return-from find-symbol* (values symbol :external)))
1032 (let* ((tables (package-tables package))
1033 (n (length tables)))
1034 (unless (eql n 0)
1035 ;; Try the most-recently-used table, then others.
1036 ;; TABLES is treated as circular for this purpose.
1037 (let* ((mru (package-mru-table-index package))
1038 (start (if (< mru n) mru 0))
1039 (i start))
1040 (loop
1041 (with-symbol ((symbol) (locally (declare (optimize (safety 0)))
1042 (svref tables i))
1043 string length hash ehash)
1044 (setf (package-mru-table-index package) i)
1045 (return-from find-symbol* (values symbol :inherited)))
1046 (if (< (decf i) 0) (setq i (1- n)))
1047 (if (= i start) (return)))))))
1048 (values nil nil))
1050 ;;; Similar to FIND-SYMBOL, but only looks for an external symbol.
1051 ;;; Return the symbol and T if found, otherwise two NILs.
1052 ;;; This is used for fast name-conflict checking in this file and symbol
1053 ;;; printing in the printer.
1054 (defun find-external-symbol (string package)
1055 (declare (simple-string string))
1056 (let* ((length (length string))
1057 (hash (%sxhash-simple-string string))
1058 (ehash (entry-hash length hash)))
1059 (declare (type index length)
1060 (type hash hash))
1061 (with-symbol ((symbol) (package-external-symbols package)
1062 string length hash ehash)
1063 (return-from find-external-symbol (values symbol t))))
1064 (values nil nil))
1066 (defun print-symbol-with-prefix (stream symbol colon at)
1067 #!+sb-doc
1068 "For use with ~/: Write SYMBOL to STREAM as if it is not accessible from
1069 the current package."
1070 (declare (ignore colon at))
1071 ;; Only keywords should be accessible from the keyword package, and
1072 ;; keywords are always printed with colons, so this guarantees that the
1073 ;; symbol will not be printed without a prefix.
1074 (let ((*package* *keyword-package*))
1075 (write symbol :stream stream :escape t)))
1077 (define-condition name-conflict (reference-condition package-error)
1078 ((function :initarg :function :reader name-conflict-function)
1079 (datum :initarg :datum :reader name-conflict-datum)
1080 (symbols :initarg :symbols :reader name-conflict-symbols))
1081 (:default-initargs :references (list '(:ansi-cl :section (11 1 1 2 5))))
1082 (:report
1083 (lambda (c s)
1084 (format s "~@<~S ~S causes name-conflicts in ~S between the ~
1085 following symbols:~2I~@:_~
1086 ~{~/sb-impl::print-symbol-with-prefix/~^, ~}~:@>"
1087 (name-conflict-function c)
1088 (name-conflict-datum c)
1089 (package-error-package c)
1090 (name-conflict-symbols c)))))
1092 (defun name-conflict (package function datum &rest symbols)
1093 (flet ((importp (c)
1094 (declare (ignore c))
1095 (eq 'import function))
1096 (use-or-export-p (c)
1097 (declare (ignore c))
1098 (or (eq 'use-package function)
1099 (eq 'export function)))
1100 (old-symbol ()
1101 (car (remove datum symbols))))
1102 (let ((pname (package-name package)))
1103 (restart-case
1104 (error 'name-conflict :package package :symbols symbols
1105 :function function :datum datum)
1106 ;; USE-PACKAGE and EXPORT
1107 (keep-old ()
1108 :report (lambda (s)
1109 (ecase function
1110 (export
1111 (format s "Keep ~S accessible in ~A (shadowing ~S)."
1112 (old-symbol) pname datum))
1113 (use-package
1114 (format s "Keep symbols already accessible ~A (shadowing others)."
1115 pname))))
1116 :test use-or-export-p
1117 (dolist (s (remove-duplicates symbols :test #'string=))
1118 (shadow (symbol-name s) package)))
1119 (take-new ()
1120 :report (lambda (s)
1121 (ecase function
1122 (export
1123 (format s "Make ~S accessible in ~A (uninterning ~S)."
1124 datum pname (old-symbol)))
1125 (use-package
1126 (format s "Make newly exposed symbols accessible in ~A, ~
1127 uninterning old ones."
1128 pname))))
1129 :test use-or-export-p
1130 (dolist (s symbols)
1131 (when (eq s (find-symbol (symbol-name s) package))
1132 (unintern s package))))
1133 ;; IMPORT
1134 (shadowing-import-it ()
1135 :report (lambda (s)
1136 (format s "Shadowing-import ~S, uninterning ~S."
1137 datum (old-symbol)))
1138 :test importp
1139 (shadowing-import datum package))
1140 (dont-import-it ()
1141 :report (lambda (s)
1142 (format s "Don't import ~S, keeping ~S."
1143 datum
1144 (car (remove datum symbols))))
1145 :test importp)
1146 ;; General case. This is exposed via SB-EXT.
1147 (resolve-conflict (chosen-symbol)
1148 :report "Resolve conflict."
1149 :interactive
1150 (lambda ()
1151 (let* ((len (length symbols))
1152 (nlen (length (write-to-string len :base 10)))
1153 (*print-pretty* t))
1154 (format *query-io* "~&~@<Select a symbol to be made accessible in ~
1155 package ~A:~2I~@:_~{~{~V,' D. ~
1156 ~/sb-impl::print-symbol-with-prefix/~}~@:_~}~
1157 ~@:>"
1158 (package-name package)
1159 (loop for s in symbols
1160 for i upfrom 1
1161 collect (list nlen i s)))
1162 (loop
1163 (format *query-io* "~&Enter an integer (between 1 and ~D): " len)
1164 (finish-output *query-io*)
1165 (let ((i (parse-integer (read-line *query-io*) :junk-allowed t)))
1166 (when (and i (<= 1 i len))
1167 (return (list (nth (1- i) symbols))))))))
1168 (multiple-value-bind (package-symbol status)
1169 (find-symbol (symbol-name chosen-symbol) package)
1170 (let* ((accessiblep status) ; never NIL here
1171 (presentp (and accessiblep
1172 (not (eq :inherited status)))))
1173 (ecase function
1174 ((unintern)
1175 (if presentp
1176 (if (eq package-symbol chosen-symbol)
1177 (shadow (list package-symbol) package)
1178 (shadowing-import (list chosen-symbol) package))
1179 (shadowing-import (list chosen-symbol) package)))
1180 ((use-package export)
1181 (if presentp
1182 (if (eq package-symbol chosen-symbol)
1183 (shadow (list package-symbol) package) ; CLHS 11.1.1.2.5
1184 (if (eq (symbol-package package-symbol) package)
1185 (unintern package-symbol package) ; CLHS 11.1.1.2.5
1186 (shadowing-import (list chosen-symbol) package)))
1187 (shadowing-import (list chosen-symbol) package)))
1188 ((import)
1189 (if presentp
1190 (if (eq package-symbol chosen-symbol)
1191 nil ; re-importing the same symbol
1192 (shadowing-import (list chosen-symbol) package))
1193 (shadowing-import (list chosen-symbol) package)))))))))))
1195 ;;; If we are uninterning a shadowing symbol, then a name conflict can
1196 ;;; result, otherwise just nuke the symbol.
1197 (defun unintern (symbol &optional (package (sane-package)))
1198 #!+sb-doc
1199 "Makes SYMBOL no longer present in PACKAGE. If SYMBOL was present then T is
1200 returned, otherwise NIL. If PACKAGE is SYMBOL's home package, then it is made
1201 uninterned."
1202 (with-package-graph ()
1203 (let* ((package (find-undeleted-package-or-lose package))
1204 (name (symbol-name symbol))
1205 (shadowing-symbols (package-%shadowing-symbols package)))
1206 (declare (list shadowing-symbols))
1208 (with-single-package-locked-error ()
1209 (when (find-symbol name package)
1210 (assert-package-unlocked package "uninterning ~A" name))
1212 ;; If a name conflict is revealed, give us a chance to
1213 ;; shadowing-import one of the accessible symbols.
1214 (when (member symbol shadowing-symbols)
1215 (let ((cset ()))
1216 (dolist (p (package-%use-list package))
1217 (multiple-value-bind (s w) (find-external-symbol name p)
1218 (when w (pushnew s cset))))
1219 (when (cdr cset)
1220 (apply #'name-conflict package 'unintern symbol cset)
1221 (return-from unintern t)))
1222 (setf (package-%shadowing-symbols package)
1223 (remove symbol shadowing-symbols)))
1225 (multiple-value-bind (s w) (find-symbol name package)
1226 (cond ((not (eq symbol s)) nil)
1227 ((or (eq w :internal) (eq w :external))
1228 (nuke-symbol (if (eq w :internal)
1229 (package-internal-symbols package)
1230 (package-external-symbols package))
1231 name)
1232 (if (eq (symbol-package symbol) package)
1233 (%set-symbol-package symbol nil))
1235 (t nil)))))))
1237 ;;; Take a symbol-or-list-of-symbols and return a list, checking types.
1238 (defun symbol-listify (thing)
1239 (cond ((listp thing)
1240 (dolist (s thing)
1241 (unless (symbolp s)
1242 (signal-package-error nil
1243 "~S is not a symbol." s)))
1244 thing)
1245 ((symbolp thing) (list thing))
1247 (signal-package-error nil
1248 "~S is neither a symbol nor a list of symbols."
1249 thing))))
1251 (defun string-listify (thing)
1252 (mapcar #'string (if (listp thing)
1253 thing
1254 (list thing))))
1256 (defun export (symbols &optional (package (sane-package)))
1257 #!+sb-doc
1258 "Exports SYMBOLS from PACKAGE, checking that no name conflicts result."
1259 (with-package-graph ()
1260 (let ((package (find-undeleted-package-or-lose package))
1261 (symbols (symbol-listify symbols))
1262 (syms ()))
1263 ;; Punt any symbols that are already external.
1264 (dolist (sym symbols)
1265 (multiple-value-bind (s found)
1266 (find-external-symbol (symbol-name sym) package)
1267 (unless (or (and found (eq s sym)) (member sym syms))
1268 (push sym syms))))
1269 (with-single-package-locked-error ()
1270 (when syms
1271 (assert-package-unlocked package "exporting symbol~P ~{~A~^, ~}"
1272 (length syms) syms))
1273 ;; Find symbols and packages with conflicts.
1274 (let ((used-by (package-%used-by-list package)))
1275 (dolist (sym syms)
1276 (let ((name (symbol-name sym)))
1277 (dolist (p used-by)
1278 (multiple-value-bind (s w) (find-symbol name p)
1279 (when (and w
1280 (not (eq s sym))
1281 (not (member s (package-%shadowing-symbols p))))
1282 ;; Beware: the name conflict is in package P, not in
1283 ;; PACKAGE.
1284 (name-conflict p 'export sym sym s)))))))
1285 ;; Check that all symbols are accessible. If not, ask to import them.
1286 (let ((missing ())
1287 (imports ()))
1288 (dolist (sym syms)
1289 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1290 (cond ((not (and w (eq s sym)))
1291 (push sym missing))
1292 ((eq w :inherited)
1293 (push sym imports)))))
1294 (when missing
1295 (signal-package-cerror
1296 package
1297 (format nil "~S these symbols into the ~A package."
1298 'import (package-%name package))
1299 "~@<These symbols are not accessible in the ~A package:~2I~_~S~@:>"
1300 (package-%name package) missing)
1301 (import missing package))
1302 (import imports package))
1304 ;; And now, three pages later, we export the suckers.
1305 (let ((internal (package-internal-symbols package))
1306 (external (package-external-symbols package)))
1307 (dolist (sym syms)
1308 (add-symbol external sym)
1309 (nuke-symbol internal (symbol-name sym)))))
1310 t)))
1312 ;;; Check that all symbols are accessible, then move from external to internal.
1313 (defun unexport (symbols &optional (package (sane-package)))
1314 #!+sb-doc
1315 "Makes SYMBOLS no longer exported from PACKAGE."
1316 (with-package-graph ()
1317 (let ((package (find-undeleted-package-or-lose package))
1318 (symbols (symbol-listify symbols))
1319 (syms ()))
1320 (dolist (sym symbols)
1321 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1322 (cond ((or (not w) (not (eq s sym)))
1323 (signal-package-error
1324 package
1325 "~S is not accessible in the ~A package."
1326 sym (package-%name package)))
1327 ((eq w :external) (pushnew sym syms)))))
1328 (with-single-package-locked-error ()
1329 (when syms
1330 (assert-package-unlocked package "unexporting symbol~P ~{~A~^, ~}"
1331 (length syms) syms))
1332 (let ((internal (package-internal-symbols package))
1333 (external (package-external-symbols package)))
1334 (dolist (sym syms)
1335 (add-symbol internal sym)
1336 (nuke-symbol external (symbol-name sym)))))
1337 t)))
1339 ;;; Check for name conflict caused by the import and let the user
1340 ;;; shadowing-import if there is.
1341 (defun import (symbols &optional (package (sane-package)))
1342 #!+sb-doc
1343 "Make SYMBOLS accessible as internal symbols in PACKAGE. If a symbol is
1344 already accessible then it has no effect. If a name conflict would result from
1345 the importation, then a correctable error is signalled."
1346 (with-package-graph ()
1347 (let* ((package (find-undeleted-package-or-lose package))
1348 (symbols (symbol-listify symbols))
1349 (homeless (remove-if #'symbol-package symbols))
1350 (syms ()))
1351 (with-single-package-locked-error ()
1352 (dolist (sym symbols)
1353 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1354 (cond ((not w)
1355 (let ((found (member sym syms :test #'string=)))
1356 (if found
1357 (when (not (eq (car found) sym))
1358 (setf syms (remove (car found) syms))
1359 (name-conflict package 'import sym sym (car found)))
1360 (push sym syms))))
1361 ((not (eq s sym))
1362 (name-conflict package 'import sym sym s))
1363 ((eq w :inherited) (push sym syms)))))
1364 (when (or homeless syms)
1365 (let ((union (delete-duplicates (append homeless syms))))
1366 (assert-package-unlocked package "importing symbol~P ~{~A~^, ~}"
1367 (length union) union)))
1368 ;; Add the new symbols to the internal hashtable.
1369 (let ((internal (package-internal-symbols package)))
1370 (dolist (sym syms)
1371 (add-symbol internal sym)))
1372 ;; If any of the symbols are uninterned, make them be owned by PACKAGE.
1373 (dolist (sym homeless)
1374 (%set-symbol-package sym package))
1375 t))))
1377 ;;; If a conflicting symbol is present, unintern it, otherwise just
1378 ;;; stick the symbol in.
1379 (defun shadowing-import (symbols &optional (package (sane-package)))
1380 #!+sb-doc
1381 "Import SYMBOLS into package, disregarding any name conflict. If
1382 a symbol of the same name is present, then it is uninterned."
1383 (with-package-graph ()
1384 (let* ((package (find-undeleted-package-or-lose package))
1385 (internal (package-internal-symbols package))
1386 (symbols (symbol-listify symbols))
1387 (lock-asserted-p nil))
1388 (with-single-package-locked-error ()
1389 (dolist (sym symbols)
1390 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1391 (unless (or lock-asserted-p
1392 (and (eq s sym)
1393 (member s (package-shadowing-symbols package))))
1394 (assert-package-unlocked package "shadowing-importing symbol~P ~
1395 ~{~A~^, ~}" (length symbols) symbols)
1396 (setf lock-asserted-p t))
1397 (unless (and w (not (eq w :inherited)) (eq s sym))
1398 (when (or (eq w :internal) (eq w :external))
1399 ;; If it was shadowed, we don't want UNINTERN to flame out...
1400 (setf (package-%shadowing-symbols package)
1401 (remove s (the list (package-%shadowing-symbols package))))
1402 (unintern s package))
1403 (add-symbol internal sym))
1404 (pushnew sym (package-%shadowing-symbols package)))))))
1407 (defun shadow (symbols &optional (package (sane-package)))
1408 #!+sb-doc
1409 "Make an internal symbol in PACKAGE with the same name as each of the
1410 specified SYMBOLS. If a symbol with the given name is already present in
1411 PACKAGE, then the existing symbol is placed in the shadowing symbols list if
1412 it is not already present."
1413 (with-package-graph ()
1414 (let* ((package (find-undeleted-package-or-lose package))
1415 (internal (package-internal-symbols package))
1416 (symbols (string-listify symbols))
1417 (lock-asserted-p nil))
1418 (flet ((present-p (w)
1419 (and w (not (eq w :inherited)))))
1420 (with-single-package-locked-error ()
1421 (dolist (name symbols)
1422 (multiple-value-bind (s w) (find-symbol name package)
1423 (unless (or lock-asserted-p
1424 (and (present-p w)
1425 (member s (package-shadowing-symbols package))))
1426 (assert-package-unlocked package "shadowing symbol~P ~{~A~^, ~}"
1427 (length symbols) symbols)
1428 (setf lock-asserted-p t))
1429 (unless (present-p w)
1430 (setq s (make-symbol name))
1431 (%set-symbol-package s package)
1432 (add-symbol internal s))
1433 (pushnew s (package-%shadowing-symbols package))))))))
1436 ;;; Do stuff to use a package, with all kinds of fun name-conflict checking.
1437 (defun use-package (packages-to-use &optional (package (sane-package)))
1438 #!+sb-doc
1439 "Add all the PACKAGES-TO-USE to the use list for PACKAGE so that the
1440 external symbols of the used packages are accessible as internal symbols in
1441 PACKAGE."
1442 (with-package-graph ()
1443 (let ((packages (package-listify packages-to-use))
1444 (package (find-undeleted-package-or-lose package)))
1446 ;; Loop over each package, USE'ing one at a time...
1447 (with-single-package-locked-error ()
1448 (dolist (pkg packages)
1449 (unless (member pkg (package-%use-list package))
1450 (assert-package-unlocked package "using package~P ~{~A~^, ~}"
1451 (length packages) packages)
1452 (let ((shadowing-symbols (package-%shadowing-symbols package))
1453 (use-list (package-%use-list package)))
1455 ;; If the number of symbols already accessible is less
1456 ;; than the number to be inherited then it is faster to
1457 ;; run the test the other way. This is particularly
1458 ;; valuable in the case of a new package USEing
1459 ;; COMMON-LISP.
1460 (cond
1461 ((< (+ (package-internal-symbol-count package)
1462 (package-external-symbol-count package)
1463 (let ((res 0))
1464 (dolist (p use-list res)
1465 (incf res (package-external-symbol-count p)))))
1466 (package-external-symbol-count pkg))
1467 (do-symbols (sym package)
1468 (multiple-value-bind (s w)
1469 (find-external-symbol (symbol-name sym) pkg)
1470 (when (and w
1471 (not (eq s sym))
1472 (not (member sym shadowing-symbols)))
1473 (name-conflict package 'use-package pkg sym s))))
1474 (dolist (p use-list)
1475 (do-external-symbols (sym p)
1476 (multiple-value-bind (s w)
1477 (find-external-symbol (symbol-name sym) pkg)
1478 (when (and w
1479 (not (eq s sym))
1480 (not (member
1481 (find-symbol (symbol-name sym) package)
1482 shadowing-symbols)))
1483 (name-conflict package 'use-package pkg sym s))))))
1485 (do-external-symbols (sym pkg)
1486 (multiple-value-bind (s w)
1487 (find-symbol (symbol-name sym) package)
1488 (when (and w
1489 (not (eq s sym))
1490 (not (member s shadowing-symbols)))
1491 (name-conflict package 'use-package pkg sym s)))))))
1493 (push pkg (package-%use-list package))
1494 (setf (package-tables package)
1495 (let ((tbls (package-tables package)))
1496 (replace (make-array (1+ (length tbls))
1497 :initial-element (package-external-symbols pkg))
1498 tbls)))
1499 (push package (package-%used-by-list pkg)))))))
1502 (defun unuse-package (packages-to-unuse &optional (package (sane-package)))
1503 #!+sb-doc
1504 "Remove PACKAGES-TO-UNUSE from the USE list for PACKAGE."
1505 (with-package-graph ()
1506 (let ((package (find-undeleted-package-or-lose package))
1507 (packages (package-listify packages-to-unuse)))
1508 (with-single-package-locked-error ()
1509 (dolist (p packages)
1510 (when (member p (package-use-list package))
1511 (assert-package-unlocked package "unusing package~P ~{~A~^, ~}"
1512 (length packages) packages))
1513 (setf (package-%use-list package)
1514 (remove p (the list (package-%use-list package))))
1515 (setf (package-tables package)
1516 (delete (package-external-symbols p)
1517 (package-tables package)))
1518 (setf (package-%used-by-list p)
1519 (remove package (the list (package-%used-by-list p))))))
1520 t)))
1522 (defun find-all-symbols (string-or-symbol)
1523 #!+sb-doc
1524 "Return a list of all symbols in the system having the specified name."
1525 (let ((string (string string-or-symbol))
1526 (res ()))
1527 (with-package-names (names)
1528 (maphash (lambda (k v)
1529 (declare (ignore k))
1530 (multiple-value-bind (s w) (find-symbol string v)
1531 (when w (pushnew s res))))
1532 names))
1533 res))
1535 ;;;; APROPOS and APROPOS-LIST
1537 (defun briefly-describe-symbol (symbol)
1538 (fresh-line)
1539 (prin1 symbol)
1540 (when (boundp symbol)
1541 (write-string " (bound)"))
1542 (when (fboundp symbol)
1543 (write-string " (fbound)")))
1545 (defun apropos-list (string-designator
1546 &optional
1547 package-designator
1548 external-only)
1549 #!+sb-doc
1550 "Like APROPOS, except that it returns a list of the symbols found instead
1551 of describing them."
1552 (if package-designator
1553 (let ((package (find-undeleted-package-or-lose package-designator))
1554 (string (stringify-string-designator string-designator))
1555 (result nil))
1556 (do-symbols (symbol package)
1557 (when (and (or (not external-only)
1558 (and (eq (symbol-package symbol) package)
1559 (eq (nth-value 1 (find-symbol (symbol-name symbol)
1560 package))
1561 :external)))
1562 (search string (symbol-name symbol) :test #'char-equal))
1563 (push symbol result)))
1564 (sort result #'string-lessp))
1565 (mapcan (lambda (package)
1566 (apropos-list string-designator package external-only))
1567 (sort (list-all-packages) #'string-lessp :key #'package-name))))
1569 (defun apropos (string-designator &optional package external-only)
1570 #!+sb-doc
1571 "Briefly describe all symbols which contain the specified STRING.
1572 If PACKAGE is supplied then only describe symbols present in
1573 that package. If EXTERNAL-ONLY then only describe
1574 external symbols in the specified package."
1575 ;; Implementing this in terms of APROPOS-LIST keeps things simple at the cost
1576 ;; of some unnecessary consing; and the unnecessary consing shouldn't be an
1577 ;; issue, since this function is is only useful interactively anyway, and
1578 ;; we can cons and GC a lot faster than the typical user can read..
1579 (dolist (symbol (apropos-list string-designator package external-only))
1580 (briefly-describe-symbol symbol))
1581 (values))
1583 ;;;; final initialization
1585 ;;;; Due to the relative difficulty - but not impossibility - of manipulating
1586 ;;;; package-hashtables in the cross-compilation host, all interning operations
1587 ;;;; are delayed until cold-init.
1588 ;;;; The cold loader (GENESIS) set *!INITIAL-SYMBOLS* to the target
1589 ;;;; representation of the hosts's *COLD-PACKAGE-SYMBOLS*.
1590 ;;;; The shape of this list is ((package . (externals . internals)) ...)
1591 (defvar *!initial-symbols*)
1593 (defun !package-cold-init ()
1594 (setf *package-graph-lock* (sb!thread:make-mutex :name "Package Graph Lock")
1595 *package-names* (make-hash-table :test 'equal :synchronized t))
1596 (with-package-names (names)
1597 (dolist (spec *!initial-symbols*)
1598 (let ((pkg (car spec)) (symbols (cdr spec)))
1599 ;; the symbol MAKE-TABLE wouldn't magically disappear,
1600 ;; though its only use be to name an FLET in a function
1601 ;; hanging on an otherwise uninternable symbol. strange but true :-(
1602 (flet ((!make-table (input)
1603 (let ((table (make-package-hashtable
1604 (length (the simple-vector input)))))
1605 (dovector (symbol input table)
1606 (add-symbol table symbol)))))
1607 (setf (package-external-symbols pkg) (!make-table (car symbols))
1608 (package-internal-symbols pkg) (!make-table (cdr symbols))))
1609 (setf (package-%shadowing-symbols pkg) nil
1610 (package-%local-nicknames pkg) nil
1611 (package-%locally-nicknamed-by pkg) nil
1612 (package-source-location pkg) nil
1613 (gethash (package-%name pkg) names) pkg)
1614 (%enter-new-nicknames pkg (package-%nicknames pkg))
1615 #!+sb-package-locks
1616 (setf (package-lock pkg) nil
1617 (package-%implementation-packages pkg) nil))))
1619 ;; pass 2 - set the 'tables' slots only after all tables have been made
1620 (dolist (spec *!initial-symbols*)
1621 (let ((pkg (car spec)))
1622 (setf (package-tables pkg)
1623 (map 'vector #'package-external-symbols (package-%use-list pkg)))))
1625 (/show0 "about to MAKUNBOUND *!INITIAL-SYMBOLS*")
1626 (%makunbound '*!initial-symbols*) ; (so that it gets GCed)
1628 ;; For the kernel core image wizards, set the package to *CL-PACKAGE*.
1630 ;; FIXME: We should just set this to (FIND-PACKAGE
1631 ;; "COMMON-LISP-USER") once and for all here, instead of setting it
1632 ;; once here and resetting it later.
1633 (setq *package* *cl-package*))