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