39f662cc8f287d2a74e4fc31e896f0e5f7d6de95
[sbcl.git] / src / code / target-package.lisp
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?
14
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.
23
24 (in-package "SB!IMPL")
25
26 (!begin-collecting-cold-init-forms)
27
28 (!cold-init-forms
29   (/show0 "entering !PACKAGE-COLD-INIT"))
30 \f
31 ;;;; PACKAGE-HASHTABLE stuff
32
33 (def!method print-object ((table package-hashtable) stream)
34   (declare (type stream stream))
35   (print-unreadable-object (table stream :type t)
36     (format stream
37             ":SIZE ~S :FREE ~S :DELETED ~S"
38             (package-hashtable-size table)
39             (package-hashtable-free table)
40             (package-hashtable-deleted table))))
41
42 ;;; the maximum density we allow in a package hashtable
43 (defconstant package-rehash-threshold 0.75)
44
45 ;;; Make a package hashtable having a prime number of entries at least
46 ;;; as great as (/ SIZE PACKAGE-REHASH-THRESHOLD). If RES is supplied,
47 ;;; then it is destructively modified to produce the result. This is
48 ;;; useful when changing the size, since there are many pointers to
49 ;;; the hashtable.
50 (defun make-or-remake-package-hashtable (size
51                                          &optional
52                                          res)
53   (flet ((actual-package-hashtable-size (size)
54            (loop for n of-type fixnum
55               from (logior (truncate size package-rehash-threshold) 1)
56               by 2
57               when (positive-primep n) return n)))
58     (let* ((n (actual-package-hashtable-size size))
59            (size (truncate (* n package-rehash-threshold)))
60            (table (make-array n))
61            (hash (make-array n
62                              :element-type '(unsigned-byte 8)
63                              :initial-element 0)))
64       (if res
65           (setf (package-hashtable-table res) table
66                 (package-hashtable-hash res) hash
67                 (package-hashtable-size res) size
68                 (package-hashtable-free res) size
69                 (package-hashtable-deleted res) 0)
70           (setf res (%make-package-hashtable table hash size)))
71       res)))
72 \f
73 ;;;; package locking operations, built conditionally on :sb-package-locks
74
75 #!+sb-package-locks
76 (progn
77 (defun package-locked-p (package) 
78   #!+sb-doc 
79   "Returns T when PACKAGE is locked, NIL otherwise. Signals an error
80 if PACKAGE doesn't designate a valid package."
81   (package-lock (find-undeleted-package-or-lose package)))
82
83 (defun lock-package (package)
84   #!+sb-doc 
85   "Locks PACKAGE and returns T. Has no effect if PACKAGE was already
86 locked. Signals an error if PACKAGE is not a valid package designator"
87   (setf (package-lock (find-undeleted-package-or-lose package)) t))
88
89 (defun unlock-package (package)
90   #!+sb-doc 
91   "Unlocks PACKAGE and returns T. Has no effect if PACKAGE was already
92 unlocked. Signals an error if PACKAGE is not a valid package designator."
93   (setf (package-lock (find-undeleted-package-or-lose package)) nil)
94   t)
95
96 (defun package-implemented-by-list (package)
97   #!+sb-doc 
98   "Returns a list containing the implementation packages of
99 PACKAGE. Signals an error if PACKAGE is not a valid package designator."
100   (package-%implementation-packages (find-undeleted-package-or-lose package)))
101
102 (defun package-implements-list (package) 
103   #!+sb-doc 
104   "Returns the packages that PACKAGE is an implementation package
105 of. Signals an error if PACKAGE is not a valid package designator."
106   (let ((package (find-undeleted-package-or-lose package)))
107     (loop for x in (list-all-packages)
108           when (member package (package-%implementation-packages x))
109           collect x)))
110
111 (defun add-implementation-package (packages-to-add 
112                                    &optional (package *package*))
113   #!+sb-doc 
114   "Adds PACKAGES-TO-ADD as implementation packages of PACKAGE. Signals
115 an error if PACKAGE or any of the PACKAGES-TO-ADD is not a valid
116 package designator."
117   (let ((package (find-undeleted-package-or-lose package))
118         (packages-to-add (package-listify packages-to-add)))
119     (setf (package-%implementation-packages package)
120           (union (package-%implementation-packages package)
121                  (mapcar #'find-undeleted-package-or-lose packages-to-add)))))
122
123 (defun remove-implementation-package (packages-to-remove 
124                                       &optional (package *package*)) 
125   #!+sb-doc 
126   "Removes PACKAGES-TO-REMOVE from the implementation packages of
127 PACKAGE. Signals an error if PACKAGE or any of the PACKAGES-TO-REMOVE
128 is not a valid package designator."
129   (let ((package (find-undeleted-package-or-lose package))
130         (packages-to-remove (package-listify packages-to-remove)))
131     (setf (package-%implementation-packages package)
132           (nset-difference 
133            (package-%implementation-packages package)
134            (mapcar #'find-undeleted-package-or-lose packages-to-remove)))))
135
136 (defmacro with-unlocked-packages ((&rest packages) &body forms)
137   #!+sb-doc
138   "Unlocks PACKAGES for the dynamic scope of the body. Signals an
139 error if any of PACKAGES is not a valid package designator."
140   (with-unique-names (unlocked-packages)
141     `(let (,unlocked-packages)
142       (unwind-protect
143            (progn 
144              (dolist (p ',packages)
145                (when (package-locked-p p)
146                  (push p ,unlocked-packages)
147                  (unlock-package p)))
148              ,@forms)
149         (dolist (p ,unlocked-packages)
150           (when (find-package p)
151             (lock-package p)))))))
152
153 (defun package-lock-violation (package &key (symbol nil symbol-p)
154                                format-control format-arguments)
155   (let* ((restart :continue)
156          (cl-violation-p (eq package *cl-package*))
157          (error-arguments
158           (append (list (if symbol-p
159                             'symbol-package-locked-error
160                             'package-locked-error)
161                         :package package
162                         :format-control format-control
163                         :format-arguments format-arguments)
164                   (when symbol-p (list :symbol symbol))
165                   (list :references
166                         (append '((:sbcl :node "Package Locks"))
167                                 (when cl-violation-p
168                                   '((:ansi-cl :section (11 1 2 1 2)))))))))
169     (restart-case
170         (apply #'cerror "Ignore the package lock." error-arguments)
171       (:ignore-all ()
172         :report "Ignore all package locks in the context of this operation."
173         (setf restart :ignore-all))
174       (:unlock-package ()
175         :report "Unlock the package."
176         (setf restart :unlock-package)))
177     (ecase restart
178       (:continue
179        (pushnew package *ignored-package-locks*))
180       (:ignore-all
181        (setf *ignored-package-locks* t))
182       (:unlock-package
183        (unlock-package package)))))
184
185 (defun package-lock-violation-p (package &optional (symbol nil symbolp))
186   ;; KLUDGE: (package-lock package) needs to be before
187   ;; comparison to *package*, since during cold init this gets
188   ;; called before *package* is bound -- but no package should
189   ;; be locked at that point.
190   (and package 
191        (package-lock package)
192        ;; In package or implementation package
193        (not (or (eq package *package*)
194                 (member *package* (package-%implementation-packages package))))
195        ;; Runtime disabling
196        (not (eq t *ignored-package-locks*))
197        (or (eq :invalid *ignored-package-locks*)
198            (not (member package *ignored-package-locks*)))
199        ;; declarations for symbols
200        (not (and symbolp (member symbol (disabled-package-locks))))))
201
202 (defun disabled-package-locks ()
203   (if (boundp 'sb!c::*lexenv*)
204       (sb!c::lexenv-disabled-package-locks sb!c::*lexenv*)
205       sb!c::*disabled-package-locks*))
206
207 ) ; progn
208
209 ;;;; more package-locking these are NOPs unless :sb-package-locks is
210 ;;;; in target features. Cross-compiler NOPs for these are in cross-misc.
211
212 ;;; The right way to establish a package lock context is
213 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR, defined in early-package.lisp
214 ;;;
215 ;;; Must be used inside the dynamic contour established by
216 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR
217 (defun assert-package-unlocked (package &optional format-control 
218                                 &rest format-arguments)
219   #!-sb-package-locks 
220   (declare (ignore format-control format-arguments))
221   #!+sb-package-locks
222   (when (package-lock-violation-p package)
223     (package-lock-violation package 
224                             :format-control format-control 
225                             :format-arguments format-arguments))
226   package)
227
228 ;;; Must be used inside the dynamic contour established by
229 ;;; WITH-SINGLE-PACKAGE-LOCKED-ERROR.
230 ;;;
231 ;;; FIXME: Maybe we should establish such contours for he toplevel
232 ;;; and others, so that %set-fdefinition and others could just use
233 ;;; this.
234 (defun assert-symbol-home-package-unlocked (name format)
235   #!-sb-package-locks
236   (declare (ignore format))
237   #!+sb-package-locks
238   (let* ((symbol (etypecase name
239                    (symbol name)
240                    (list (if (eq 'setf (first name))
241                              (second name)
242                              ;; Skip (class-predicate foo), etc.
243                              ;; FIXME: MOP and package-lock
244                              ;; interaction needs to be thought about.
245                              (return-from 
246                               assert-symbol-home-package-unlocked
247                                name)))))
248          (package (symbol-package symbol)))
249     (when (package-lock-violation-p package symbol)
250       (package-lock-violation package 
251                               :symbol symbol
252                               :format-control format
253                               :format-arguments (list name))))
254   name)
255
256 \f
257 ;;;; miscellaneous PACKAGE operations
258
259 (def!method print-object ((package package) stream)
260   (let ((name (package-%name package)))
261     (if name
262         (print-unreadable-object (package stream :type t)
263           (prin1 name stream))
264         (print-unreadable-object (package stream :type t :identity t)
265           (write-string "(deleted)" stream)))))
266
267 ;;; ANSI says (in the definition of DELETE-PACKAGE) that these, and
268 ;;; most other operations, are unspecified for deleted packages. We
269 ;;; just do the easy thing and signal errors in that case.
270 (macrolet ((def (ext real)
271              `(defun ,ext (x) (,real (find-undeleted-package-or-lose x)))))
272   (def package-nicknames package-%nicknames)
273   (def package-use-list package-%use-list)
274   (def package-used-by-list package-%used-by-list)
275   (def package-shadowing-symbols package-%shadowing-symbols))
276
277 (defun %package-hashtable-symbol-count (table)
278   (let ((size (the fixnum
279                 (- (package-hashtable-size table)
280                    (package-hashtable-deleted table)))))
281     (the fixnum
282       (- size (package-hashtable-free table)))))
283
284 (defun package-internal-symbol-count (package)
285   (%package-hashtable-symbol-count (package-internal-symbols package)))
286
287 (defun package-external-symbol-count (package)
288   (%package-hashtable-symbol-count (package-external-symbols package)))
289 \f
290 (defvar *package* (error "*PACKAGE* should be initialized in cold load!") 
291   #!+sb-doc "the current package")
292 ;;; FIXME: should be declared of type PACKAGE, with no NIL init form,
293 ;;; after I get around to cleaning up DOCUMENTATION
294
295 ;;; a map from package names to packages
296 (defvar *package-names*)
297 (declaim (type hash-table *package-names*))
298 (!cold-init-forms
299   (setf *package-names* (make-hash-table :test 'equal)))
300
301 ;;; This magical variable is T during initialization so that
302 ;;; USE-PACKAGE's of packages that don't yet exist quietly win. Such
303 ;;; packages are thrown onto the list *DEFERRED-USE-PACKAGES* so that
304 ;;; this can be fixed up later.
305 ;;;
306 ;;; FIXME: This could be cleaned up the same way I do it in my package
307 ;;; hacking when setting up the cross-compiler. Then we wouldn't have
308 ;;; this extraneous global variable and annoying runtime tests on
309 ;;; package operations. (*DEFERRED-USE-PACKAGES* would also go away.)
310 (defvar *in-package-init*)
311
312 ;;; pending USE-PACKAGE arguments saved up while *IN-PACKAGE-INIT* is true
313 (defvar *!deferred-use-packages*)
314 (!cold-init-forms
315   (setf *!deferred-use-packages* nil))
316
317 (define-condition bootstrap-package-not-found (condition)
318   ((name :initarg :name :reader bootstrap-package-name)))
319 (defun debootstrap-package (&optional condition)
320   (invoke-restart 
321    (find-restart-or-control-error 'debootstrap-package condition)))
322   
323 (defun find-package (package-designator)
324   (flet ((find-package-from-string (string)
325            (declare (type string string))
326            (let ((packageoid (gethash string *package-names*)))
327              (when (and (null packageoid)
328                         (not *in-package-init*) ; KLUDGE
329                         (let ((mismatch (mismatch "SB!" string)))
330                           (and mismatch (= mismatch 3))))
331                (restart-case
332                    (signal 'bootstrap-package-not-found :name string)
333                  (debootstrap-package ()
334                    (return-from find-package
335                      (if (string= string "SB!XC")
336                          (find-package "COMMON-LISP")
337                          (find-package 
338                           (substitute #\- #\! string :count 1)))))))
339              packageoid)))
340     (typecase package-designator
341       (package package-designator)
342       (symbol (find-package-from-string (symbol-name package-designator)))
343       (string (find-package-from-string package-designator))
344       (character (find-package-from-string (string package-designator)))
345       (t (error 'type-error
346                 :datum package-designator
347                 :expected-type '(or character package string symbol))))))
348
349 ;;; Return a list of packages given a package designator or list of
350 ;;; package designators, or die trying.
351 (defun package-listify (thing)
352   (let ((res ()))
353     (dolist (thing (if (listp thing) thing (list thing)) res)
354       (push (find-undeleted-package-or-lose thing) res))))
355
356 ;;; Make a package name into a simple-string.
357 (defun package-namify (n)
358   (stringify-name n "package"))
359
360 ;;; ANSI specifies (in the definition of DELETE-PACKAGE) that PACKAGE-NAME
361 ;;; returns NIL (not an error) for a deleted package, so this is a special
362 ;;; case where we want to use bare %FIND-PACKAGE-OR-LOSE instead of
363 ;;; FIND-UNDELETED-PACKAGE-OR-LOSE.
364 (defun package-name (package-designator)
365   (package-%name (%find-package-or-lose package-designator)))
366 \f
367 ;;;; operations on package hashtables
368
369 ;;; Compute a number from the sxhash of the pname and the length which
370 ;;; must be between 2 and 255.
371 (defmacro entry-hash (length sxhash)
372   `(the fixnum
373         (+ (the fixnum
374                 (rem (the fixnum
375                           (logxor ,length
376                                   ,sxhash
377                                   (the fixnum (ash ,sxhash -8))
378                                   (the fixnum (ash ,sxhash -16))
379                                   (the fixnum (ash ,sxhash -19))))
380                      254))
381            2)))
382 ;;; FIXME: should be wrapped in EVAL-WHEN (COMPILE EXECUTE)
383
384 ;;; Add a symbol to a package hashtable. The symbol is assumed
385 ;;; not to be present.
386 (defun add-symbol (table symbol)
387   (let* ((vec (package-hashtable-table table))
388          (hash (package-hashtable-hash table))
389          (len (length vec))
390          (sxhash (%sxhash-simple-string (symbol-name symbol)))
391          (h2 (the fixnum (1+ (the fixnum (rem sxhash
392                                               (the fixnum (- len 2))))))))
393     (declare (fixnum len sxhash h2))
394     (cond ((zerop (the fixnum (package-hashtable-free table)))
395            (make-or-remake-package-hashtable (* (package-hashtable-size table)
396                                                 2)
397                                              table)
398            (add-symbol table symbol)
399            (dotimes (i len)
400              (declare (fixnum i))
401              (when (> (the fixnum (aref hash i)) 1)
402                (add-symbol table (svref vec i)))))
403           (t
404            (do ((i (rem sxhash len) (rem (+ i h2) len)))
405                ((< (the fixnum (aref hash i)) 2)
406                 (if (zerop (the fixnum (aref hash i)))
407                     (decf (package-hashtable-free table))
408                     (decf (package-hashtable-deleted table)))
409                 (setf (svref vec i) symbol)
410                 (setf (aref hash i)
411                       (entry-hash (length (symbol-name symbol))
412                                   sxhash)))
413              (declare (fixnum i)))))))
414
415 ;;; Find where the symbol named STRING is stored in TABLE. INDEX-VAR
416 ;;; is bound to the index, or NIL if it is not present. SYMBOL-VAR
417 ;;; is bound to the symbol. LENGTH and HASH are the length and sxhash
418 ;;; of STRING. ENTRY-HASH is the entry-hash of the string and length.
419 (defmacro with-symbol ((index-var symbol-var table string length sxhash
420                                   entry-hash)
421                        &body forms)
422   (let ((vec (gensym)) (hash (gensym)) (len (gensym)) (h2 (gensym))
423         (name (gensym)) (name-len (gensym)) (ehash (gensym)))
424     `(let* ((,vec (package-hashtable-table ,table))
425             (,hash (package-hashtable-hash ,table))
426             (,len (length ,vec))
427             (,h2 (1+ (the index (rem (the index ,sxhash)
428                                       (the index (- ,len 2)))))))
429        (declare (type index ,len ,h2))
430        (prog ((,index-var (rem (the index ,sxhash) ,len))
431               ,symbol-var ,ehash)
432          (declare (type (or index null) ,index-var))
433          LOOP
434          (setq ,ehash (aref ,hash ,index-var))
435          (cond ((eql ,ehash ,entry-hash)
436                 (setq ,symbol-var (svref ,vec ,index-var))
437                 (let* ((,name (symbol-name ,symbol-var))
438                        (,name-len (length ,name)))
439                   (declare (type index ,name-len))
440                   (when (and (= ,name-len ,length)
441                              (string= ,string ,name
442                                       :end1 ,length
443                                       :end2 ,name-len))
444                     (go DOIT))))
445                ((zerop ,ehash)
446                 (setq ,index-var nil)
447                 (go DOIT)))
448          (setq ,index-var (+ ,index-var ,h2))
449          (when (>= ,index-var ,len)
450            (setq ,index-var (- ,index-var ,len)))
451          (go LOOP)
452          DOIT
453          (return (progn ,@forms))))))
454
455 ;;; Delete the entry for STRING in TABLE. The entry must exist.
456 (defun nuke-symbol (table string)
457   (declare (simple-string string))
458   (let* ((length (length string))
459          (hash (%sxhash-simple-string string))
460          (ehash (entry-hash length hash)))
461     (declare (type index length hash))
462     (with-symbol (index symbol table string length hash ehash)
463       (setf (aref (package-hashtable-hash table) index) 1)
464       (setf (aref (package-hashtable-table table) index) nil)
465       (incf (package-hashtable-deleted table)))))
466 \f
467 ;;; Enter any new NICKNAMES for PACKAGE into *PACKAGE-NAMES*.
468 ;;; If there is a conflict then give the user a chance to do
469 ;;; something about it.
470 (defun enter-new-nicknames (package nicknames)
471   (declare (type list nicknames))
472   (dolist (n nicknames)
473     (let* ((n (package-namify n))
474            (found (gethash n *package-names*)))
475       (cond ((not found)
476              (setf (gethash n *package-names*) package)
477              (push n (package-%nicknames package)))
478             ((eq found package))
479             ((string= (the string (package-%name found)) n)
480              (cerror "Ignore this nickname."
481                      'simple-package-error
482                      :package package
483                      :format-control "~S is a package name, so it cannot be a nickname for ~S."
484                      :format-arguments (list n (package-%name package))))
485             (t
486              (cerror "Leave this nickname alone."
487                      'simple-package-error
488                      :package package
489                      :format-control "~S is already a nickname for ~S."
490                      :format-arguments (list n (package-%name found))))))))
491
492 (defun make-package (name &key
493                           (use '#.*default-package-use-list*)
494                           nicknames
495                           (internal-symbols 10)
496                           (external-symbols 10))
497   #!+sb-doc
498   #.(format nil
499      "Make a new package having the specified NAME, NICKNAMES, and 
500   USE list. :INTERNAL-SYMBOLS and :EXTERNAL-SYMBOLS are
501   estimates for the number of internal and external symbols which
502   will ultimately be present in the package. The default value of
503   USE is implementation-dependent, and in this implementation
504   it is ~S."
505      *default-package-use-list*)
506
507   ;; Check for package name conflicts in name and nicknames, then
508   ;; make the package.
509   (when (find-package name)
510     ;; ANSI specifies that this error is correctable.
511     (cerror "Leave existing package alone."
512             "A package named ~S already exists" name))
513   (let* ((name (package-namify name))
514          (package (internal-make-package
515                    :%name name
516                    :internal-symbols (make-or-remake-package-hashtable
517                                       internal-symbols)
518                    :external-symbols (make-or-remake-package-hashtable
519                                       external-symbols))))
520
521     ;; Do a USE-PACKAGE for each thing in the USE list so that checking for
522     ;; conflicting exports among used packages is done.
523     (if *in-package-init*
524         (push (list use package) *!deferred-use-packages*)
525         (use-package use package))
526
527     ;; FIXME: ENTER-NEW-NICKNAMES can fail (ERROR) if nicknames are illegal,
528     ;; which would leave us with possibly-bad side effects from the earlier
529     ;; USE-PACKAGE (e.g. this package on the used-by lists of other packages,
530     ;; but not in *PACKAGE-NAMES*, and possibly import side effects too?).
531     ;; Perhaps this can be solved by just moving ENTER-NEW-NICKNAMES before
532     ;; USE-PACKAGE, but I need to check what kinds of errors can be caused by
533     ;; USE-PACKAGE, too.
534     (enter-new-nicknames package nicknames)
535     (setf (gethash name *package-names*) package)))
536
537 ;;; Change the name if we can, blast any old nicknames and then
538 ;;; add in any new ones.
539 ;;;
540 ;;; FIXME: ANSI claims that NAME is a package designator (not just a
541 ;;; string designator -- weird). Thus, NAME could
542 ;;; be a package instead of a string. Presumably then we should not change
543 ;;; the package name if NAME is the same package that's referred to by PACKAGE.
544 ;;; If it's a *different* package, we should probably signal an error.
545 ;;; (perhaps (ERROR 'ANSI-WEIRDNESS ..):-)
546 (defun rename-package (package name &optional (nicknames ()))
547   #!+sb-doc
548   "Changes the name and nicknames for a package."
549   (let* ((package (find-undeleted-package-or-lose package))
550          (name (package-namify name))
551          (found (find-package name))
552          (nicks (mapcar #'string nicknames)))
553     (unless (or (not found) (eq found package))
554       (error 'simple-package-error
555              :package name
556              :format-control "A package named ~S already exists."
557              :format-arguments (list name)))
558     (with-single-package-locked-error ()
559         (unless (and (string= name (package-name package))
560                      (null (set-difference nicks (package-nicknames package) 
561                                        :test #'string=)))
562           (assert-package-unlocked package "rename as ~A~@[ with nickname~P ~
563                                            ~{~A~^, ~}~]" 
564                                    name (length nicks) nicks))
565       ;; do the renaming
566       (remhash (package-%name package) *package-names*)
567       (dolist (n (package-%nicknames package))
568         (remhash n *package-names*))
569       (setf (package-%name package) name
570             (gethash name *package-names*) package
571             (package-%nicknames package) ())
572       (enter-new-nicknames package nicknames))
573     package))
574
575 (defun delete-package (package-designator)
576   #!+sb-doc
577   "Delete the package designated by PACKAGE-DESIGNATOR from the package
578   system data structures."
579   (let ((package (if (packagep package-designator)
580                      package-designator
581                      (find-package package-designator))))
582     (cond ((not package)
583            ;; This continuable error is required by ANSI.
584            (cerror
585             "Return ~S."
586             (make-condition
587              'simple-package-error
588              :package package-designator
589              :format-control "There is no package named ~S."
590              :format-arguments (list package-designator))
591             nil))
592           ((not (package-name package)) ; already deleted
593            nil)
594           (t
595            (with-single-package-locked-error
596                (:package package "deleting package ~A" package)
597              (let ((use-list (package-used-by-list package)))
598                (when use-list
599                  ;; This continuable error is specified by ANSI.
600                  (cerror
601                   "Remove dependency in other packages."
602                   (make-condition
603                    'simple-package-error
604                    :package package
605                    :format-control
606                    "~@<Package ~S is used by package~P:~2I~_~S~@:>"
607                    :format-arguments (list (package-name package)
608                                            (length use-list)
609                                            (mapcar #'package-name use-list))))
610                  (dolist (p use-list)
611                    (unuse-package package p))))
612              (dolist (used (package-use-list package))
613                (unuse-package used package))
614              (do-symbols (sym package)
615                (unintern sym package))
616              (remhash (package-name package) *package-names*)
617              (dolist (nick (package-nicknames package))
618                (remhash nick *package-names*))
619              (setf (package-%name package) nil
620                    ;; Setting PACKAGE-%NAME to NIL is required in order to
621                    ;; make PACKAGE-NAME return NIL for a deleted package as
622                    ;; ANSI requires. Setting the other slots to NIL
623                    ;; and blowing away the PACKAGE-HASHTABLES is just done
624                    ;; for tidiness and to help the GC.
625                    (package-%nicknames package) nil
626                    (package-%use-list package) nil
627                    (package-tables package) nil
628                    (package-%shadowing-symbols package) nil
629                    (package-internal-symbols package)
630                    (make-or-remake-package-hashtable 0)
631                    (package-external-symbols package)
632                    (make-or-remake-package-hashtable 0))
633              t)))))
634
635 (defun list-all-packages ()
636   #!+sb-doc
637   "Return a list of all existing packages."
638   (let ((res ()))
639     (maphash (lambda (k v)
640                (declare (ignore k))
641                (pushnew v res))
642              *package-names*)
643     res))
644 \f
645 (defun intern (name &optional (package (sane-package)))
646   #!+sb-doc
647   "Return a symbol in PACKAGE having the specified NAME, creating it
648   if necessary."
649   ;; We just simple-stringify the name and call INTERN*, where the real
650   ;; logic is.
651   (let ((name (if (simple-string-p name)
652                   name
653                   (coerce name 'simple-string)))
654         (package (find-undeleted-package-or-lose package)))
655     (declare (simple-string name))
656       (intern* name
657                (length name)
658                package)))
659
660 (defun find-symbol (name &optional (package (sane-package)))
661   #!+sb-doc
662   "Return the symbol named STRING in PACKAGE. If such a symbol is found
663   then the second value is :INTERNAL, :EXTERNAL or :INHERITED to indicate
664   how the symbol is accessible. If no symbol is found then both values
665   are NIL."
666   ;; We just simple-stringify the name and call FIND-SYMBOL*, where the
667   ;; real logic is.
668   (let ((name (if (simple-string-p name) name (coerce name 'simple-string))))
669     (declare (simple-string name))
670     (find-symbol* name
671                   (length name)
672                   (find-undeleted-package-or-lose package))))
673
674 ;;; If the symbol named by the first LENGTH characters of NAME doesn't exist,
675 ;;; then create it, special-casing the keyword package.
676 (defun intern* (name length package)
677   (declare (simple-string name))
678   (multiple-value-bind (symbol where) (find-symbol* name length package)
679     (cond (where
680            (values symbol where))
681           (t
682            (let ((symbol-name (subseq name 0 length)))
683              (with-single-package-locked-error 
684                  (:package package "interning ~A" symbol-name)
685                (let ((symbol (make-symbol symbol-name)))
686                  (%set-symbol-package symbol package)
687                  (cond ((eq package *keyword-package*)
688                         (add-symbol (package-external-symbols package) symbol)
689                         (%set-symbol-value symbol symbol))
690                        (t
691                         (add-symbol (package-internal-symbols package) symbol)))
692                  (values symbol nil))))))))
693
694 ;;; Check internal and external symbols, then scan down the list
695 ;;; of hashtables for inherited symbols. When an inherited symbol
696 ;;; is found pull that table to the beginning of the list.
697 (defun find-symbol* (string length package)
698   (declare (simple-string string)
699            (type index length))
700   (let* ((hash (%sxhash-simple-substring string length))
701          (ehash (entry-hash length hash)))
702     (declare (type index hash ehash))
703     (with-symbol (found symbol (package-internal-symbols package)
704                         string length hash ehash)
705       (when found
706         (return-from find-symbol* (values symbol :internal))))
707     (with-symbol (found symbol (package-external-symbols package)
708                         string length hash ehash)
709       (when found
710         (return-from find-symbol* (values symbol :external))))
711     (let ((head (package-tables package)))
712       (do ((prev head table)
713            (table (cdr head) (cdr table)))
714           ((null table) (values nil nil))
715         (with-symbol (found symbol (car table) string length hash ehash)
716           (when found
717             (unless (eq prev head)
718               (shiftf (cdr prev) (cdr table) (cdr head) table))
719             (return-from find-symbol* (values symbol :inherited))))))))
720
721 ;;; Similar to FIND-SYMBOL, but only looks for an external symbol.
722 ;;; This is used for fast name-conflict checking in this file and symbol
723 ;;; printing in the printer.
724 (defun find-external-symbol (string package)
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 hash))
730     (with-symbol (found symbol (package-external-symbols package)
731                         string length hash ehash)
732       (values symbol found))))
733 \f
734 (define-condition name-conflict (reference-condition package-error)
735   ((function :initarg :function :reader name-conflict-function)
736    (datum :initarg :datum :reader name-conflict-datum)
737    (symbols :initarg :symbols :reader name-conflict-symbols))
738   (:default-initargs :references (list '(:ansi-cl :section (11 1 1 2 5))))
739   (:report
740    (lambda (c s)
741      (format s "~@<~S ~S causes name-conflicts in ~S between the ~
742                 following symbols:~2I~@:_~{~S~^, ~}~:@>"
743              (name-conflict-function c)
744              (name-conflict-datum c)
745              (package-error-package c)
746              (name-conflict-symbols c)))))
747
748 (defun name-conflict (package function datum &rest symbols)
749   (restart-case
750       (error 'name-conflict :package package :symbols symbols
751              :function function :datum datum)
752     (resolve-conflict (s)
753       :report "Resolve conflict."
754       :interactive
755       (lambda ()
756         (let* ((len (length symbols))
757                (nlen (length (write-to-string len :base 10))))
758           (format *query-io* "~&~@<Select a symbol to be made accessible in ~
759                               package ~A:~2I~@:_~{~{~V,' D. ~S~}~@:_~}~@:>"
760                 (package-name package)
761                 (loop for s in symbols
762                       for i upfrom 1
763                       collect (list nlen i s)))
764           (loop
765            (format *query-io* "~&Enter an integer (between 1 and ~D): " len)
766            (finish-output *query-io*)
767            (let ((i (parse-integer (read-line *query-io*) :junk-allowed t)))
768              (when (and i (<= 1 i len))
769                (return (list (nth (1- i) symbols))))))))
770       (multiple-value-bind (symbol status)
771           (find-symbol (symbol-name s) package)
772         (declare (ignore status)) ; FIXME: is that true?
773         (case function
774           ((export)
775            (if (eq symbol s)
776                (shadow symbol package)
777                (unintern symbol package)))
778           ((unintern)
779            (shadowing-import s package))
780           ((import)
781            (if (eq symbol s)
782                nil ; do nothing
783                (shadowing-import s package)))
784           ((use-package)
785            (if (eq symbol s)
786                (shadow s package)
787                (shadowing-import s package))))))))
788
789 #+nil ; this solution gives a variable number of restarts instead, but
790       ; no good way of programmatically choosing between them.
791 (defun name-conflict (package function datum &rest symbols)
792   (let ((condition (make-condition 'name-conflict
793                                    :package package :symbols symbols
794                                    :function function :datum datum)))
795     ;; this is a gross violation of modularity, but I can't see any
796     ;; other way to have a variable number of restarts.
797     (let ((*restart-clusters*
798            (cons
799             (mapcan
800              (lambda (s)
801                (multiple-value-bind (accessible-symbol status)
802                    (find-symbol (symbol-name s) package)
803                  (cond
804                    ;; difficult case
805                    ((eq s accessible-symbol)
806                     (ecase status
807                       ((:inherited)
808                        (list (make-restart
809                               :name (make-symbol "SHADOWING-IMPORT")
810                               :function (lambda ()
811                                           (shadowing-import s package)
812                                           (return-from name-conflict))
813                               :report-function
814                               (lambda (stream)
815                                 (format stream "Shadowing-import ~S into ~A."
816                                         s (package-%name package))))))
817                       ((:internal :external)
818                        (aver (= (length symbols) 2))
819                        ;; ARGH! FIXME: this unintern restart can
820                        ;; _still_ leave the system in an
821                        ;; unsatisfactory state: if the symbol is a
822                        ;; external symbol of a package which is
823                        ;; already used by this package, and has also
824                        ;; been imported, then uninterning it from this
825                        ;; package will still leave it visible!
826                        ;;
827                        ;; (DEFPACKAGE "FOO" (:EXPORT "SYM"))
828                        ;; (DEFPACKAGE "BAR" (:EXPORT "SYM"))
829                        ;; (DEFPACKAGE "BAZ" (:USE "FOO"))
830                        ;; (IMPORT 'FOO:SYM "BAZ")
831                        ;; (USE-PACKAGE "BAR" "BAZ")
832                        ;;
833                        ;; Now (UNINTERN 'FOO:SYM "BAZ") doesn't
834                        ;; resolve the conflict. :-(
835                        ;;
836                        ;; -- CSR, 2004-10-20
837                        (list (make-restart
838                               :name (make-symbol "UNINTERN")
839                               :function (lambda ()
840                                           (unintern s package)
841                                           (import
842                                            (find s symbols :test-not #'eq)
843                                            package)
844                                           (return-from name-conflict))
845                               :report-function
846                               (lambda (stream)
847                                 (format stream
848                                         "Unintern ~S from ~A and import ~S."
849                                         s
850                                         (package-%name package)
851                                         (find s symbols :test-not #'eq))))))))
852                    (t (list (make-restart
853                              :name (make-symbol "SHADOWING-IMPORT")
854                              :function (lambda ()
855                                          (shadowing-import s package)
856                                          (return-from name-conflict))
857                              :report-function
858                              (lambda (stream)
859                                (format stream "Shadowing-import ~S into ~A."
860                                        s (package-%name package)))))))))
861              symbols)
862             *restart-clusters*)))
863       (with-condition-restarts condition (car *restart-clusters*)
864         (with-simple-restart (abort "Leave action undone.")
865           (error condition))))))
866
867 ;;; If we are uninterning a shadowing symbol, then a name conflict can
868 ;;; result, otherwise just nuke the symbol.
869 (defun unintern (symbol &optional (package (sane-package)))
870   #!+sb-doc
871   "Makes SYMBOL no longer present in PACKAGE. If SYMBOL was present
872   then T is returned, otherwise NIL. If PACKAGE is SYMBOL's home
873   package, then it is made uninterned."
874   (let* ((package (find-undeleted-package-or-lose package))
875          (name (symbol-name symbol))
876          (shadowing-symbols (package-%shadowing-symbols package)))
877     (declare (list shadowing-symbols))
878
879     (with-single-package-locked-error ()
880       (when (find-symbol name package)
881         (assert-package-unlocked package "uninterning ~A" name))
882       
883       ;; If a name conflict is revealed, give us a chance to
884       ;; shadowing-import one of the accessible symbols.
885       (when (member symbol shadowing-symbols)
886         (let ((cset ()))
887           (dolist (p (package-%use-list package))
888             (multiple-value-bind (s w) (find-external-symbol name p)
889               (when w (pushnew s cset))))
890           (when (cdr cset)
891             (apply #'name-conflict package 'unintern symbol cset)
892             (return-from unintern t)))
893         (setf (package-%shadowing-symbols package)
894               (remove symbol shadowing-symbols)))
895
896       (multiple-value-bind (s w) (find-symbol name package)
897         (declare (ignore s))
898         (cond ((or (eq w :internal) (eq w :external))
899                (nuke-symbol (if (eq w :internal)
900                                 (package-internal-symbols package)
901                                 (package-external-symbols package))
902                             name)
903                (if (eq (symbol-package symbol) package)
904                    (%set-symbol-package symbol nil))
905                t)
906               (t nil))))))
907 \f
908 ;;; Take a symbol-or-list-of-symbols and return a list, checking types.
909 (defun symbol-listify (thing)
910   (cond ((listp thing)
911          (dolist (s thing)
912            (unless (symbolp s) (error "~S is not a symbol." s)))
913          thing)
914         ((symbolp thing) (list thing))
915         (t
916          (error "~S is neither a symbol nor a list of symbols." thing))))
917
918 (defun string-listify (thing)
919   (mapcar #'string (if (listp thing) 
920                        thing 
921                        (list thing))))
922
923 ;;; This is like UNINTERN, except if SYMBOL is inherited, it chases
924 ;;; down the package it is inherited from and uninterns it there. Used
925 ;;; for name-conflict resolution. Shadowing symbols are not uninterned
926 ;;; since they do not cause conflicts.
927 (defun moby-unintern (symbol package)
928   (unless (member symbol (package-%shadowing-symbols package))
929     (or (unintern symbol package)
930         (let ((name (symbol-name symbol)))
931           (multiple-value-bind (s w) (find-symbol name package)
932             (declare (ignore s))
933             (when (eq w :inherited)
934               (dolist (q (package-%use-list package))
935                 (multiple-value-bind (u x) (find-external-symbol name q)
936                   (declare (ignore u))
937                   (when x
938                     (unintern symbol q)
939                     (return t))))))))))
940 \f
941 (defun export (symbols &optional (package (sane-package)))
942   #!+sb-doc
943   "Exports SYMBOLS from PACKAGE, checking that no name conflicts result."
944   (let ((package (find-undeleted-package-or-lose package))
945         (syms ()))
946     ;; Punt any symbols that are already external.
947     (dolist (sym (symbol-listify symbols))
948       (multiple-value-bind (s w)
949           (find-external-symbol (symbol-name sym) package)
950         (declare (ignore s))
951         (unless (or w (member sym syms))
952           (push sym syms))))
953     (with-single-package-locked-error ()
954       (when syms
955         (assert-package-unlocked package "exporting symbol~P ~{~A~^, ~}"
956                                  (length syms) syms))
957       ;; Find symbols and packages with conflicts.
958       (let ((used-by (package-%used-by-list package))
959             (cset ()))
960         (dolist (sym syms)
961           (let ((name (symbol-name sym)))
962             (dolist (p used-by)
963               (multiple-value-bind (s w) (find-symbol name p)
964                 (when (and w
965                            (not (eq s sym))
966                            (not (member s (package-%shadowing-symbols p))))
967                   ;; Beware: the name conflict is in package P, not in
968                   ;; PACKAGE.
969                   (name-conflict p 'export sym sym s)
970                   (pushnew sym cset))))))
971         (when cset
972           (setq syms (set-difference syms cset))))
973       ;; Check that all symbols are accessible. If not, ask to import them.
974       (let ((missing ())
975             (imports ()))
976         (dolist (sym syms)
977           (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
978             (cond ((not (and w (eq s sym)))
979                    (push sym missing))
980                   ((eq w :inherited)
981                    (push sym imports)))))
982         (when missing
983           (cerror
984            "~S these symbols into the ~A package."
985            (make-condition
986             'simple-package-error
987             :package package
988             :format-control
989             "~@<These symbols are not accessible in the ~A package:~2I~_~S~@:>"
990             :format-arguments (list (package-%name package) missing))
991            'import (package-%name package))
992           (import missing package))
993         (import imports package))
994
995       ;; And now, three pages later, we export the suckers.
996       (let ((internal (package-internal-symbols package))
997             (external (package-external-symbols package)))
998         (dolist (sym syms)
999           (nuke-symbol internal (symbol-name sym))
1000           (add-symbol external sym))))
1001       t))
1002 \f
1003 ;;; Check that all symbols are accessible, then move from external to internal.
1004 (defun unexport (symbols &optional (package (sane-package)))
1005   #!+sb-doc
1006   "Makes SYMBOLS no longer exported from PACKAGE."
1007   (let ((package (find-undeleted-package-or-lose package))
1008         (syms ()))
1009     (dolist (sym (symbol-listify symbols))
1010       (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1011         (cond ((or (not w) (not (eq s sym)))
1012                (error 'simple-package-error
1013                       :package package
1014                       :format-control "~S is not accessible in the ~A package."
1015                       :format-arguments (list sym (package-%name package))))
1016               ((eq w :external) (pushnew sym syms)))))
1017     (with-single-package-locked-error ()
1018       (when syms
1019         (assert-package-unlocked package "unexporting symbol~P ~{~A~^, ~}"
1020                                  (length syms) syms))
1021       (let ((internal (package-internal-symbols package))
1022             (external (package-external-symbols package)))
1023         (dolist (sym syms)
1024           (add-symbol internal sym)
1025           (nuke-symbol external (symbol-name sym)))))
1026     t))
1027 \f
1028 ;;; Check for name conflict caused by the import and let the user
1029 ;;; shadowing-import if there is.
1030 (defun import (symbols &optional (package (sane-package)))
1031   #!+sb-doc
1032   "Make SYMBOLS accessible as internal symbols in PACKAGE. If a symbol
1033   is already accessible then it has no effect. If a name conflict
1034   would result from the importation, then a correctable error is signalled."
1035   (let* ((package (find-undeleted-package-or-lose package))
1036          (symbols (symbol-listify symbols))
1037          (homeless (remove-if #'symbol-package symbols))
1038          (syms ()))
1039     (with-single-package-locked-error ()
1040       (dolist (sym symbols)
1041         (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1042           (cond ((not w)
1043                  (let ((found (member sym syms :test #'string=)))
1044                    (if found
1045                        (when (not (eq (car found) sym))
1046                          (name-conflict package 'import sym sym (car found)))
1047                        (push sym syms))))
1048                 ((not (eq s sym))
1049                  (name-conflict package 'import sym sym s))
1050                 ((eq w :inherited) (push sym syms)))))
1051       (when (or homeless syms)
1052         (let ((union (delete-duplicates (append homeless syms))))
1053           (assert-package-unlocked package "importing symbol~P ~{~A~^, ~}" 
1054                                    (length union) union)))
1055       ;; Add the new symbols to the internal hashtable.
1056       (let ((internal (package-internal-symbols package)))
1057         (dolist (sym syms)
1058           (add-symbol internal sym)))
1059       ;; If any of the symbols are uninterned, make them be owned by PACKAGE.
1060       (dolist (sym homeless)
1061         (%set-symbol-package sym package))
1062       t)))
1063 \f
1064 ;;; If a conflicting symbol is present, unintern it, otherwise just
1065 ;;; stick the symbol in.
1066 (defun shadowing-import (symbols &optional (package (sane-package)))
1067   #!+sb-doc
1068   "Import SYMBOLS into package, disregarding any name conflict. If
1069   a symbol of the same name is present, then it is uninterned."
1070   (let* ((package (find-undeleted-package-or-lose package))
1071          (internal (package-internal-symbols package))
1072          (symbols (symbol-listify symbols))
1073          (lock-asserted-p nil))
1074     (with-single-package-locked-error ()
1075       (dolist (sym symbols)
1076         (multiple-value-bind (s w) (find-symbol (symbol-name sym) package)
1077           (unless (or lock-asserted-p 
1078                       (and (eq s sym) 
1079                            (member s (package-shadowing-symbols package))))
1080             (assert-package-unlocked package "shadowing-importing symbol~P ~
1081                                            ~{~A~^, ~}" (length symbols) symbols)
1082             (setf lock-asserted-p t))
1083           (unless (and w (not (eq w :inherited)) (eq s sym))
1084             (when (or (eq w :internal) (eq w :external))
1085               ;; If it was shadowed, we don't want UNINTERN to flame out...
1086               (setf (package-%shadowing-symbols package)
1087                     (remove s (the list (package-%shadowing-symbols package))))
1088               (unintern s package))
1089             (add-symbol internal sym))
1090           (pushnew sym (package-%shadowing-symbols package))))))
1091   t)
1092
1093 (defun shadow (symbols &optional (package (sane-package)))
1094   #!+sb-doc
1095   "Make an internal symbol in PACKAGE with the same name as each of
1096   the specified SYMBOLS. If a symbol with the given name is already
1097   present in PACKAGE, then the existing symbol is placed in the
1098   shadowing symbols list if it is not already present."
1099   (let* ((package (find-undeleted-package-or-lose package))
1100          (internal (package-internal-symbols package))
1101          (symbols (string-listify symbols))
1102          (lock-asserted-p nil))
1103     (flet ((present-p (w)
1104              (and w (not (eq w :inherited)))))
1105       (with-single-package-locked-error ()
1106         (dolist (name symbols)
1107           (multiple-value-bind (s w) (find-symbol name package)
1108             (unless (or lock-asserted-p 
1109                         (and (present-p w)
1110                              (member s (package-shadowing-symbols package))))
1111               (assert-package-unlocked package "shadowing symbol~P ~{~A~^, ~}"
1112                                        (length symbols) symbols)
1113               (setf lock-asserted-p t))
1114             (unless (present-p w)
1115               (setq s (make-symbol name))
1116               (%set-symbol-package s package)
1117               (add-symbol internal s))
1118             (pushnew s (package-%shadowing-symbols package)))))))
1119   t)
1120 \f
1121 ;;; Do stuff to use a package, with all kinds of fun name-conflict checking.
1122 (defun use-package (packages-to-use &optional (package (sane-package)))
1123   #!+sb-doc
1124   "Add all the PACKAGES-TO-USE to the use list for PACKAGE so that
1125   the external symbols of the used packages are accessible as internal
1126   symbols in PACKAGE."
1127   (let ((packages (package-listify packages-to-use))
1128         (package (find-undeleted-package-or-lose package)))
1129
1130     ;; Loop over each package, USE'ing one at a time...
1131     (with-single-package-locked-error ()
1132       (dolist (pkg packages)
1133         (unless (member pkg (package-%use-list package))
1134           (assert-package-unlocked package "using package~P ~{~A~^, ~}"
1135                                    (length packages) packages)
1136           (let ((shadowing-symbols (package-%shadowing-symbols package))
1137                 (use-list (package-%use-list package)))
1138           
1139             ;; If the number of symbols already accessible is less
1140             ;; than the number to be inherited then it is faster to
1141             ;; run the test the other way. This is particularly
1142             ;; valuable in the case of a new package USEing
1143             ;; COMMON-LISP.
1144             (cond
1145               ((< (+ (package-internal-symbol-count package)
1146                      (package-external-symbol-count package)
1147                      (let ((res 0))
1148                        (dolist (p use-list res)
1149                          (incf res (package-external-symbol-count p)))))
1150                   (package-external-symbol-count pkg))
1151                (do-symbols (sym package)
1152                  (multiple-value-bind (s w)
1153                      (find-external-symbol (symbol-name sym) pkg)
1154                    (when (and w
1155                               (not (eq s sym))
1156                               (not (member sym shadowing-symbols)))
1157                      (name-conflict package 'use-package pkg sym s))))
1158                (dolist (p use-list)
1159                  (do-external-symbols (sym p)
1160                    (multiple-value-bind (s w)
1161                        (find-external-symbol (symbol-name sym) pkg)
1162                      (when (and w
1163                                 (not (eq s sym))
1164                                 (not (member
1165                                       (find-symbol (symbol-name sym) package)
1166                                       shadowing-symbols)))
1167                        (name-conflict package 'use-package pkg sym s))))))
1168               (t
1169                (do-external-symbols (sym pkg)
1170                  (multiple-value-bind (s w)
1171                      (find-symbol (symbol-name sym) package)
1172                    (when (and w
1173                               (not (eq s sym))
1174                               (not (member s shadowing-symbols)))
1175                      (name-conflict package 'use-package pkg sym s)))))))
1176           
1177           (push pkg (package-%use-list package))
1178           (push (package-external-symbols pkg) (cdr (package-tables package)))
1179           (push package (package-%used-by-list pkg))))))
1180   t)
1181
1182 (defun unuse-package (packages-to-unuse &optional (package (sane-package)))
1183   #!+sb-doc
1184   "Remove PACKAGES-TO-UNUSE from the USE list for PACKAGE."
1185   (let ((package (find-undeleted-package-or-lose package))
1186         (packages (package-listify packages-to-unuse)))
1187     (with-single-package-locked-error ()
1188       (dolist (p packages)
1189         (when (member p (package-use-list package))
1190           (assert-package-unlocked package "unusing package~P ~{~A~^, ~}"
1191                                    (length packages) packages))
1192         (setf (package-%use-list package)
1193               (remove p (the list (package-%use-list package))))
1194         (setf (package-tables package)
1195               (delete (package-external-symbols p)
1196                       (the list (package-tables package))))
1197         (setf (package-%used-by-list p)
1198               (remove package (the list (package-%used-by-list p))))))
1199     t))
1200
1201 (defun find-all-symbols (string-or-symbol)
1202   #!+sb-doc
1203   "Return a list of all symbols in the system having the specified name."
1204   (let ((string (string string-or-symbol))
1205         (res ()))
1206     (maphash (lambda (k v)
1207                (declare (ignore k))
1208                (multiple-value-bind (s w) (find-symbol string v)
1209                  (when w (pushnew s res))))
1210              *package-names*)
1211     res))
1212 \f
1213 ;;;; APROPOS and APROPOS-LIST
1214
1215 (defun briefly-describe-symbol (symbol)
1216   (fresh-line)
1217   (prin1 symbol)
1218   (when (boundp symbol)
1219     (write-string " (bound)"))
1220   (when (fboundp symbol)
1221     (write-string " (fbound)")))
1222
1223 (defun apropos-list (string-designator
1224                      &optional
1225                      package-designator
1226                      external-only)
1227   #!+sb-doc
1228   "Like APROPOS, except that it returns a list of the symbols found instead
1229   of describing them."
1230   (if package-designator
1231       (let ((package (find-undeleted-package-or-lose package-designator))
1232             (string (stringify-name string-designator "APROPOS search"))
1233             (result nil))
1234         (do-symbols (symbol package)
1235           (when (and (eq (symbol-package symbol) package)
1236                      (or (not external-only)
1237                          (eq (nth-value 1 (find-symbol (symbol-name symbol)
1238                                                        package))
1239                              :external))
1240                      (search string (symbol-name symbol) :test #'char-equal))
1241             (push symbol result)))
1242         result)
1243       (mapcan (lambda (package)
1244                 (apropos-list string-designator package external-only))
1245               (list-all-packages))))
1246
1247 (defun apropos (string-designator &optional package external-only)
1248   #!+sb-doc
1249   "Briefly describe all symbols which contain the specified STRING.
1250   If PACKAGE is supplied then only describe symbols present in
1251   that package. If EXTERNAL-ONLY then only describe
1252   external symbols in the specified package."
1253   ;; Implementing this in terms of APROPOS-LIST keeps things simple at the cost
1254   ;; of some unnecessary consing; and the unnecessary consing shouldn't be an
1255   ;; issue, since this function is is only useful interactively anyway, and
1256   ;; we can cons and GC a lot faster than the typical user can read..
1257   (dolist (symbol (apropos-list string-designator package external-only))
1258     (briefly-describe-symbol symbol))
1259   (values))
1260 \f
1261 ;;;; final initialization
1262
1263 ;;;; The cold loader (GENESIS) makes the data structure in
1264 ;;;; *!INITIAL-SYMBOLS*. We grovel over it, making the specified
1265 ;;;; packages and interning the symbols. For a description of the
1266 ;;;; format of *!INITIAL-SYMBOLS*, see the GENESIS source.
1267
1268 (defvar *!initial-symbols*)
1269
1270 (!cold-init-forms
1271
1272   (setq *in-package-init* t)
1273
1274   (/show0 "about to loop over *!INITIAL-SYMBOLS* to make packages")
1275   (dolist (spec *!initial-symbols*)
1276     (let* ((pkg (apply #'make-package (first spec)))
1277            (internal (package-internal-symbols pkg))
1278            (external (package-external-symbols pkg)))
1279       (/show0 "back from MAKE-PACKAGE, PACKAGE-NAME=..")
1280       (/primitive-print (package-name pkg))
1281
1282       ;; Put internal symbols in the internal hashtable and set package.
1283       (dolist (symbol (second spec))
1284         (add-symbol internal symbol)
1285         (%set-symbol-package symbol pkg))
1286
1287       ;; External symbols same, only go in external table.
1288       (dolist (symbol (third spec))
1289         (add-symbol external symbol)
1290         (%set-symbol-package symbol pkg))
1291
1292       ;; Don't set package for imported symbols.
1293       (dolist (symbol (fourth spec))
1294         (add-symbol internal symbol))
1295       (dolist (symbol (fifth spec))
1296         (add-symbol external symbol))
1297
1298       ;; Put shadowing symbols in the shadowing symbols list.
1299       (setf (package-%shadowing-symbols pkg) (sixth spec))
1300       ;; Set the package documentation
1301       (setf (package-doc-string pkg) (seventh spec))))
1302
1303   ;; FIXME: These assignments are also done at toplevel in
1304   ;; boot-extensions.lisp. They should probably only be done once.
1305   (/show0 "setting up *CL-PACKAGE* and *KEYWORD-PACKAGE*")
1306   (setq *cl-package* (find-package "COMMON-LISP"))
1307   (setq *keyword-package* (find-package "KEYWORD"))
1308
1309   (/show0 "about to MAKUNBOUND *!INITIAL-SYMBOLS*")
1310   (makunbound '*!initial-symbols*)       ; (so that it gets GCed)
1311
1312   ;; Make some other packages that should be around in the cold load.
1313   ;; The COMMON-LISP-USER package is required by the ANSI standard,
1314   ;; but not completely specified by it, so in the cross-compilation
1315   ;; host Lisp it could contain various symbols, USE-PACKAGEs, or
1316   ;; nicknames that we don't want in our target SBCL. For that reason,
1317   ;; we handle it specially, not dumping the host Lisp version at
1318   ;; genesis time..
1319   (aver (not (find-package "COMMON-LISP-USER")))
1320   ;; ..but instead making our own from scratch here.
1321   (/show0 "about to MAKE-PACKAGE COMMON-LISP-USER")
1322   (make-package "COMMON-LISP-USER"
1323                 :nicknames '("CL-USER")
1324                 :use '("COMMON-LISP"
1325                        ;; ANSI encourages us to put extension packages
1326                        ;; in the USE list of COMMON-LISP-USER.
1327                        "SB!ALIEN" "SB!ALIEN" "SB!DEBUG"
1328                        "SB!EXT" "SB!GRAY" "SB!PROFILE"))
1329
1330   ;; Now do the *!DEFERRED-USE-PACKAGES*.
1331   (/show0 "about to do *!DEFERRED-USE-PACKAGES*")
1332   (dolist (args *!deferred-use-packages*)
1333     (apply #'use-package args))
1334
1335   ;; The Age Of Magic is over, we can behave ANSIly henceforth.
1336   (/show0 "about to SETQ *IN-PACKAGE-INIT*")
1337   (setq *in-package-init* nil)
1338
1339   ;; For the kernel core image wizards, set the package to *CL-PACKAGE*.
1340   ;;
1341   ;; FIXME: We should just set this to (FIND-PACKAGE
1342   ;; "COMMON-LISP-USER") once and for all here, instead of setting it
1343   ;; once here and resetting it later.
1344   (setq *package* *cl-package*))
1345 \f
1346 (!cold-init-forms
1347   (/show0 "done with !PACKAGE-COLD-INIT"))
1348
1349 (!defun-from-collected-cold-init-forms !package-cold-init)