1 ;;;; cold initialization stuff, plus some other miscellaneous stuff
2 ;;;; that we don't have any better place for
4 ;;;; This software is part of the SBCL system. See the README file for
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
13 (in-package "SB!IMPL")
15 ;;;; burning our ships behind us
17 ;;; There's a fair amount of machinery which is needed only at cold
18 ;;; init time, and should be discarded before freezing the final
19 ;;; system. We discard it by uninterning the associated symbols.
20 ;;; Rather than using a special table of symbols to be uninterned,
21 ;;; which might be tedious to maintain, instead we use a hack:
22 ;;; anything whose name matches a magic character pattern is
24 ;;; Additionally, you can specify an arbitrary way to destroy
25 ;;; random bootstrap stuff on per-package basis.
26 (defun !unintern-init-only-stuff
()
27 (dolist (package (list-all-packages))
28 (awhen (find-symbol "UNINTERN-INIT-ONLY-STUFF" package
)
29 (format t
"~&Calling ~/sb-impl::print-symbol-with-prefix/~%" it
)
31 (unintern it package
)))
32 (flet ((uninternable-p (symbol)
33 (let ((name (symbol-name symbol
)))
34 (or (and (>= (length name
) 1) (char= (char name
0) #\
!))
35 (and (>= (length name
) 2) (string= name
"*!" :end1
2))
37 '(sb!c
::sb
!pcl sb
!c
::sb
!impl sb
!c
::sb
!kernel
38 sb
!c
::sb
!c sb
!c
::sb
!int
))))))
39 ;; A structure constructor name, in particular !MAKE-SAETP,
40 ;; can't be uninterned if referenced by a defstruct-description.
41 ;; So loop over all structure classoids and clobber any
42 ;; symbol that should be uninternable.
43 (maphash (lambda (classoid layout
)
44 (when (structure-classoid-p classoid
)
45 (let ((dd (layout-info layout
)))
46 (setf (dd-constructors dd
)
47 (delete-if (lambda (x)
48 (and (consp x
) (uninternable-p (car x
))))
49 (dd-constructors dd
))))))
50 (classoid-subclasses (find-classoid t
)))
51 ;; Todo: perform one pass, then a full GC, then a final pass to confirm
52 ;; it worked. It shoud be an error if any uninternable symbols remain,
53 ;; but at present there are about 13 other "!" symbols with referers.
54 (with-package-iterator (iter (list-all-packages) :internal
:external
)
55 (loop (multiple-value-bind (winp symbol accessibility package
) (iter)
56 (declare (ignore accessibility
))
59 (when (uninternable-p symbol
)
60 ;; Uninternable symbols which are referenced by other stuff
61 ;; can't disappear from the image, but we don't need to preserve
62 ;; their functions, so FMAKUNBOUND them. This doesn't have
63 ;; the intended effect if the function shares a code-component
64 ;; with non-cold-init lambdas. Though the cold-init function is
65 ;; never called post-build, it is not discarded. Also, I suspect
66 ;; that the following loop should print nothing, but it does:
68 (sb-vm::map-allocated-objects
69 (lambda (obj type size
)
70 (declare (ignore size
))
71 (when (= type sb-vm
:code-header-widetag
)
72 (let ((name (sb-c::debug-info-name
73 (sb-kernel:%code-debug-info obj
))))
74 (when (and (stringp name
) (search "COLD-INIT-FORMS" name
))
79 (unintern symbol package
)))))))
81 ;;;; putting ourselves out of our misery when things become too much to bear
83 (declaim (ftype (function (simple-string) nil
) !cold-lose
))
84 (defun !cold-lose
(msg)
85 (%primitive print msg
)
86 (%primitive print
"too early in cold init to recover from errors")
89 ;;; last-ditch error reporting for things which should never happen
90 ;;; and which, if they do happen, are sufficiently likely to torpedo
91 ;;; the normal error-handling system that we want to bypass it
92 (declaim (ftype (function (simple-string) nil
) critically-unreachable
))
93 (defun critically-unreachable (where)
94 (%primitive print
"internal error: Control should never reach here, i.e.")
95 (%primitive print where
)
100 ;;; a list of toplevel things set by GENESIS
101 (defvar *!cold-toplevels
*) ; except for DEFUNs and SETF macros
102 (defvar *!cold-setf-macros
*) ; just SETF macros
103 (defvar *!cold-defconstants
*) ; just DEFCONSTANT-EQXs
104 (defvar *!cold-defuns
*) ; just DEFUNs
106 ;;; a SIMPLE-VECTOR set by GENESIS
107 (defvar *!load-time-values
*)
109 (eval-when (:compile-toplevel
:execute
)
110 ;; FIXME: Perhaps we should make SHOW-AND-CALL-AND-FMAKUNBOUND, too,
111 ;; and use it for most of the cold-init functions. (Just be careful
112 ;; not to use it for the COLD-INIT-OR-REINIT functions.)
113 (sb!xc
:defmacro show-and-call
(name)
115 (/primitive-print
,(symbol-name name
))
118 (defun !encapsulate-stuff-for-cold-init
(&aux names
)
119 (flet ((encapsulate-1 (name handler
)
120 (encapsulate name
'!cold-init handler
)
122 (encapsulate-1 '%failed-aver
124 ;; output the message before signaling error,
125 ;; as it may be this is too early in the cold init.
127 (write-line "failed AVER:")
134 (lambda (f designator
)
135 (cond ((packagep designator
) designator
)
136 (t (funcall f
(let ((s (string designator
)))
137 (if (eql (mismatch s
"SB!") 3)
138 (concatenate 'string
"SB-" (subseq s
3))
141 ;; Wrap thing-defining-functions that style-warn sufficiently early
142 ;; that HANDLER-BIND can't be used to suppress the warning
143 ;; (since condition classoids don't exist yet).
144 (flet ((warning-suppressor (signaler)
145 (lambda (f &rest args
)
146 (encapsulate signaler
'!cold-init
(constantly nil
))
148 (unencapsulate signaler
'!cold-init
)))) ; Restore it.
149 ;; %DEFUN complains about everything being redefined
150 (encapsulate-1 '%defun
(warning-suppressor 'warn
))
151 ;; %DEFCONSTANT complains about all named types because of earmuffs.
152 (encapsulate-1 'sb
!c
::%defconstant
(warning-suppressor 'style-warn
))
153 ;; %DEFSETF ',FN warns when #'(SETF fn) also has a function binding.
154 (encapsulate-1 '%defsetf
(warning-suppressor 'style-warn
))))
157 (defmacro !with-init-wrappers
(&rest forms
)
158 `(let ((wrapped-functions (!encapsulate-stuff-for-cold-init
)))
160 (dolist (f wrapped-functions
) (unencapsulate f
'!cold-init
))))
162 ;;; called when a cold system starts up
164 #!+sb-doc
"Give the world a shove and hope it spins."
167 (sb!int
::cannot-
/show
"Test of CANNOT-/SHOW [don't worry - this is expected]")
168 (/show0
"entering !COLD-INIT")
169 (setq *readtable
* (make-readtable)
171 *previous-readtable-case
* nil
172 *print-length
* 6 *print-level
* 3)
174 (write-string "COLD-INIT... "
175 (setq *error-output
* (!make-cold-stderr-stream
)
176 *standard-output
* *error-output
*
177 *trace-output
* *error-output
*))
179 ;; Assert that FBOUNDP doesn't choke when its answer is NIL.
180 ;; It was fine if T because in that case the legality of the arg is certain.
181 ;; And be extra paranoid - ensure that it really gets called.
182 (locally (declare (notinline fboundp
)) (fboundp '(setf !zzzzzz
)))
184 ;; Putting data in a synchronized hashtable (*PACKAGE-NAMES*)
185 ;; requires that the main thread be properly initialized.
186 (show-and-call thread-init-or-reinit
)
187 ;; Printing of symbols requires that packages be filled in, because
188 ;; OUTPUT-SYMBOL calls FIND-SYMBOL to determine accessibility.
189 (show-and-call !package-cold-init
)
190 ;; Fill in the printer's character attribute tables now.
191 ;; If Genesis could write constant arrays into a target core,
192 ;; that would be nice, and would tidy up some other things too.
193 (show-and-call !printer-cold-init
)
195 (progn (prin1 `(package = ,(package-name *package
*)))
198 ;; *RAW-SLOT-DATA* is essentially a compile-time constant
199 ;; but isn't dumpable as such because it has functions in it.
200 (show-and-call sb
!kernel
::!raw-slot-data-init
)
202 ;; Anyone might call RANDOM to initialize a hash value or something;
203 ;; and there's nothing which needs to be initialized in order for
204 ;; this to be initialized, so we initialize it right away.
205 (show-and-call !random-cold-init
)
207 ;; Must be done before any non-opencoded array references are made.
208 (show-and-call !hairy-data-vector-reffer-init
)
210 (show-and-call !character-database-cold-init
)
211 (show-and-call !character-name-database-cold-init
)
212 (show-and-call sb
!unicode
::!unicode-properties-cold-init
)
214 ;; All sorts of things need INFO and/or (SETF INFO).
215 (/show0
"about to SHOW-AND-CALL !GLOBALDB-COLD-INIT")
216 (show-and-call !globaldb-cold-init
)
218 ;; Various toplevel forms call MAKE-ARRAY, which calls SUBTYPEP, so
219 ;; the basic type machinery needs to be initialized before toplevel
221 (show-and-call !type-class-cold-init
)
222 (!with-init-wrappers
(show-and-call sb
!kernel
::!primordial-type-cold-init
))
223 (show-and-call !world-lock-cold-init
)
224 (show-and-call !classes-cold-init
)
225 (show-and-call !early-type-cold-init
)
226 (show-and-call !late-type-cold-init
)
227 (show-and-call !alien-type-cold-init
)
228 (show-and-call !target-type-cold-init
)
229 ;; FIXME: It would be tidy to make sure that that these cold init
230 ;; functions are called in the same relative order as the toplevel
231 ;; forms of the corresponding source files.
233 (show-and-call !policy-cold-init-or-resanify
)
234 (/show0
"back from !POLICY-COLD-INIT-OR-RESANIFY")
236 ;; Must be done before toplevel forms are invoked
237 ;; because a toplevel defstruct will need to add itself
238 ;; to the subclasses of STRUCTURE-OBJECT.
239 (show-and-call sb
!kernel
::!set-up-structure-object-class
)
241 (dolist (x *!cold-defconstants
*)
242 (destructuring-bind (name source-loc
&optional docstring
) x
243 (setf (info :variable
:kind name
) :constant
)
244 (when source-loc
(setf (info :source-location
:constant name
) source-loc
))
245 (when docstring
(setf (fdocumentation name
'variable
) docstring
))))
247 (dolist (x *!cold-defuns
*)
248 (destructuring-bind (name . inline-expansion
) x
249 (%defun
name (fdefinition name
) nil inline-expansion
))))
251 ;; KLUDGE: Why are fixups mixed up with toplevel forms? Couldn't
252 ;; fixups be done separately? Wouldn't that be clearer and better?
254 (/show0
"doing cold toplevel forms and fixups")
256 (progn (write `("Length(TLFs)= " ,(length *!cold-toplevels
*)))
260 (loop for index-in-cold-toplevels from
0
261 for toplevel-thing in
(prog1 *!cold-toplevels
*
262 (makunbound '*!cold-toplevels
*))
265 (when (zerop (mod index-in-cold-toplevels
1024))
266 (/show0
"INDEX-IN-COLD-TOPLEVELS=..")
267 (/hexstr index-in-cold-toplevels
))
268 (typecase toplevel-thing
270 (funcall toplevel-thing
))
271 ((cons (eql :load-time-value
))
272 (setf (svref *!load-time-values
* (third toplevel-thing
))
273 (funcall (second toplevel-thing
))))
274 ((cons (eql :load-time-value-fixup
))
275 (setf (sap-ref-word (int-sap (get-lisp-obj-address (second toplevel-thing
)))
276 (third toplevel-thing
))
277 (get-lisp-obj-address
278 (svref *!load-time-values
* (fourth toplevel-thing
)))))
279 ((cons (eql defstruct
))
280 (apply 'sb
!kernel
::%defstruct
(cdr toplevel-thing
)))
282 (!cold-lose
"bogus operation in *!COLD-TOPLEVELS*")))))
283 (/show0
"done with loop over cold toplevel forms and fixups")
285 (show-and-call time-reinit
)
287 ;; Set sane values again, so that the user sees sane values instead
288 ;; of whatever is left over from the last DECLAIM/PROCLAIM.
289 (show-and-call !policy-cold-init-or-resanify
)
291 ;; Only do this after toplevel forms have run, 'cause that's where
293 (setf *type-system-initialized
* t
)
295 ;; now that the type system is definitely initialized, fixup UNKNOWN
296 ;; types that have crept in.
297 (show-and-call !fixup-type-cold-init
)
298 ;; run the PROCLAIMs.
299 (show-and-call !late-proclaim-cold-init
)
301 (show-and-call os-cold-init-or-reinit
)
302 (show-and-call !pathname-cold-init
)
303 (show-and-call !debug-info-cold-init
)
305 (show-and-call stream-cold-init-or-reset
)
306 (show-and-call !loader-cold-init
)
307 (show-and-call !foreign-cold-init
)
308 #!-
(and win32
(not sb-thread
))
309 (show-and-call signal-cold-init-or-reinit
)
311 (show-and-call float-cold-init-or-reinit
)
313 (show-and-call !class-finalize
)
315 ;; The reader and printer are initialized very late, so that they
316 ;; can do hairy things like invoking the compiler as part of their
318 (let ((*readtable
* (make-readtable)))
319 (show-and-call !reader-cold-init
)
320 (show-and-call !sharpm-cold-init
)
321 (show-and-call !backq-cold-init
)
322 ;; The *STANDARD-READTABLE* is assigned at last because the above
323 ;; functions would operate on the standard readtable otherwise---
324 ;; which would result in an error.
325 (setf *standard-readtable
* *readtable
*))
326 (setf *readtable
* (copy-readtable *standard-readtable
*))
327 (setf sb
!debug
:*debug-readtable
* (copy-readtable *standard-readtable
*))
328 (sb!pretty
:!pprint-cold-init
)
329 (setq *print-level
* nil
*print-length
* nil
) ; restore defaults
331 ;; the ANSI-specified initial value of *PACKAGE*
332 (setf *package
* (find-package "COMMON-LISP-USER"))
334 ;; Enable normal (post-cold-init) behavior of INFINITE-ERROR-PROTECT.
335 (setf sb
!kernel
::*maximum-error-depth
* 10)
336 (/show0
"enabling internal errors")
337 (setf (extern-alien "internal_errors_enabled" int
) 1)
340 ; hppa heap is segmented, lisp and c uses a stub to call eachother
341 #!+hpux
(%primitive sb
!vm
::setup-return-from-lisp-stub
)
342 ;; The system is finally ready for GC.
343 (/show0
"enabling GC")
344 (setq *gc-inhibit
* nil
)
345 (/show0
"doing first GC")
347 (/show0
"back from first GC")
351 (/show0
"going into toplevel loop")
352 (handling-end-of-the-world
354 (critically-unreachable "after TOPLEVEL-INIT")))
356 (define-deprecated-function :early
"1.0.56.55" quit
(exit sb
!thread
:abort-thread
)
357 (&key recklessly-p
(unix-status 0))
358 (if (or recklessly-p
(sb!thread
:main-thread-p
))
359 (exit :code unix-status
:abort recklessly-p
)
360 (sb!thread
:abort-thread
))
361 (critically-unreachable "after trying to die in QUIT"))
363 (declaim (ftype (sfunction (&key
(:code
(or null exit-code
))
364 (:timeout
(or null real
))
368 (defun exit (&key code abort
(timeout *exit-timeout
*))
370 "Terminates the process, causing SBCL to exit with CODE. CODE
371 defaults to 0 when ABORT is false, and 1 when it is true.
373 When ABORT is false (the default), current thread is first unwound,
374 *EXIT-HOOKS* are run, other threads are terminated, and standard
375 output streams are flushed before SBCL calls exit(3) -- at which point
376 atexit(3) functions will run. If multiple threads call EXIT with ABORT
377 being false, the first one to call it will complete the protocol.
379 When ABORT is true, SBCL exits immediately by calling _exit(2) without
380 unwinding stack, or calling exit hooks. Note that _exit(2) does not
381 call atexit(3) functions unlike exit(3).
383 Recursive calls to EXIT cause EXIT to behave as it ABORT was true.
385 TIMEOUT controls waiting for other threads to terminate when ABORT is
386 NIL. Once current thread has been unwound and *EXIT-HOOKS* have been
387 run, spawning new threads is prevented and all other threads are
388 terminated by calling TERMINATE-THREAD on them. The system then waits
389 for them to finish using JOIN-THREAD, waiting at most a total TIMEOUT
390 seconds for all threads to join. Those threads that do not finish
391 in time are simply ignored while the exit protocol continues. TIMEOUT
392 defaults to *EXIT-TIMEOUT*, which in turn defaults to 60. TIMEOUT NIL
393 means to wait indefinitely.
395 Note that TIMEOUT applies only to JOIN-THREAD, not *EXIT-HOOKS*. Since
396 TERMINATE-THREAD is asynchronous, getting multithreaded application
397 termination with complex cleanups right using it can be tricky. To
398 perform an orderly synchronous shutdown use an exit hook instead of
399 relying on implicit thread termination.
401 Consequences are unspecified if serious conditions occur during EXIT
402 excepting errors from *EXIT-HOOKS*, which cause warnings and stop
403 execution of the hook that signaled, but otherwise allow the exit
404 process to continue normally."
405 (if (or abort
*exit-in-process
*)
406 (os-exit (or code
1) :abort t
)
407 (let ((code (or code
0)))
408 (with-deadline (:seconds nil
:override t
)
409 (sb!thread
:grab-mutex
*exit-lock
*))
410 (setf *exit-in-process
* code
411 *exit-timeout
* timeout
)
412 (throw '%end-of-the-world t
)))
413 (critically-unreachable "After trying to die in EXIT."))
415 ;;;; initialization functions
417 (defun thread-init-or-reinit ()
418 (sb!thread
::init-initial-thread
)
419 (sb!thread
::init-job-control
)
420 (sb!thread
::get-foreground
))
424 (setf sb
!win32
::*ansi-codepage
* nil
)
425 (setf *default-external-format
* nil
)
426 (setf sb
!alien
::*default-c-string-external-format
* nil
)
427 ;; WITHOUT-GCING implies WITHOUT-INTERRUPTS.
429 ;; Initialize streams first, so that any errors can be printed later
431 (os-cold-init-or-reinit)
432 (thread-init-or-reinit)
433 #!-
(and win32
(not sb-thread
))
434 (signal-cold-init-or-reinit)
435 (setf (extern-alien "internal_errors_enabled" int
) 1)
436 (float-cold-init-or-reinit))
440 ;; If the debugger was disabled in the saved core, we need to
441 ;; re-disable ldb again.
442 (when (eq *invoke-debugger-hook
* 'sb
!debug
::debugger-disabled-hook
)
443 (sb!debug
::disable-debugger
))
444 (call-hooks "initialization" *init-hooks
*))
446 ;;;; some support for any hapless wretches who end up debugging cold
449 ;;; Decode THING into hexadecimal notation using only machinery
450 ;;; available early in cold init.
452 (defun hexstr (thing)
453 (/noshow0
"entering HEXSTR")
454 (let* ((addr (get-lisp-obj-address thing
))
455 (nchars (* sb
!vm
:n-word-bytes
2))
456 (str (make-string (+ nchars
2) :element-type
'base-char
)))
457 (/noshow0
"ADDR and STR calculated")
458 (setf (char str
0) #\
0
460 (/noshow0
"CHARs 0 and 1 set")
462 (/noshow0
"at head of DOTIMES loop")
463 (let* ((nibble (ldb (byte 4 0) addr
))
464 (chr (char "0123456789abcdef" nibble
)))
465 (declare (type (unsigned-byte 4) nibble
)
467 (/noshow0
"NIBBLE and CHR calculated")
468 (setf (char str
(- (1+ nchars
) i
)) chr
469 addr
(ash addr -
4))))
472 ;; But: you almost never need this. Just use WRITE in all its glory.
474 (defun cold-print (x)
475 (labels ((%cold-print
(obj depthoid
)
477 (%primitive print
"...")
480 (%primitive print obj
))
482 (%primitive print
(symbol-name obj
)))
484 (%primitive print
"cons:")
485 (let ((d (1+ depthoid
)))
486 (%cold-print
(car obj
) d
)
487 (%cold-print
(cdr obj
) d
)))
489 (%primitive print
(hexstr obj
)))))))
493 (in-package "SB!INT")
494 (defun unintern-init-only-stuff ()
495 (let ((this-package (find-package "SB-INT")))
496 ;; For some reason uninterning these:
497 ;; DEF!TYPE DEF!CONSTANT DEF!STRUCT
498 ;; does not work, they stick around as uninterned symbols.
499 ;; Some other macros must expand into them. Ugh.
500 (dolist (s '(defenum defun-cached with-globaldb-name
503 #!-sb-show
(/hexstr
/nohexstr
/noshow
/noshow0
/noxhow
504 /primitive-print
/show
/show0
/xhow
)))
505 (unintern s this-package
))))