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