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