1 ;;;; PACKAGEs and stuff like that
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.
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.
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 (!begin-collecting-cold-init-forms)
29 (/show0 "entering !PACKAGE-COLD-INIT"))
33 ;;;; ...this could still use work, but the basic idea is:
35 ;;;; *PACKAGE-GRAPH-LOCK* is held via WITH-PACKAGE-GRAPH while working on
36 ;;;; package graph, including package -> package links, and interning and
37 ;;;; uninterning symbols.
39 ;;;; Hash-table lock on *PACKAGE-NAMES* is held via WITH-PACKAGE-NAMES while
40 ;;;; frobbing name -> package associations.
42 ;;;; There should be no deadlocks due to ordering issues between these two, as
43 ;;;; the latter is only held over operations guaranteed to terminate in finite
46 ;;;; Errors may be signalled while holding on to the *PACKAGE-GRAPH-LOCK*,
47 ;;;; which can still lead to pretty damned inconvenient situations -- but
48 ;;;; since FIND-PACKAGE, FIND-SYMBOL from other threads isn't blocked by this,
49 ;;;; the situation isn't *quite* hopeless.
51 ;;;; A better long-term solution seems to be in splitting the granularity of
52 ;;;; the *PACKAGE-GRAPH-LOCK* down: for interning a per-package lock should be
53 ;;;; sufficient, though interaction between parallel intern and use-package
54 ;;;; needs to be considered with some care.
56 (defvar *package-graph-lock*)
58 (setf *package-graph-lock* (sb!thread:make-mutex :name "Package Graph Lock")))
60 (defun call-with-package-graph (function)
61 (declare (function function))
62 ;; FIXME: Since name conflicts can be signalled while holding the
63 ;; mutex, user code can be run leading to lock ordering problems.
64 (sb!thread:with-recursive-lock (*package-graph-lock*)
67 ;;; a map from package names to packages
68 (defvar *package-names*)
69 (declaim (type hash-table *package-names*))
71 (setf *package-names* (make-hash-table :test 'equal :synchronized t)))
73 (defmacro with-package-names ((names &key) &body body)
74 `(let ((,names *package-names*))
75 (with-locked-system-table (,names)
78 ;;;; PACKAGE-HASHTABLE stuff
80 (def!method print-object ((table package-hashtable) stream)
81 (declare (type stream stream))
82 (print-unreadable-object (table stream :type t)
84 ":SIZE ~S :FREE ~S :DELETED ~S"
85 (package-hashtable-size table)
86 (package-hashtable-free table)
87 (package-hashtable-deleted table))))
89 ;;; the maximum load factor we allow in a package hashtable
90 (defconstant +package-rehash-threshold+ 0.75)
92 ;;; the load factor desired for a package hashtable when writing a
94 (defconstant +package-hashtable-image-load-factor+ 0.5)
96 ;;; Make a package hashtable having a prime number of entries at least
97 ;;; as great as (/ SIZE +PACKAGE-REHASH-THRESHOLD+). If RES is supplied,
98 ;;; then it is destructively modified to produce the result. This is
99 ;;; useful when changing the size, since there are many pointers to
101 ;;; Actually, the smallest table built here has three entries. This
102 ;;; is necessary because the double hashing step size is calculated
103 ;;; using a division by the table size minus two.
104 (defun make-or-remake-package-hashtable (size
107 (flet ((actual-package-hashtable-size (size)
108 (loop for n of-type fixnum
109 from (logior (ceiling size +package-rehash-threshold+) 1)
111 when (positive-primep n) return n)))
112 (let* ((n (actual-package-hashtable-size size))
113 (size (truncate (* n +package-rehash-threshold+)))
114 (table (make-array n))
116 :element-type '(unsigned-byte 8)
117 :initial-element 0)))
119 (setf (package-hashtable-table res) table
120 (package-hashtable-hash res) hash
121 (package-hashtable-size res) size
122 (package-hashtable-free res) size
123 (package-hashtable-deleted res) 0)
124 (setf res (%make-package-hashtable table hash size)))
127 ;;; Destructively resize TABLE to have room for at least SIZE entries
128 ;;; and rehash its existing entries.
129 (defun resize-package-hashtable (table size)
130 (let* ((vec (package-hashtable-table table))
131 (hash (package-hashtable-hash table))
133 (make-or-remake-package-hashtable size table)
135 (when (> (aref hash i) 1)
136 (add-symbol table (svref vec i))))))
138 ;;;; package locking operations, built conditionally on :sb-package-locks
142 (defun package-locked-p (package)
144 "Returns T when PACKAGE is locked, NIL otherwise. Signals an error
145 if PACKAGE doesn't designate a valid package."
146 (package-lock (find-undeleted-package-or-lose package)))
148 (defun lock-package (package)
150 "Locks PACKAGE and returns T. Has no effect if PACKAGE was already
151 locked. Signals an error if PACKAGE is not a valid package designator"
152 (setf (package-lock (find-undeleted-package-or-lose package)) t))
154 (defun unlock-package (package)
156 "Unlocks PACKAGE and returns T. Has no effect if PACKAGE was already
157 unlocked. Signals an error if PACKAGE is not a valid package designator."
158 (setf (package-lock (find-undeleted-package-or-lose package)) nil)
161 (defun package-implemented-by-list (package)
163 "Returns a list containing the implementation packages of
164 PACKAGE. Signals an error if PACKAGE is not a valid package designator."
165 (package-%implementation-packages (find-undeleted-package-or-lose package)))
167 (defun package-implements-list (package)
169 "Returns the packages that PACKAGE is an implementation package
170 of. Signals an error if PACKAGE is not a valid package designator."
171 (let ((package (find-undeleted-package-or-lose package)))
172 (loop for x in (list-all-packages)
173 when (member package (package-%implementation-packages x))
176 (defun add-implementation-package (packages-to-add
177 &optional (package *package*))
179 "Adds PACKAGES-TO-ADD as implementation packages of PACKAGE. Signals
180 an error if PACKAGE or any of the PACKAGES-TO-ADD is not a valid
182 (let ((package (find-undeleted-package-or-lose package))
183 (packages-to-add (package-listify packages-to-add)))
184 (setf (package-%implementation-packages package)
185 (union (package-%implementation-packages package)
186 (mapcar #'find-undeleted-package-or-lose packages-to-add)))))
188 (defun remove-implementation-package (packages-to-remove
189 &optional (package *package*))
191 "Removes PACKAGES-TO-REMOVE from the implementation packages of
192 PACKAGE. Signals an error if PACKAGE or any of the PACKAGES-TO-REMOVE
193 is not a valid package designator."
194 (let ((package (find-undeleted-package-or-lose package))
195 (packages-to-remove (package-listify packages-to-remove)))
196 (setf (package-%implementation-packages package)
198 (package-%implementation-packages package)
199 (mapcar #'find-undeleted-package-or-lose packages-to-remove)))))
201 (defmacro with-unlocked-packages ((&rest packages) &body forms)
203 "Unlocks PACKAGES for the dynamic scope of the body. Signals an
204 error if any of PACKAGES is not a valid package designator."
205 (with-unique-names (unlocked-packages)
206 `(let (,unlocked-packages)
209 (dolist (p ',packages)
210 (when (package-locked-p p)
211 (push p ,unlocked-packages)
214 (dolist (p ,unlocked-packages)
215 (when (find-package p)
216 (lock-package p)))))))
218 (defun package-lock-violation (package &key (symbol nil symbol-p)
219 format-control format-arguments)
220 (let* ((restart :continue)
221 (cl-violation-p (eq package *cl-package*))
223 (append (list (if symbol-p
224 'symbol-package-locked-error
225 'package-locked-error)
227 :format-control format-control
228 :format-arguments format-arguments)
229 (when symbol-p (list :symbol symbol))
231 (append '((:sbcl :node "Package Locks"))
233 '((:ansi-cl :section (11 1 2 1 2)))))))))
235 (apply #'cerror "Ignore the package lock." error-arguments)
237 :report "Ignore all package locks in the context of this operation."
238 (setf restart :ignore-all))
240 :report "Unlock the package."
241 (setf restart :unlock-package)))
244 (pushnew package *ignored-package-locks*))
246 (setf *ignored-package-locks* t))
248 (unlock-package package)))))
250 (defun package-lock-violation-p (package &optional (symbol nil symbolp))
251 ;; KLUDGE: (package-lock package) needs to be before
252 ;; comparison to *package*, since during cold init this gets
253 ;; called before *package* is bound -- but no package should
254 ;; be locked at that point.
256 (package-lock package)
257 ;; In package or implementation package
258 (not (or (eq package *package*)
259 (member *package* (package-%implementation-packages package))))
261 (not (eq t *ignored-package-locks*))
262 (or (eq :invalid *ignored-package-locks*)
263 (not (member package *ignored-package-locks*)))
264 ;; declarations for symbols
265 (not (and symbolp (member symbol (disabled-package-locks))))))
267 (defun disabled-package-locks ()
268 (if (boundp 'sb!c::*lexenv*)
269 (sb!c::lexenv-disabled-package-locks sb!c::*lexenv*)
270 sb!c::*disabled-package-locks*))
274 ;;;; more package-locking these are NOPs unless :sb-package-locks is
275 ;;;; in target features. Cross-compiler NOPs for these are in cross-misc.
277 ;;; The right way to establish a package lock context is
278 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR, defined in early-package.lisp
280 ;;; Must be used inside the dynamic contour established by
281 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR
282 (defun assert-package-unlocked (package &optional format-control
283 &rest format-arguments)
285 (declare (ignore format-control format-arguments))
287 (when (package-lock-violation-p package)
288 (package-lock-violation package
289 :format-control format-control
290 :format-arguments format-arguments))
293 ;;; Must be used inside the dynamic contour established by
294 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR.
296 ;;; FIXME: Maybe we should establish such contours for he toplevel
297 ;;; and others, so that %set-fdefinition and others could just use
299 (defun assert-symbol-home-package-unlocked (name format)
301 (declare (ignore format))
303 (let* ((symbol (etypecase name
305 (list (if (and (consp (cdr name))
306 (eq 'setf (first name)))
308 ;; Skip lists of length 1, single conses and
309 ;; (class-predicate foo), etc.
310 ;; FIXME: MOP and package-lock
311 ;; interaction needs to be thought about.
313 assert-symbol-home-package-unlocked
315 (package (symbol-package symbol)))
316 (when (package-lock-violation-p package symbol)
317 (package-lock-violation package
319 :format-control format
320 :format-arguments (list name))))
324 ;;;; miscellaneous PACKAGE operations
326 (def!method print-object ((package package) stream)
327 (let ((name (package-%name package)))
329 (print-unreadable-object (package stream :type t)
331 (print-unreadable-object (package stream :type t :identity t)
332 (write-string "(deleted)" stream)))))
334 ;;; ANSI says (in the definition of DELETE-PACKAGE) that these, and
335 ;;; most other operations, are unspecified for deleted packages. We
336 ;;; just do the easy thing and signal errors in that case.
337 (macrolet ((def (ext real)
338 `(defun ,ext (package-designator)
339 (,real (find-undeleted-package-or-lose package-designator)))))
340 (def package-nicknames package-%nicknames)
341 (def package-use-list package-%use-list)
342 (def package-used-by-list package-%used-by-list)
343 (def package-shadowing-symbols package-%shadowing-symbols))
345 (defun package-local-nicknames (package-designator)
346 "Returns an alist of \(local-nickname . actual-package) describing the
347 nicknames local to the designated package.
349 When in the designated package, calls to FIND-PACKAGE with the any of the
350 local-nicknames will return the corresponding actual-package instead. This
351 also affects all implied calls to FIND-PACKAGE, including those performed by
354 When printing a package prefix for a symbol with a package local nickname, the
355 local nickname is used instead of the real name in order to preserve
356 print-read consistency.
358 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
359 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
361 Experimental: interface subject to change."
363 (package-%local-nicknames
364 (find-undeleted-package-or-lose package-designator))))
366 (defun signal-package-error (package format-control &rest format-args)
367 (error 'simple-package-error
369 :format-control format-control
370 :format-arguments format-args))
372 (defun signal-package-cerror (package continue-string
373 format-control &rest format-args)
374 (cerror continue-string
375 'simple-package-error
377 :format-control format-control
378 :format-arguments format-args))
380 (defun package-locally-nicknamed-by-list (package-designator)
381 "Returns a list of packages which have a local nickname for the designated
384 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
385 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
387 Experimental: interface subject to change."
389 (package-%locally-nicknamed-by
390 (find-undeleted-package-or-lose package-designator))))
392 (defun add-package-local-nickname (local-nickname actual-package
393 &optional (package-designator (sane-package)))
394 "Adds LOCAL-NICKNAME for ACTUAL-PACKAGE in the designated package, defaulting
395 to current package. LOCAL-NICKNAME must be a string designator, and
396 ACTUAL-PACKAGE must be a package designator.
398 Returns the designated package.
400 Signals a continuable error if LOCAL-NICKNAME is already a package local
401 nickname for a different package, or if LOCAL-NICKNAME is one of \"CL\",
402 \"COMMON-LISP\", or, \"KEYWORD\", or if LOCAL-NICKNAME is a global name or
403 nickname for the package to which the nickname would be added.
405 When in the designated package, calls to FIND-PACKAGE with the LOCAL-NICKNAME
406 will return the package the designated ACTUAL-PACKAGE instead. This also
407 affects all implied calls to FIND-PACKAGE, including those performed by the
410 When printing a package prefix for a symbol with a package local nickname,
411 local nickname is used instead of the real name in order to preserve
412 print-read consistency.
414 See also: PACKAGE-LOCAL-NICKNAMES, PACKAGE-LOCALLY-NICKNAMED-BY-LIST,
415 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES.
417 Experimental: interface subject to change."
418 (let* ((nick (string local-nickname))
419 (actual (find-package-using-package actual-package nil))
420 (package (find-undeleted-package-or-lose package-designator))
421 (existing (package-%local-nicknames package))
422 (cell (assoc nick existing :test #'string=)))
424 (signal-package-error
426 "The name ~S does not designate any package."
428 (unless (package-name actual)
429 (signal-package-error
431 "Cannot add ~A as local nickname for a deleted package: ~S"
433 (with-single-package-locked-error
434 (:package package "adding ~A as a local nickname for ~A"
436 (when (member nick '("CL" "COMMON-LISP" "KEYWORD") :test #'string=)
437 (signal-package-cerror
439 "Continue, use it as local nickname anyways."
440 "Attempt to use ~A as a package local nickname (for ~A)."
441 nick (package-name actual)))
442 (when (string= nick (package-name package))
443 (signal-package-cerror
445 "Continue, use it as a local nickname anyways."
446 "Attempt to use ~A as a package local nickname (for ~A) in ~
447 package named globally ~A."
448 nick (package-name actual) nick))
449 (when (member nick (package-nicknames package) :test #'string=)
450 (signal-package-cerror
452 "Continue, use it as a local nickname anyways."
453 "Attempt to use ~A as a package local nickname (for ~A) in ~
454 package nicknamed globally ~A."
455 nick (package-name actual) nick))
456 (when (and cell (neq actual (cdr cell)))
458 (signal-package-error
460 "~@<Cannot add ~A as local nickname for ~A in ~A: ~
461 already nickname for ~A.~:@>"
462 nick (package-name actual)
463 (package-name package) (package-name (cdr cell)))
466 (format s "Keep ~A as local nicname for ~A."
467 nick (package-name (cdr cell)))))
470 (format s "Use ~A as local nickname for ~A instead."
471 nick (package-name actual)))
472 (let ((old (cdr cell)))
473 (with-package-graph ()
474 (setf (package-%locally-nicknamed-by old)
475 (delete package (package-%locally-nicknamed-by old)))
476 (push package (package-%locally-nicknamed-by actual))
477 (setf (cdr cell) actual)))))
478 (return-from add-package-local-nickname package))
480 (with-package-graph ()
481 (push (cons nick actual) (package-%local-nicknames package))
482 (push package (package-%locally-nicknamed-by actual))))
485 (defun remove-package-local-nickname (old-nickname
486 &optional (package-designator (sane-package)))
487 "If the designated package had OLD-NICKNAME as a local nickname for
488 another package, it is removed. Returns true if the nickname existed and was
489 removed, and NIL otherwise.
491 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
492 PACKAGE-LOCALLY-NICKNAMED-BY-LIST, and the DEFPACKAGE option :LOCAL-NICKNAMES.
494 Experimental: interface subject to change."
495 (let* ((nick (string old-nickname))
496 (package (find-undeleted-package-or-lose package-designator))
497 (existing (package-%local-nicknames package))
498 (cell (assoc nick existing :test #'string=)))
500 (with-single-package-locked-error
501 (:package package "removing local nickname ~A for ~A"
503 (with-package-graph ()
504 (let ((old (cdr cell)))
505 (setf (package-%local-nicknames package) (delete cell existing))
506 (setf (package-%locally-nicknamed-by old)
507 (delete package (package-%locally-nicknamed-by old)))))
510 (defun %package-hashtable-symbol-count (table)
511 (let ((size (the fixnum
512 (- (package-hashtable-size table)
513 (package-hashtable-deleted table)))))
515 (- size (package-hashtable-free table)))))
517 (defun package-internal-symbol-count (package)
518 (%package-hashtable-symbol-count (package-internal-symbols package)))
520 (defun package-external-symbol-count (package)
521 (%package-hashtable-symbol-count (package-external-symbols package)))
523 (defvar *package* (error "*PACKAGE* should be initialized in cold load!")
524 #!+sb-doc "the current package")
525 ;;; FIXME: should be declared of type PACKAGE, with no NIL init form,
526 ;;; after I get around to cleaning up DOCUMENTATION
528 ;;; This magical variable is T during initialization so that
529 ;;; USE-PACKAGE's of packages that don't yet exist quietly win. Such
530 ;;; packages are thrown onto the list *DEFERRED-USE-PACKAGES* so that
531 ;;; this can be fixed up later.
533 ;;; FIXME: This could be cleaned up the same way I do it in my package
534 ;;; hacking when setting up the cross-compiler. Then we wouldn't have
535 ;;; this extraneous global variable and annoying runtime tests on
536 ;;; package operations. (*DEFERRED-USE-PACKAGES* would also go away.)
537 (defvar *in-package-init*)
539 ;;; pending USE-PACKAGE arguments saved up while *IN-PACKAGE-INIT* is true
540 (defvar *!deferred-use-packages*)
542 (setf *!deferred-use-packages* nil))
544 (define-condition bootstrap-package-not-found (condition)
545 ((name :initarg :name :reader bootstrap-package-name)))
546 (defun debootstrap-package (&optional condition)
548 (find-restart-or-control-error 'debootstrap-package condition)))
550 (defun find-package (package-designator)
551 "If PACKAGE-DESIGNATOR is a package, it is returned. Otherwise PACKAGE-DESIGNATOR
552 must be a string designator, in which case the package it names is located and returned.
554 As an SBCL extension, the current package may effect the way a package name is
555 resolved: if the current package has local nicknames specified, package names
556 matching those are resolved to the packages associated with them instead.
561 (defpackage :example (:use :cl) (:local-nicknames (:x :a)))
562 (let ((*package* (find-package :example)))
563 (find-package :x)) => #<PACKAGE A>
565 See also: ADD-PACKAGE-LOCAL-NICKNAME, PACKAGE-LOCAL-NICKNAMES,
566 REMOVE-PACKAGE-LOCAL-NICKNAME, and the DEFPACKAGE option :LOCAL-NICKNAMES."
567 (find-package-using-package package-designator
568 (when (boundp '*package*)
571 ;;; This is undocumented and unexported for now, but the idea is that by
572 ;;; making this a generic function then packages with custom package classes
573 ;;; could hook into this to provide their own resolution.
574 (defun find-package-using-package (package-designator base)
575 (flet ((find-package-from-string (string)
576 (declare (type string string))
577 (let* ((nicknames (when base
578 (package-%local-nicknames base)))
579 (nicknamed (when nicknames
580 (cdr (assoc string nicknames :test #'string=))))
581 (packageoid (or nicknamed (gethash string *package-names*))))
582 (if (and (null packageoid)
583 (not *in-package-init*) ; KLUDGE
584 (let ((mismatch (mismatch "SB!" string)))
585 (and mismatch (= mismatch 3))))
587 (signal 'bootstrap-package-not-found :name string)
588 (debootstrap-package ()
589 (if (string= string "SB!XC")
590 (find-package "COMMON-LISP")
592 (substitute #\- #\! string :count 1)))))
594 (typecase package-designator
595 (package package-designator)
596 (symbol (find-package-from-string (symbol-name package-designator)))
597 (string (find-package-from-string package-designator))
598 (character (find-package-from-string (string package-designator)))
599 (t (error 'type-error
600 :datum package-designator
601 :expected-type '(or character package string symbol))))))
603 ;;; Return a list of packages given a package designator or list of
604 ;;; package designators, or die trying.
605 (defun package-listify (thing)
607 (dolist (thing (if (listp thing) thing (list thing)) res)
608 (push (find-undeleted-package-or-lose thing) res))))
610 ;;; Make a package name into a simple-string.
611 (defun package-namify (n)
612 (stringify-package-designator n))
614 ;;; ANSI specifies (in the definition of DELETE-PACKAGE) that PACKAGE-NAME
615 ;;; returns NIL (not an error) for a deleted package, so this is a special
616 ;;; case where we want to use bare %FIND-PACKAGE-OR-LOSE instead of
617 ;;; FIND-UNDELETED-PACKAGE-OR-LOSE.
618 (defun package-name (package-designator)
619 (package-%name (%find-package-or-lose package-designator)))
621 ;;;; operations on package hashtables
623 ;;; Compute a number from the sxhash of the pname and the length which
624 ;;; must be between 2 and 255.
625 (defmacro entry-hash (length sxhash)
631 (the fixnum (ash ,sxhash -8))
632 (the fixnum (ash ,sxhash -16))
633 (the fixnum (ash ,sxhash -19))))
636 ;;; FIXME: should be wrapped in EVAL-WHEN (COMPILE EXECUTE)
638 ;;; Add a symbol to a package hashtable. The symbol is assumed
639 ;;; not to be present.
640 (defun add-symbol (table symbol)
641 (when (zerop (package-hashtable-free table))
642 ;; The hashtable is full. Resize it to be able to hold twice the
643 ;; amount of symbols than it currently contains. The actual new size
644 ;; can be smaller than twice the current size if the table contained
646 (resize-package-hashtable table
647 (* (- (package-hashtable-size table)
648 (package-hashtable-deleted table))
650 (let* ((vec (package-hashtable-table table))
651 (hash (package-hashtable-hash table))
653 (sxhash (%sxhash-simple-string (symbol-name symbol)))
654 (h2 (1+ (rem sxhash (- len 2)))))
655 (declare (fixnum sxhash h2))
656 (do ((i (rem sxhash len) (rem (+ i h2) len)))
657 ((< (the fixnum (aref hash i)) 2)
658 (if (zerop (the fixnum (aref hash i)))
659 (decf (package-hashtable-free table))
660 (decf (package-hashtable-deleted table)))
661 (setf (svref vec i) symbol)
663 (entry-hash (length (symbol-name symbol))
665 (declare (fixnum i)))))
667 ;;; Resize the package hashtables of all packages so that their load
668 ;;; factor is +PACKAGE-HASHTABLE-IMAGE-LOAD-FACTOR+. Called from
669 ;;; SAVE-LISP-AND-DIE to optimize space usage in the image.
670 (defun tune-hashtable-sizes-of-all-packages ()
671 (flet ((tune-table-size (table)
672 (resize-package-hashtable
674 (round (* (/ +package-rehash-threshold+
675 +package-hashtable-image-load-factor+)
676 (- (package-hashtable-size table)
677 (package-hashtable-free table)
678 (package-hashtable-deleted table)))))))
679 (dolist (package (list-all-packages))
680 (tune-table-size (package-internal-symbols package))
681 (tune-table-size (package-external-symbols package)))))
683 ;;; Find where the symbol named STRING is stored in TABLE. INDEX-VAR
684 ;;; is bound to the index, or NIL if it is not present. SYMBOL-VAR
685 ;;; is bound to the symbol. LENGTH and HASH are the length and sxhash
686 ;;; of STRING. ENTRY-HASH is the entry-hash of the string and length.
687 (defmacro with-symbol ((index-var symbol-var table string length sxhash
690 (let ((vec (gensym)) (hash (gensym)) (len (gensym)) (h2 (gensym))
691 (name (gensym)) (name-len (gensym)) (ehash (gensym)))
692 `(let* ((,vec (package-hashtable-table ,table))
693 (,hash (package-hashtable-hash ,table))
695 (,h2 (1+ (the index (rem (the hash ,sxhash)
696 (the index (- ,len 2)))))))
697 (declare (type index ,len ,h2))
698 (prog ((,index-var (rem (the hash ,sxhash) ,len))
700 (declare (type (or index null) ,index-var))
702 (setq ,ehash (aref ,hash ,index-var))
703 (cond ((eql ,ehash ,entry-hash)
704 (setq ,symbol-var (svref ,vec ,index-var))
705 (let* ((,name (symbol-name ,symbol-var))
706 (,name-len (length ,name)))
707 (declare (type index ,name-len))
708 (when (and (= ,name-len ,length)
709 (string= ,string ,name
714 (setq ,index-var nil)
716 (setq ,index-var (+ ,index-var ,h2))
717 (when (>= ,index-var ,len)
718 (setq ,index-var (- ,index-var ,len)))
721 (return (progn ,@forms))))))
723 ;;; Delete the entry for STRING in TABLE. The entry must exist.
724 (defun nuke-symbol (table string)
725 (declare (simple-string string))
726 (let* ((length (length string))
727 (hash (%sxhash-simple-string string))
728 (ehash (entry-hash length hash)))
729 (declare (type index length)
731 (with-symbol (index symbol table string length hash ehash)
732 (setf (aref (package-hashtable-hash table) index) 1)
733 (setf (aref (package-hashtable-table table) index) nil)
734 (incf (package-hashtable-deleted table))))
735 ;; If the table is less than one quarter full, halve its size and
736 ;; rehash the entries.
737 (let* ((size (package-hashtable-size table))
738 (deleted (package-hashtable-deleted table))
740 (package-hashtable-free table)
742 (declare (type fixnum size deleted used))
743 (when (< used (truncate size 4))
744 (resize-package-hashtable table (* used 2)))))
746 ;;; Enter any new NICKNAMES for PACKAGE into *PACKAGE-NAMES*. If there is a
747 ;;; conflict then give the user a chance to do something about it. Caller is
748 ;;; responsible for having acquired the mutex via WITH-PACKAGES.
749 (defun %enter-new-nicknames (package nicknames)
750 (declare (type list nicknames))
751 (dolist (n nicknames)
752 (let* ((n (package-namify n))
753 (found (with-package-names (names)
754 (or (gethash n names)
756 (setf (gethash n names) package)
757 (push n (package-%nicknames package))
759 (cond ((eq found package))
760 ((string= (the string (package-%name found)) n)
761 (signal-package-cerror
763 "Ignore this nickname."
764 "~S is a package name, so it cannot be a nickname for ~S."
765 n (package-%name package)))
767 (signal-package-cerror
769 "Leave this nickname alone."
770 "~S is already a nickname for ~S."
771 n (package-%name found)))))))
773 (defun make-package (name &key
774 (use '#.*default-package-use-list*)
776 (internal-symbols 10)
777 (external-symbols 10))
780 "Make a new package having the specified NAME, NICKNAMES, and USE
781 list. :INTERNAL-SYMBOLS and :EXTERNAL-SYMBOLS are estimates for the number of
782 internal and external symbols which will ultimately be present in the package.
783 The default value of USE is implementation-dependent, and in this
784 implementation it is ~S." *default-package-use-list*)
787 (when (find-package name)
788 ;; ANSI specifies that this error is correctable.
789 (signal-package-cerror
791 "Clobber existing package."
792 "A package named ~S already exists" name)
794 (with-package-graph ()
795 ;; Check for race, signal the error outside the lock.
796 (when (and (not clobber) (find-package name))
798 (let* ((name (package-namify name))
799 (package (internal-make-package
801 :internal-symbols (make-or-remake-package-hashtable
803 :external-symbols (make-or-remake-package-hashtable
806 ;; Do a USE-PACKAGE for each thing in the USE list so that checking for
807 ;; conflicting exports among used packages is done.
808 (if *in-package-init*
809 (push (list use package) *!deferred-use-packages*)
810 (use-package use package))
812 ;; FIXME: ENTER-NEW-NICKNAMES can fail (ERROR) if nicknames are illegal,
813 ;; which would leave us with possibly-bad side effects from the earlier
814 ;; USE-PACKAGE (e.g. this package on the used-by lists of other packages,
815 ;; but not in *PACKAGE-NAMES*, and possibly import side effects too?).
816 ;; Perhaps this can be solved by just moving ENTER-NEW-NICKNAMES before
817 ;; USE-PACKAGE, but I need to check what kinds of errors can be caused by
819 (%enter-new-nicknames package nicknames)
820 (return (setf (gethash name *package-names*) package))))
823 ;;; Change the name if we can, blast any old nicknames and then
824 ;;; add in any new ones.
826 ;;; FIXME: ANSI claims that NAME is a package designator (not just a
827 ;;; string designator -- weird). Thus, NAME could
828 ;;; be a package instead of a string. Presumably then we should not change
829 ;;; the package name if NAME is the same package that's referred to by PACKAGE.
830 ;;; If it's a *different* package, we should probably signal an error.
831 ;;; (perhaps (ERROR 'ANSI-WEIRDNESS ..):-)
832 (defun rename-package (package-designator name &optional (nicknames ()))
834 "Changes the name and nicknames for a package."
836 (let ((package (find-undeleted-package-or-lose package-designator))
837 (name (package-namify name))
838 (found (find-package name))
839 (nicks (mapcar #'string nicknames)))
840 (unless (or (not found) (eq found package))
841 (signal-package-error name
842 "A package named ~S already exists." name))
843 (with-single-package-locked-error ()
844 (unless (and (string= name (package-name package))
845 (null (set-difference nicks (package-nicknames package)
847 (assert-package-unlocked package "rename as ~A~@[ with nickname~P ~
849 name (length nicks) nicks))
850 (with-package-names (names)
851 ;; Check for race conditions now that we have the lock.
852 (unless (eq package (find-package package-designator))
855 (remhash (package-%name package) names)
856 (dolist (n (package-%nicknames package))
858 (setf (package-%name package) name
859 (gethash name names) package
860 (package-%nicknames package) ()))
861 (%enter-new-nicknames package nicknames))
864 (defun delete-package (package-designator)
866 "Delete the package designated by PACKAGE-DESIGNATOR from the package
867 system data structures."
869 (let ((package (find-package package-designator)))
871 ;; This continuable error is required by ANSI.
872 (signal-package-cerror
875 "There is no package named ~S." package-designator)
876 (return-from delete-package nil))
877 ((not (package-name package)) ; already deleted
878 (return-from delete-package nil))
880 (with-single-package-locked-error
881 (:package package "deleting package ~A" package)
882 (let ((use-list (package-used-by-list package)))
884 ;; This continuable error is specified by ANSI.
885 (signal-package-cerror
887 "Remove dependency in other packages."
888 "~@<Package ~S is used by package~P:~2I~_~S~@:>"
889 (package-name package)
891 (mapcar #'package-name use-list))
893 (unuse-package package p))))
894 (dolist (p (package-implements-list package))
895 (remove-implementation-package package p))
896 (with-package-graph ()
897 ;; Check for races, restart if necessary.
898 (let ((package2 (find-package package-designator)))
899 (when (or (neq package package2) (package-used-by-list package2))
901 (dolist (used (package-use-list package))
902 (unuse-package used package))
903 (dolist (namer (package-%locally-nicknamed-by package))
904 (setf (package-%local-nicknames namer)
905 (delete package (package-%local-nicknames namer) :key #'cdr)))
906 (setf (package-%locally-nicknamed-by package) nil)
907 (dolist (cell (package-%local-nicknames package))
908 (let ((actual (cdr cell)))
909 (setf (package-%locally-nicknamed-by actual)
910 (delete package (package-%locally-nicknamed-by actual)))))
911 (setf (package-%local-nicknames package) nil)
912 (do-symbols (sym package)
913 (unintern sym package))
914 (with-package-names (names)
915 (remhash (package-name package) names)
916 (dolist (nick (package-nicknames package))
917 (remhash nick names))
918 (setf (package-%name package) nil
919 ;; Setting PACKAGE-%NAME to NIL is required in order to
920 ;; make PACKAGE-NAME return NIL for a deleted package as
921 ;; ANSI requires. Setting the other slots to NIL
922 ;; and blowing away the PACKAGE-HASHTABLES is just done
923 ;; for tidiness and to help the GC.
924 (package-%nicknames package) nil))
925 (setf (package-%use-list package) nil
926 (package-tables package) nil
927 (package-%shadowing-symbols package) nil
928 (package-internal-symbols package)
929 (make-or-remake-package-hashtable 0)
930 (package-external-symbols package)
931 (make-or-remake-package-hashtable 0)))
932 (return-from delete-package t)))))))
934 (defun list-all-packages ()
936 "Return a list of all existing packages."
938 (with-package-names (names)
939 (maphash (lambda (k v)
945 (defun intern (name &optional (package (sane-package)))
947 "Return a symbol in PACKAGE having the specified NAME, creating it
949 ;; We just simple-stringify the name and call INTERN*, where the real
951 (let ((name (if (simple-string-p name)
953 (coerce name 'simple-string)))
954 (package (find-undeleted-package-or-lose package)))
955 (declare (simple-string name))
960 (defun find-symbol (name &optional (package (sane-package)))
962 "Return the symbol named STRING in PACKAGE. If such a symbol is found
963 then the second value is :INTERNAL, :EXTERNAL or :INHERITED to indicate
964 how the symbol is accessible. If no symbol is found then both values
966 ;; We just simple-stringify the name and call FIND-SYMBOL*, where the
968 (let ((name (if (simple-string-p name) name (coerce name 'simple-string))))
969 (declare (simple-string name))
972 (find-undeleted-package-or-lose package))))
974 ;;; If the symbol named by the first LENGTH characters of NAME doesn't exist,
975 ;;; then create it, special-casing the keyword package.
976 (defun intern* (name length package &key no-copy)
977 (declare (simple-string name))
978 (multiple-value-bind (symbol where) (find-symbol* name length package)
980 (values symbol where))
982 ;; Let's try again with a lock: the common case has the
983 ;; symbol already interned, handled by the first leg of the
984 ;; COND, but in case another thread is interning in
985 ;; parallel we need to check after grabbing the lock.
986 (with-package-graph ()
987 (setf (values symbol where) (find-symbol* name length package))
989 (values symbol where)
990 (let ((symbol-name (cond (no-copy
991 (aver (= (length name) length))
994 ;; This so that SUBSEQ is inlined,
995 ;; because we need it fixed for cold init.
997 ((simple-array base-char (*))
998 (simple-array character (*)))
1000 (declare (optimize speed))
1001 (subseq name 0 length))))))
1002 (with-single-package-locked-error
1003 (:package package "interning ~A" symbol-name)
1004 (let ((symbol (make-symbol symbol-name)))
1005 (%set-symbol-package symbol package)
1007 ((eq package *keyword-package*)
1008 (%set-symbol-value symbol symbol)
1009 (add-symbol (package-external-symbols package) symbol))
1011 (add-symbol (package-internal-symbols package) symbol)))
1012 (values symbol nil))))))))))
1014 ;;; Check internal and external symbols, then scan down the list
1015 ;;; of hashtables for inherited symbols.
1016 (defun find-symbol* (string length package)
1017 (declare (simple-string string)
1018 (type index length))
1019 (let* ((hash (%sxhash-simple-substring string length))
1020 (ehash (entry-hash length hash)))
1021 (declare (type hash hash ehash))
1022 (with-symbol (found symbol (package-internal-symbols package)
1023 string length hash ehash)
1025 (return-from find-symbol* (values symbol :internal))))
1026 (with-symbol (found symbol (package-external-symbols package)
1027 string length hash ehash)
1029 (return-from find-symbol* (values symbol :external))))
1030 (let ((head (package-tables package)))
1031 (do ((prev head table)
1032 (table (cdr head) (cdr table)))
1033 ((null table) (values nil nil))
1034 (with-symbol (found symbol (car table) string length hash ehash)
1036 ;; At this point we used to move the table to the
1037 ;; beginning of the list, probably on the theory that we'd
1038 ;; soon be looking up further items there. Unfortunately
1039 ;; that was very much non-thread safe. Since the failure
1040 ;; mode was nasty (corruption of the package in a way
1041 ;; which would make symbol lookups loop infinitely) and it
1042 ;; would be triggered just by doing reads to a resource
1043 ;; that users can't do their own locking on, that code has
1044 ;; been removed. If we ever add locking to packages,
1045 ;; resurrecting that code might make sense, even though it
1046 ;; didn't seem to have much of an performance effect in
1049 ;; -- JES, 2006-09-13
1050 (return-from find-symbol* (values symbol :inherited))))))))
1052 ;;; Similar to FIND-SYMBOL, but only looks for an external symbol.
1053 ;;; This is used for fast name-conflict checking in this file and symbol
1054 ;;; printing in the printer.
1055 (defun find-external-symbol (string package)
1056 (declare (simple-string string))
1057 (let* ((length (length string))
1058 (hash (%sxhash-simple-string string))
1059 (ehash (entry-hash length hash)))
1060 (declare (type index length)
1062 (with-symbol (found symbol (package-external-symbols package)
1063 string length hash ehash)
1064 (values symbol found))))
1066 (defun print-symbol-with-prefix (stream symbol colon at)
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))))
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)
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)))
1101 (car (remove datum symbols))))
1102 (let ((pname (package-name package)))
1104 (error 'name-conflict :package package :symbols symbols
1105 :function function :datum datum)
1106 ;; USE-PACKAGE and EXPORT
1111 (format s "Keep ~S accessible in ~A (shadowing ~S)."
1112 (old-symbol) pname datum))
1114 (format s "Keep symbols already accessible ~A (shadowing others)."
1116 :test use-or-export-p
1117 (dolist (s (remove-duplicates symbols :test #'string=))
1118 (shadow (symbol-name s) package)))
1123 (format s "Make ~S accessible in ~A (uninterning ~S)."
1124 datum pname (old-symbol)))
1126 (format s "Make newly exposed symbols accessible in ~A, ~
1127 uninterning old ones."
1129 :test use-or-export-p
1131 (when (eq s (find-symbol (symbol-name s) package))
1132 (unintern s package))))
1134 (shadowing-import-it ()
1136 (format s "Shadowing-import ~S, uninterning ~S."
1137 datum (old-symbol)))
1139 (shadowing-import datum package))
1142 (format s "Don't import ~S, keeping ~S."
1144 (car (remove datum symbols))))
1146 ;; General case. This is exposed via SB-EXT.
1147 (resolve-conflict (chosen-symbol)
1148 :report "Resolve conflict."
1151 (let* ((len (length symbols))
1152 (nlen (length (write-to-string len :base 10)))
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/~}~@:_~}~
1158 (package-name package)
1159 (loop for s in symbols
1161 collect (list nlen i s)))
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)))))
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)
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)))
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)))
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
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)
1216 (dolist (p (package-%use-list package))
1217 (multiple-value-bind (s w) (find-external-symbol name p)
1218 (when w (pushnew s 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))
1232 (if (eq (symbol-package symbol) package)
1233 (%set-symbol-package symbol nil))
1237 ;;; Take a symbol-or-list-of-symbols and return a list, checking types.
1238 (defun symbol-listify (thing)
1239 (cond ((listp thing)
1242 (signal-package-error nil
1243 "~S is not a symbol." s)))
1245 ((symbolp thing) (list thing))
1247 (signal-package-error nil
1248 "~S is neither a symbol nor a list of symbols."
1251 (defun string-listify (thing)
1252 (mapcar #'string (if (listp thing)
1256 ;;; This is like UNINTERN, except if SYMBOL is inherited, it chases
1257 ;;; down the package it is inherited from and uninterns it there. Used
1258 ;;; for name-conflict resolution. Shadowing symbols are not uninterned
1259 ;;; since they do not cause conflicts.
1260 (defun moby-unintern (symbol package)
1261 (unless (member symbol (package-%shadowing-symbols package))
1262 (or (unintern symbol package)
1263 (let ((name (symbol-name symbol)))
1264 (multiple-value-bind (s w) (find-symbol name package)
1265 (declare (ignore s))
1266 (when (eq w :inherited)
1267 (dolist (q (package-%use-list package))
1268 (multiple-value-bind (u x) (find-external-symbol name q)
1269 (declare (ignore u))
1274 (defun export (symbols &optional (package (sane-package)))
1276 "Exports SYMBOLS from PACKAGE, checking that no name conflicts result."
1277 (with-package-graph ()
1278 (let ((package (find-undeleted-package-or-lose package))
1279 (symbols (symbol-listify symbols))
1281 ;; Punt any symbols that are already external.
1282 (dolist (sym symbols)
1283 (multiple-value-bind (s w)
1284 (find-external-symbol (symbol-name sym) package)
1285 (declare (ignore s))
1286 (unless (or w (member sym syms))
1288 (with-single-package-locked-error ()
1290 (assert-package-unlocked package "exporting symbol~P ~{~A~^, ~}"
1291 (length syms) syms))
1292 ;; Find symbols and packages with conflicts.
1293 (let ((used-by (package-%used-by-list package)))
1295 (let ((name (symbol-name sym)))
1297 (multiple-value-bind (s w) (find-symbol name p)
1300 (not (member s (package-%shadowing-symbols p))))
1301 ;; Beware: the name conflict is in package P, not in
1303 (name-conflict p 'export sym sym s)))))))
1304 ;; Check that all symbols are accessible. If not, ask to import them.
1308 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1309 (cond ((not (and w (eq s sym)))
1312 (push sym imports)))))
1314 (signal-package-cerror
1316 (format nil "~S these symbols into the ~A package."
1317 'import (package-%name package))
1318 "~@<These symbols are not accessible in the ~A package:~2I~_~S~@:>"
1319 (package-%name package) missing)
1320 (import missing package))
1321 (import imports package))
1323 ;; And now, three pages later, we export the suckers.
1324 (let ((internal (package-internal-symbols package))
1325 (external (package-external-symbols package)))
1327 (nuke-symbol internal (symbol-name sym))
1328 (add-symbol external sym))))
1331 ;;; Check that all symbols are accessible, then move from external to internal.
1332 (defun unexport (symbols &optional (package (sane-package)))
1334 "Makes SYMBOLS no longer exported from PACKAGE."
1335 (with-package-graph ()
1336 (let ((package (find-undeleted-package-or-lose package))
1337 (symbols (symbol-listify symbols))
1339 (dolist (sym symbols)
1340 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1341 (cond ((or (not w) (not (eq s sym)))
1342 (signal-package-error
1344 "~S is not accessible in the ~A package."
1345 sym (package-%name package)))
1346 ((eq w :external) (pushnew sym syms)))))
1347 (with-single-package-locked-error ()
1349 (assert-package-unlocked package "unexporting symbol~P ~{~A~^, ~}"
1350 (length syms) syms))
1351 (let ((internal (package-internal-symbols package))
1352 (external (package-external-symbols package)))
1354 (add-symbol internal sym)
1355 (nuke-symbol external (symbol-name sym)))))
1358 ;;; Check for name conflict caused by the import and let the user
1359 ;;; shadowing-import if there is.
1360 (defun import (symbols &optional (package (sane-package)))
1362 "Make SYMBOLS accessible as internal symbols in PACKAGE. If a symbol is
1363 already accessible then it has no effect. If a name conflict would result from
1364 the importation, then a correctable error is signalled."
1365 (with-package-graph ()
1366 (let* ((package (find-undeleted-package-or-lose package))
1367 (symbols (symbol-listify symbols))
1368 (homeless (remove-if #'symbol-package symbols))
1370 (with-single-package-locked-error ()
1371 (dolist (sym symbols)
1372 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1374 (let ((found (member sym syms :test #'string=)))
1376 (when (not (eq (car found) sym))
1377 (setf syms (remove (car found) syms))
1378 (name-conflict package 'import sym sym (car found)))
1381 (name-conflict package 'import sym sym s))
1382 ((eq w :inherited) (push sym syms)))))
1383 (when (or homeless syms)
1384 (let ((union (delete-duplicates (append homeless syms))))
1385 (assert-package-unlocked package "importing symbol~P ~{~A~^, ~}"
1386 (length union) union)))
1387 ;; Add the new symbols to the internal hashtable.
1388 (let ((internal (package-internal-symbols package)))
1390 (add-symbol internal sym)))
1391 ;; If any of the symbols are uninterned, make them be owned by PACKAGE.
1392 (dolist (sym homeless)
1393 (%set-symbol-package sym package))
1396 ;;; If a conflicting symbol is present, unintern it, otherwise just
1397 ;;; stick the symbol in.
1398 (defun shadowing-import (symbols &optional (package (sane-package)))
1400 "Import SYMBOLS into package, disregarding any name conflict. If
1401 a symbol of the same name is present, then it is uninterned."
1402 (with-package-graph ()
1403 (let* ((package (find-undeleted-package-or-lose package))
1404 (internal (package-internal-symbols package))
1405 (symbols (symbol-listify symbols))
1406 (lock-asserted-p nil))
1407 (with-single-package-locked-error ()
1408 (dolist (sym symbols)
1409 (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1410 (unless (or lock-asserted-p
1412 (member s (package-shadowing-symbols package))))
1413 (assert-package-unlocked package "shadowing-importing symbol~P ~
1414 ~{~A~^, ~}" (length symbols) symbols)
1415 (setf lock-asserted-p t))
1416 (unless (and w (not (eq w :inherited)) (eq s sym))
1417 (when (or (eq w :internal) (eq w :external))
1418 ;; If it was shadowed, we don't want UNINTERN to flame out...
1419 (setf (package-%shadowing-symbols package)
1420 (remove s (the list (package-%shadowing-symbols package))))
1421 (unintern s package))
1422 (add-symbol internal sym))
1423 (pushnew sym (package-%shadowing-symbols package)))))))
1426 (defun shadow (symbols &optional (package (sane-package)))
1428 "Make an internal symbol in PACKAGE with the same name as each of the
1429 specified SYMBOLS. If a symbol with the given name is already present in
1430 PACKAGE, then the existing symbol is placed in the shadowing symbols list if
1431 it is not already present."
1432 (with-package-graph ()
1433 (let* ((package (find-undeleted-package-or-lose package))
1434 (internal (package-internal-symbols package))
1435 (symbols (string-listify symbols))
1436 (lock-asserted-p nil))
1437 (flet ((present-p (w)
1438 (and w (not (eq w :inherited)))))
1439 (with-single-package-locked-error ()
1440 (dolist (name symbols)
1441 (multiple-value-bind (s w) (find-symbol name package)
1442 (unless (or lock-asserted-p
1444 (member s (package-shadowing-symbols package))))
1445 (assert-package-unlocked package "shadowing symbol~P ~{~A~^, ~}"
1446 (length symbols) symbols)
1447 (setf lock-asserted-p t))
1448 (unless (present-p w)
1449 (setq s (make-symbol name))
1450 (%set-symbol-package s package)
1451 (add-symbol internal s))
1452 (pushnew s (package-%shadowing-symbols package))))))))
1455 ;;; Do stuff to use a package, with all kinds of fun name-conflict checking.
1456 (defun use-package (packages-to-use &optional (package (sane-package)))
1458 "Add all the PACKAGES-TO-USE to the use list for PACKAGE so that the
1459 external symbols of the used packages are accessible as internal symbols in
1461 (with-package-graph ()
1462 (let ((packages (package-listify packages-to-use))
1463 (package (find-undeleted-package-or-lose package)))
1465 ;; Loop over each package, USE'ing one at a time...
1466 (with-single-package-locked-error ()
1467 (dolist (pkg packages)
1468 (unless (member pkg (package-%use-list package))
1469 (assert-package-unlocked package "using package~P ~{~A~^, ~}"
1470 (length packages) packages)
1471 (let ((shadowing-symbols (package-%shadowing-symbols package))
1472 (use-list (package-%use-list package)))
1474 ;; If the number of symbols already accessible is less
1475 ;; than the number to be inherited then it is faster to
1476 ;; run the test the other way. This is particularly
1477 ;; valuable in the case of a new package USEing
1480 ((< (+ (package-internal-symbol-count package)
1481 (package-external-symbol-count package)
1483 (dolist (p use-list res)
1484 (incf res (package-external-symbol-count p)))))
1485 (package-external-symbol-count pkg))
1486 (do-symbols (sym package)
1487 (multiple-value-bind (s w)
1488 (find-external-symbol (symbol-name sym) pkg)
1491 (not (member sym shadowing-symbols)))
1492 (name-conflict package 'use-package pkg sym s))))
1493 (dolist (p use-list)
1494 (do-external-symbols (sym p)
1495 (multiple-value-bind (s w)
1496 (find-external-symbol (symbol-name sym) pkg)
1500 (find-symbol (symbol-name sym) package)
1501 shadowing-symbols)))
1502 (name-conflict package 'use-package pkg sym s))))))
1504 (do-external-symbols (sym pkg)
1505 (multiple-value-bind (s w)
1506 (find-symbol (symbol-name sym) package)
1509 (not (member s shadowing-symbols)))
1510 (name-conflict package 'use-package pkg sym s)))))))
1512 (push pkg (package-%use-list package))
1513 (push (package-external-symbols pkg) (cdr (package-tables package)))
1514 (push package (package-%used-by-list pkg)))))))
1517 (defun unuse-package (packages-to-unuse &optional (package (sane-package)))
1519 "Remove PACKAGES-TO-UNUSE from the USE list for PACKAGE."
1520 (with-package-graph ()
1521 (let ((package (find-undeleted-package-or-lose package))
1522 (packages (package-listify packages-to-unuse)))
1523 (with-single-package-locked-error ()
1524 (dolist (p packages)
1525 (when (member p (package-use-list package))
1526 (assert-package-unlocked package "unusing package~P ~{~A~^, ~}"
1527 (length packages) packages))
1528 (setf (package-%use-list package)
1529 (remove p (the list (package-%use-list package))))
1530 (setf (package-tables package)
1531 (delete (package-external-symbols p)
1532 (the list (package-tables package))))
1533 (setf (package-%used-by-list p)
1534 (remove package (the list (package-%used-by-list p))))))
1537 (defun find-all-symbols (string-or-symbol)
1539 "Return a list of all symbols in the system having the specified name."
1540 (let ((string (string string-or-symbol))
1542 (with-package-names (names)
1543 (maphash (lambda (k v)
1544 (declare (ignore k))
1545 (multiple-value-bind (s w) (find-symbol string v)
1546 (when w (pushnew s res))))
1550 ;;;; APROPOS and APROPOS-LIST
1552 (defun briefly-describe-symbol (symbol)
1555 (when (boundp symbol)
1556 (write-string " (bound)"))
1557 (when (fboundp symbol)
1558 (write-string " (fbound)")))
1560 (defun apropos-list (string-designator
1565 "Like APROPOS, except that it returns a list of the symbols found instead
1566 of describing them."
1567 (if package-designator
1568 (let ((package (find-undeleted-package-or-lose package-designator))
1569 (string (stringify-string-designator string-designator))
1571 (do-symbols (symbol package)
1572 (when (and (eq (symbol-package symbol) package)
1573 (or (not external-only)
1574 (eq (nth-value 1 (find-symbol (symbol-name symbol)
1577 (search string (symbol-name symbol) :test #'char-equal))
1578 (push symbol result)))
1579 (sort result #'string-lessp))
1580 (mapcan (lambda (package)
1581 (apropos-list string-designator package external-only))
1582 (sort (list-all-packages) #'string-lessp :key #'package-name))))
1584 (defun apropos (string-designator &optional package external-only)
1586 "Briefly describe all symbols which contain the specified STRING.
1587 If PACKAGE is supplied then only describe symbols present in
1588 that package. If EXTERNAL-ONLY then only describe
1589 external symbols in the specified package."
1590 ;; Implementing this in terms of APROPOS-LIST keeps things simple at the cost
1591 ;; of some unnecessary consing; and the unnecessary consing shouldn't be an
1592 ;; issue, since this function is is only useful interactively anyway, and
1593 ;; we can cons and GC a lot faster than the typical user can read..
1594 (dolist (symbol (apropos-list string-designator package external-only))
1595 (briefly-describe-symbol symbol))
1598 ;;;; final initialization
1600 ;;;; The cold loader (GENESIS) makes the data structure in
1601 ;;;; *!INITIAL-SYMBOLS*. We grovel over it, making the specified
1602 ;;;; packages and interning the symbols. For a description of the
1603 ;;;; format of *!INITIAL-SYMBOLS*, see the GENESIS source.
1605 (defvar *!initial-symbols*)
1609 (setq *in-package-init* t)
1611 (/show0 "about to loop over *!INITIAL-SYMBOLS* to make packages")
1612 (dolist (spec *!initial-symbols*)
1613 (let* ((pkg (apply #'make-package (first spec)))
1614 (internal (package-internal-symbols pkg))
1615 (external (package-external-symbols pkg)))
1616 (/show0 "back from MAKE-PACKAGE, PACKAGE-NAME=..")
1617 (/primitive-print (package-name pkg))
1619 ;; Put internal symbols in the internal hashtable and set package.
1620 (dolist (symbol (second spec))
1621 (add-symbol internal symbol)
1622 (%set-symbol-package symbol pkg))
1624 ;; External symbols same, only go in external table.
1625 (dolist (symbol (third spec))
1626 (add-symbol external symbol)
1627 (%set-symbol-package symbol pkg))
1629 ;; Don't set package for imported symbols.
1630 (dolist (symbol (fourth spec))
1631 (add-symbol internal symbol))
1632 (dolist (symbol (fifth spec))
1633 (add-symbol external symbol))
1635 ;; Put shadowing symbols in the shadowing symbols list.
1636 (setf (package-%shadowing-symbols pkg) (sixth spec))
1637 ;; Set the package documentation
1638 (setf (package-doc-string pkg) (seventh spec))))
1640 ;; FIXME: These assignments are also done at toplevel in
1641 ;; boot-extensions.lisp. They should probably only be done once.
1642 (/show0 "setting up *CL-PACKAGE* and *KEYWORD-PACKAGE*")
1643 (setq *cl-package* (find-package "COMMON-LISP"))
1644 (setq *keyword-package* (find-package "KEYWORD"))
1646 (/show0 "about to MAKUNBOUND *!INITIAL-SYMBOLS*")
1647 (%makunbound '*!initial-symbols*) ; (so that it gets GCed)
1649 ;; Make some other packages that should be around in the cold load.
1650 ;; The COMMON-LISP-USER package is required by the ANSI standard,
1651 ;; but not completely specified by it, so in the cross-compilation
1652 ;; host Lisp it could contain various symbols, USE-PACKAGEs, or
1653 ;; nicknames that we don't want in our target SBCL. For that reason,
1654 ;; we handle it specially, not dumping the host Lisp version at
1656 (aver (not (find-package "COMMON-LISP-USER")))
1657 ;; ..but instead making our own from scratch here.
1658 (/show0 "about to MAKE-PACKAGE COMMON-LISP-USER")
1659 (make-package "COMMON-LISP-USER"
1660 :nicknames '("CL-USER")
1661 :use '("COMMON-LISP"
1662 ;; ANSI encourages us to put extension packages
1663 ;; in the USE list of COMMON-LISP-USER.
1664 "SB!ALIEN" "SB!ALIEN" "SB!DEBUG"
1665 "SB!EXT" "SB!GRAY" "SB!PROFILE"))
1667 ;; Now do the *!DEFERRED-USE-PACKAGES*.
1668 (/show0 "about to do *!DEFERRED-USE-PACKAGES*")
1669 (dolist (args *!deferred-use-packages*)
1670 (apply #'use-package args))
1672 ;; The Age Of Magic is over, we can behave ANSIly henceforth.
1673 (/show0 "about to SETQ *IN-PACKAGE-INIT*")
1674 (setq *in-package-init* nil)
1676 ;; For the kernel core image wizards, set the package to *CL-PACKAGE*.
1678 ;; FIXME: We should just set this to (FIND-PACKAGE
1679 ;; "COMMON-LISP-USER") once and for all here, instead of setting it
1680 ;; once here and resetting it later.
1681 (setq *package* *cl-package*))
1684 (/show0 "done with !PACKAGE-COLD-INIT"))
1686 (!defun-from-collected-cold-init-forms !package-cold-init)