Get genesis to execute some cold %SVSET toplevel forms.
[sbcl.git] / src / code / cold-init.lisp
blobb76441c1fa632043a9984e2245d5c8cb572cca58
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
5 ;;;; more information.
6 ;;;;
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
23 ;;; uninterned.
24 ;;;
25 ;;; FIXME: Are there other tables that need to have entries removed?
26 ;;; What about symbols of the form DEF!FOO?
27 (defun !unintern-init-only-stuff ()
28 (flet ((uninternable-p (symbol)
29 (let ((name (symbol-name symbol)))
30 (or (and (>= (length name) 1) (char= (char name 0) #\!))
31 (and (>= (length name) 2) (string= name "*!" :end1 2))
32 (memq symbol
33 ;; DEF!METHOD need no longer be accessible,
34 ;; but *DELAYED-DEF!METHOD-ARGS* remains,
35 ;; due to a reference from pcl/methods.lisp.
36 ;; It would be nice to fix that.
37 '(def!method
38 sb!c::sb!pcl sb!c::sb!impl sb!c::sb!kernel
39 sb!c::sb!c sb!c::sb!int))))))
40 ;; A structure constructor name, in particular !MAKE-SAETP,
41 ;; can't be uninterned if referenced by a defstruct-description.
42 ;; So loop over all structure classoids and clobber any
43 ;; symbol that should be uninternable.
44 (maphash (lambda (classoid layout)
45 (when (structure-classoid-p classoid)
46 (let ((dd (layout-info layout)))
47 (setf (dd-constructors dd)
48 (delete-if (lambda (x)
49 (and (consp x) (uninternable-p (car x))))
50 (dd-constructors dd))))))
51 (classoid-subclasses (find-classoid t)))
52 ;; Todo: perform one pass, then a full GC, then a final pass to confirm
53 ;; it worked. It shoud be an error if any uninternable symbols remain,
54 ;; but at present there are about 13 other "!" symbols with referers.
55 (with-package-iterator (iter (list-all-packages) :internal :external)
56 (loop (multiple-value-bind (winp symbol accessibility package) (iter)
57 (declare (ignore accessibility))
58 (unless winp
59 (return))
60 (when (uninternable-p symbol)
61 ;; Uninternable symbols which are referenced by other stuff
62 ;; can't disappear from the image, but we don't need to preserve
63 ;; their functions, so FMAKUNBOUND them. This doesn't have
64 ;; the intended effect if the function shares a code-component
65 ;; with non-cold-init lambdas, such as in !CONSTANTP-COLD-INIT
66 ;; and !GLOBALDB-COLD-INIT. Though the cold-init function is
67 ;; never called post-build, it is not discarded. Also, I suspect
68 ;; that the following loop should print nothing, but it does:
70 (sb-vm::map-allocated-objects
71 (lambda (obj type size)
72 (declare (ignore size))
73 (when (= type sb-vm:code-header-widetag)
74 (let ((name (sb-c::debug-info-name
75 (sb-kernel:%code-debug-info obj))))
76 (when (and (stringp name) (search "COLD-INIT-FORMS" name))
77 (print obj)))))
78 :dynamic)
80 (fmakunbound symbol)
81 (unintern symbol package)))))))
83 ;;;; putting ourselves out of our misery when things become too much to bear
85 (declaim (ftype (function (simple-string) nil) !cold-lose))
86 (defun !cold-lose (msg)
87 (%primitive print msg)
88 (%primitive print "too early in cold init to recover from errors")
89 (%halt))
91 ;;; last-ditch error reporting for things which should never happen
92 ;;; and which, if they do happen, are sufficiently likely to torpedo
93 ;;; the normal error-handling system that we want to bypass it
94 (declaim (ftype (function (simple-string) nil) critically-unreachable))
95 (defun critically-unreachable (where)
96 (%primitive print "internal error: Control should never reach here, i.e.")
97 (%primitive print where)
98 (%halt))
100 ;;;; !COLD-INIT
102 ;;; a list of toplevel things set by GENESIS
103 (defvar *!reversed-cold-toplevels*)
104 (!defvar *!reversed-cold-setf-macros* nil) ; just SETF macros
105 (!defvar *!reversed-cold-defuns* nil) ; just DEFUNs
107 ;;; a SIMPLE-VECTOR set by GENESIS
108 (defvar *!load-time-values*)
110 (eval-when (:compile-toplevel :execute)
111 ;; FIXME: Perhaps we should make SHOW-AND-CALL-AND-FMAKUNBOUND, too,
112 ;; and use it for most of the cold-init functions. (Just be careful
113 ;; not to use it for the COLD-INIT-OR-REINIT functions.)
114 (sb!xc:defmacro show-and-call (name)
115 `(progn
116 (/primitive-print ,(symbol-name name))
117 (,name))))
119 ;;; called when a cold system starts up
120 (defun !cold-init ()
121 #!+sb-doc "Give the world a shove and hope it spins."
123 #!+sb-show
124 (sb!int::cannot-/show "Test of CANNOT-/SHOW [don't worry - this is expected]")
125 (/show0 "entering !COLD-INIT")
126 (setq *readtable* (make-readtable)
127 *previous-case* nil
128 *previous-readtable-case* nil
129 *print-length* 6 *print-level* 3)
130 #!-win32
131 (write-string "COLD-INIT... "
132 (setq *error-output* (!make-cold-stderr-stream)
133 *standard-output* *error-output*
134 *trace-output* *error-output*))
136 ;; Assert that FBOUNDP doesn't choke when its answer is NIL.
137 ;; It was fine if T because in that case the legality of the arg is certain.
138 ;; And be extra paranoid - ensure that it really gets called.
139 (locally (declare (notinline fboundp)) (fboundp '(setf !zzzzzz)))
141 ;; Putting data in a synchronized hashtable (*PACKAGE-NAMES*)
142 ;; requires that the main thread be properly initialized.
143 (show-and-call thread-init-or-reinit)
144 ;; Printing of symbols requires that packages be filled in, because
145 ;; OUTPUT-SYMBOL calls FIND-SYMBOL to determine accessibility.
146 (show-and-call !package-cold-init)
147 ;; Fill in the printer's character attribute tables now.
148 ;; If Genesis could write constant arrays into a target core,
149 ;; that would be nice, and would tidy up some other things too.
150 (show-and-call !printer-cold-init)
151 #!-win32
152 (progn (prin1 `(package = ,(package-name *package*)))
153 (terpri))
155 ;; Anyone might call RANDOM to initialize a hash value or something;
156 ;; and there's nothing which needs to be initialized in order for
157 ;; this to be initialized, so we initialize it right away.
158 (show-and-call !random-cold-init)
160 ;; Must be done before any non-opencoded array references are made.
161 (show-and-call !hairy-data-vector-reffer-init)
163 (show-and-call !character-database-cold-init)
164 (show-and-call !character-name-database-cold-init)
165 (show-and-call sb!unicode::!unicode-properties-cold-init)
167 ;; All sorts of things need INFO and/or (SETF INFO).
168 (/show0 "about to SHOW-AND-CALL !GLOBALDB-COLD-INIT")
169 (show-and-call !globaldb-cold-init)
171 ;; Various toplevel forms call MAKE-ARRAY, which calls SUBTYPEP, so
172 ;; the basic type machinery needs to be initialized before toplevel
173 ;; forms run.
174 (show-and-call !type-class-cold-init)
175 (show-and-call !typedefs-cold-init)
176 (show-and-call !world-lock-cold-init)
177 (show-and-call !classes-cold-init)
178 (show-and-call !early-type-cold-init)
179 (show-and-call !late-type-cold-init)
180 ;; See comment at the DEFUN explaining why there are 2 of them.
181 (show-and-call sb!kernel::!late-type-cold-init2)
182 (show-and-call !alien-type-cold-init)
183 (show-and-call !target-type-cold-init)
184 ;; FIXME: It would be tidy to make sure that that these cold init
185 ;; functions are called in the same relative order as the toplevel
186 ;; forms of the corresponding source files.
188 (show-and-call !policy-cold-init-or-resanify)
189 (/show0 "back from !POLICY-COLD-INIT-OR-RESANIFY")
191 (show-and-call !constantp-cold-init)
192 ;; Must be done before toplevel forms are invoked
193 ;; because a toplevel defstruct will need to add itself
194 ;; to the subclasses of STRUCTURE-OBJECT.
195 (show-and-call sb!kernel::!set-up-structure-object-class)
197 (dolist (x (nreverse *!reversed-cold-setf-macros*))
198 (apply #'!quietly-defsetf x))
199 (dolist (x (nreverse *!reversed-cold-defuns*))
200 (destructuring-bind (name &optional docstring . inline-expansion) x
201 (!%quietly-defun name docstring inline-expansion)))
203 ;; KLUDGE: Why are fixups mixed up with toplevel forms? Couldn't
204 ;; fixups be done separately? Wouldn't that be clearer and better?
205 ;; -- WHN 19991204
206 (/show0 "doing cold toplevel forms and fixups")
207 (/show0 "(LISTP *!REVERSED-COLD-TOPLEVELS*)=..")
208 (/hexstr (if (listp *!reversed-cold-toplevels*) "true" "NIL"))
209 #!-win32
210 (progn (write `("Length(TLFs)= " ,(length *!reversed-cold-toplevels*)))
211 (terpri))
212 #!+win32
213 (progn (/show0 "about to calculate (LENGTH *!REVERSED-COLD-TOPLEVELS*)")
214 (/show0 "(LENGTH *!REVERSED-COLD-TOPLEVELS*)=..")
215 #!+sb-show (let ((r-c-tl-length (length *!reversed-cold-toplevels*)))
216 (/show0 "(length calculated..)")
217 (let ((hexstr (hexstr r-c-tl-length)))
218 (/show0 "(hexstr calculated..)")
219 (/primitive-print hexstr))))
220 (let (#!+sb-show (index-in-cold-toplevels 0))
221 #!+sb-show (declare (type fixnum index-in-cold-toplevels))
223 (dolist (toplevel-thing (prog1
224 (nreverse *!reversed-cold-toplevels*)
225 ;; (Now that we've NREVERSEd it, it's
226 ;; somewhat scrambled, so keep anyone
227 ;; else from trying to get at it.)
228 (makunbound '*!reversed-cold-toplevels*)))
229 #!+sb-show
230 (when (zerop (mod index-in-cold-toplevels 1024))
231 (/show0 "INDEX-IN-COLD-TOPLEVELS=..")
232 (/hexstr index-in-cold-toplevels))
233 #!+sb-show
234 (setf index-in-cold-toplevels
235 (the fixnum (1+ index-in-cold-toplevels)))
236 (typecase toplevel-thing
237 (function
238 (funcall toplevel-thing))
239 (cons
240 (case (first toplevel-thing)
241 (:load-time-value
242 (setf (svref *!load-time-values* (third toplevel-thing))
243 (funcall (second toplevel-thing))))
244 (:load-time-value-fixup
245 (setf (sap-ref-word (int-sap (get-lisp-obj-address (second toplevel-thing)))
246 (third toplevel-thing))
247 (get-lisp-obj-address
248 (svref *!load-time-values* (fourth toplevel-thing)))))
249 (defstruct
250 (apply 'sb!kernel::%defstruct (cdr toplevel-thing)))
252 (!cold-lose "bogus fixup code in *!REVERSED-COLD-TOPLEVELS*"))))
253 (t (!cold-lose "bogus operation in *!REVERSED-COLD-TOPLEVELS*")))))
254 (/show0 "done with loop over cold toplevel forms and fixups")
256 ;; Set sane values again, so that the user sees sane values instead
257 ;; of whatever is left over from the last DECLAIM/PROCLAIM.
258 (show-and-call !policy-cold-init-or-resanify)
260 ;; Only do this after toplevel forms have run, 'cause that's where
261 ;; DEFTYPEs are.
262 (setf *type-system-initialized* t)
264 ;; now that the type system is definitely initialized, fixup UNKNOWN
265 ;; types that have crept in.
266 (show-and-call !fixup-type-cold-init)
267 ;; run the PROCLAIMs.
268 (show-and-call !late-proclaim-cold-init)
270 (show-and-call os-cold-init-or-reinit)
271 (show-and-call !pathname-cold-init)
272 (show-and-call !debug-info-cold-init)
274 (show-and-call stream-cold-init-or-reset)
275 (show-and-call !loader-cold-init)
276 (show-and-call !foreign-cold-init)
277 #!-(and win32 (not sb-thread))
278 (show-and-call signal-cold-init-or-reinit)
279 (/show0 "enabling internal errors")
280 (setf (extern-alien "internal_errors_enabled" int) 1)
282 (show-and-call float-cold-init-or-reinit)
284 (show-and-call !class-finalize)
286 ;; The reader and printer are initialized very late, so that they
287 ;; can do hairy things like invoking the compiler as part of their
288 ;; initialization.
289 (let ((*readtable* (make-readtable)))
290 (show-and-call !reader-cold-init)
291 (show-and-call !sharpm-cold-init)
292 (show-and-call !backq-cold-init)
293 ;; The *STANDARD-READTABLE* is assigned at last because the above
294 ;; functions would operate on the standard readtable otherwise---
295 ;; which would result in an error.
296 (setf *standard-readtable* *readtable*))
297 (setf *readtable* (copy-readtable *standard-readtable*))
298 (setf sb!debug:*debug-readtable* (copy-readtable *standard-readtable*))
299 (sb!pretty:!pprint-cold-init)
300 (setq *print-level* nil *print-length* nil) ; restore defaults
302 ;; the ANSI-specified initial value of *PACKAGE*
303 (setf *package* (find-package "COMMON-LISP-USER"))
305 (!enable-infinite-error-protector)
307 ; hppa heap is segmented, lisp and c uses a stub to call eachother
308 #!+hpux (%primitive sb!vm::setup-return-from-lisp-stub)
309 ;; The system is finally ready for GC.
310 (/show0 "enabling GC")
311 (setq *gc-inhibit* nil)
312 (/show0 "doing first GC")
313 (gc :full t)
314 (/show0 "back from first GC")
316 ;; The show is on.
317 (terpri)
318 (/show0 "going into toplevel loop")
319 (handling-end-of-the-world
320 (toplevel-init)
321 (critically-unreachable "after TOPLEVEL-INIT")))
323 (define-deprecated-function :early "1.0.56.55" quit (exit sb!thread:abort-thread)
324 (&key recklessly-p (unix-status 0))
325 (if (or recklessly-p (sb!thread:main-thread-p))
326 (exit :code unix-status :abort recklessly-p)
327 (sb!thread:abort-thread))
328 (critically-unreachable "after trying to die in QUIT"))
330 (declaim (ftype (sfunction (&key (:code (or null exit-code))
331 (:timeout (or null real))
332 (:abort t))
333 nil)
334 exit))
335 (defun exit (&key code abort (timeout *exit-timeout*))
336 #!+sb-doc
337 "Terminates the process, causing SBCL to exit with CODE. CODE
338 defaults to 0 when ABORT is false, and 1 when it is true.
340 When ABORT is false (the default), current thread is first unwound,
341 *EXIT-HOOKS* are run, other threads are terminated, and standard
342 output streams are flushed before SBCL calls exit(3) -- at which point
343 atexit(3) functions will run. If multiple threads call EXIT with ABORT
344 being false, the first one to call it will complete the protocol.
346 When ABORT is true, SBCL exits immediately by calling _exit(2) without
347 unwinding stack, or calling exit hooks. Note that _exit(2) does not
348 call atexit(3) functions unlike exit(3).
350 Recursive calls to EXIT cause EXIT to behave as it ABORT was true.
352 TIMEOUT controls waiting for other threads to terminate when ABORT is
353 NIL. Once current thread has been unwound and *EXIT-HOOKS* have been
354 run, spawning new threads is prevented and all other threads are
355 terminated by calling TERMINATE-THREAD on them. The system then waits
356 for them to finish using JOIN-THREAD, waiting at most a total TIMEOUT
357 seconds for all threads to join. Those threads that do not finish
358 in time are simply ignored while the exit protocol continues. TIMEOUT
359 defaults to *EXIT-TIMEOUT*, which in turn defaults to 60. TIMEOUT NIL
360 means to wait indefinitely.
362 Note that TIMEOUT applies only to JOIN-THREAD, not *EXIT-HOOKS*. Since
363 TERMINATE-THREAD is asynchronous, getting multithreaded application
364 termination with complex cleanups right using it can be tricky. To
365 perform an orderly synchronous shutdown use an exit hook instead of
366 relying on implicit thread termination.
368 Consequences are unspecified if serious conditions occur during EXIT
369 excepting errors from *EXIT-HOOKS*, which cause warnings and stop
370 execution of the hook that signaled, but otherwise allow the exit
371 process to continue normally."
372 (if (or abort *exit-in-process*)
373 (os-exit (or code 1) :abort t)
374 (let ((code (or code 0)))
375 (with-deadline (:seconds nil :override t)
376 (sb!thread:grab-mutex *exit-lock*))
377 (setf *exit-in-process* code
378 *exit-timeout* timeout)
379 (throw '%end-of-the-world t)))
380 (critically-unreachable "After trying to die in EXIT."))
382 ;;;; initialization functions
384 (defun thread-init-or-reinit ()
385 (sb!thread::init-initial-thread)
386 (sb!thread::init-job-control)
387 (sb!thread::get-foreground))
389 (defun reinit ()
390 #!+win32
391 (setf sb!win32::*ansi-codepage* nil)
392 (setf *default-external-format* nil)
393 (setf sb!alien::*default-c-string-external-format* nil)
394 ;; WITHOUT-GCING implies WITHOUT-INTERRUPTS.
395 (without-gcing
396 ;; Initialize streams first, so that any errors can be printed later
397 (stream-reinit t)
398 (os-cold-init-or-reinit)
399 (thread-init-or-reinit)
400 #!-(and win32 (not sb-thread))
401 (signal-cold-init-or-reinit)
402 (setf (extern-alien "internal_errors_enabled" int) 1)
403 (float-cold-init-or-reinit))
404 (gc-reinit)
405 (foreign-reinit)
406 (time-reinit)
407 ;; If the debugger was disabled in the saved core, we need to
408 ;; re-disable ldb again.
409 (when (eq *invoke-debugger-hook* 'sb!debug::debugger-disabled-hook)
410 (sb!debug::disable-debugger))
411 (call-hooks "initialization" *init-hooks*))
413 ;;;; some support for any hapless wretches who end up debugging cold
414 ;;;; init code
416 ;;; Decode THING into hexadecimal notation using only machinery
417 ;;; available early in cold init.
418 #!+sb-show
419 (defun hexstr (thing)
420 (/noshow0 "entering HEXSTR")
421 (let* ((addr (get-lisp-obj-address thing))
422 (nchars (* sb!vm:n-word-bytes 2))
423 (str (make-string (+ nchars 2) :element-type 'base-char)))
424 (/noshow0 "ADDR and STR calculated")
425 (setf (char str 0) #\0
426 (char str 1) #\x)
427 (/noshow0 "CHARs 0 and 1 set")
428 (dotimes (i nchars)
429 (/noshow0 "at head of DOTIMES loop")
430 (let* ((nibble (ldb (byte 4 0) addr))
431 (chr (char "0123456789abcdef" nibble)))
432 (declare (type (unsigned-byte 4) nibble)
433 (base-char chr))
434 (/noshow0 "NIBBLE and CHR calculated")
435 (setf (char str (- (1+ nchars) i)) chr
436 addr (ash addr -4))))
437 str))
439 ;; But: you almost never need this. Just use WRITE in all its glory.
440 #!+sb-show
441 (defun cold-print (x)
442 (labels ((%cold-print (obj depthoid)
443 (if (> depthoid 4)
444 (%primitive print "...")
445 (typecase obj
446 (simple-string
447 (%primitive print obj))
448 (symbol
449 (%primitive print (symbol-name obj)))
450 (cons
451 (%primitive print "cons:")
452 (let ((d (1+ depthoid)))
453 (%cold-print (car obj) d)
454 (%cold-print (cdr obj) d)))
456 (%primitive print (hexstr obj)))))))
457 (%cold-print x 0))
458 (values))