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