hexstr / cold-print fixes from Douglas Katzman
[sbcl.git] / src / code / cold-init.lisp
1 ;;;; cold initialization stuff, plus some other miscellaneous stuff
2 ;;;; that we don't have any better place for
3
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.
12
13 (in-package "SB!IMPL")
14 \f
15 ;;;; burning our ships behind us
16
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   (do ((any-changes? nil nil))
29       (nil)
30     (dolist (package (list-all-packages))
31       (do-symbols (symbol package)
32         (let ((name (symbol-name symbol)))
33           (when (or (string= name "!" :end1 1 :end2 1)
34                     (and (>= (length name) 2)
35                          (string= name "*!" :end1 2 :end2 2)))
36             (/show0 "uninterning cold-init-only symbol..")
37             (/primitive-print name)
38             ;; FIXME: Is this (FIRST (LAST *INFO-ENVIRONMENT*)) really
39             ;; meant to be an idiom to use?  Is there a more obvious
40             ;; name for this? [e.g. (GLOBAL-ENVIRONMENT)?]
41             (do-info ((first (last *info-environment*))
42                             :name entry :class class :type type)
43               (when (eq entry symbol)
44                 (clear-info class type entry)))
45             (unintern symbol package)
46             (setf any-changes? t)))))
47     (unless any-changes?
48       (return))))
49 \f
50 ;;;; putting ourselves out of our misery when things become too much to bear
51
52 (declaim (ftype (function (simple-string) nil) !cold-lose))
53 (defun !cold-lose (msg)
54   (%primitive print msg)
55   (%primitive print "too early in cold init to recover from errors")
56   (%halt))
57
58 ;;; last-ditch error reporting for things which should never happen
59 ;;; and which, if they do happen, are sufficiently likely to torpedo
60 ;;; the normal error-handling system that we want to bypass it
61 (declaim (ftype (function (simple-string) nil) critically-unreachable))
62 (defun critically-unreachable (where)
63   (%primitive print "internal error: Control should never reach here, i.e.")
64   (%primitive print where)
65   (%halt))
66 \f
67 ;;;; !COLD-INIT
68
69 ;;; a list of toplevel things set by GENESIS
70 (defvar *!reversed-cold-toplevels*)
71
72 ;;; a SIMPLE-VECTOR set by GENESIS
73 (defvar *!load-time-values*)
74
75 (eval-when (:compile-toplevel :execute)
76   ;; FIXME: Perhaps we should make SHOW-AND-CALL-AND-FMAKUNBOUND, too,
77   ;; and use it for most of the cold-init functions. (Just be careful
78   ;; not to use it for the COLD-INIT-OR-REINIT functions.)
79   (sb!xc:defmacro show-and-call (name)
80     `(progn
81        (/primitive-print ,(symbol-name name))
82        (,name))))
83
84 ;;; called when a cold system starts up
85 (defun !cold-init ()
86   #!+sb-doc "Give the world a shove and hope it spins."
87
88   (/show0 "entering !COLD-INIT")
89
90   ;; FIXME: It'd probably be cleaner to have most of the stuff here
91   ;; handled by calls like !GC-COLD-INIT, !ERROR-COLD-INIT, and
92   ;; !UNIX-COLD-INIT. And *TYPE-SYSTEM-INITIALIZED* could be changed to
93   ;; *TYPE-SYSTEM-INITIALIZED-WHEN-BOUND* so that it doesn't need to
94   ;; be explicitly set in order to be meaningful.
95   (setf *after-gc-hooks* nil
96         *in-without-gcing* nil
97         *gc-inhibit* t
98         *gc-pending* nil
99         #!+sb-thread *stop-for-gc-pending* #!+sb-thread nil
100         *allow-with-interrupts* t
101         sb!unix::*unblock-deferrables-on-enabling-interrupts-p* nil
102         *interrupts-enabled* t
103         *interrupt-pending* nil
104         #!+sb-thruption #!+sb-thruption *thruption-pending* nil
105         *break-on-signals* nil
106         *maximum-error-depth* 10
107         *current-error-depth* 0
108         *cold-init-complete-p* nil
109         *type-system-initialized* nil
110         sb!vm:*alloc-signal* nil
111         sb!kernel::*gc-epoch* (cons nil nil))
112
113   ;; I'm not sure where eval is first called, so I put this first.
114   (show-and-call !eval-cold-init)
115   (show-and-call !deadline-cold-init)
116   (show-and-call thread-init-or-reinit)
117   (show-and-call !typecheckfuns-cold-init)
118
119   ;; Anyone might call RANDOM to initialize a hash value or something;
120   ;; and there's nothing which needs to be initialized in order for
121   ;; this to be initialized, so we initialize it right away.
122   (show-and-call !random-cold-init)
123
124   ;; Must be done before any non-opencoded array references are made.
125   (show-and-call !hairy-data-vector-reffer-init)
126
127   (show-and-call !character-database-cold-init)
128   (show-and-call !character-name-database-cold-init)
129
130   (show-and-call !early-package-cold-init)
131   (show-and-call !package-cold-init)
132
133   ;; All sorts of things need INFO and/or (SETF INFO).
134   (/show0 "about to SHOW-AND-CALL !GLOBALDB-COLD-INIT")
135   (show-and-call !globaldb-cold-init)
136
137   ;; This needs to be done early, but needs to be after INFO is
138   ;; initialized.
139   (show-and-call !function-names-cold-init)
140   (show-and-call !fdefn-cold-init)
141
142   ;; Various toplevel forms call MAKE-ARRAY, which calls SUBTYPEP, so
143   ;; the basic type machinery needs to be initialized before toplevel
144   ;; forms run.
145   (show-and-call !type-class-cold-init)
146   (show-and-call !typedefs-cold-init)
147   (show-and-call !world-lock-cold-init)
148   (show-and-call !classes-cold-init)
149   (show-and-call !early-type-cold-init)
150   (show-and-call !late-type-cold-init)
151   (show-and-call !alien-type-cold-init)
152   (show-and-call !target-type-cold-init)
153   (show-and-call !vm-type-cold-init)
154   ;; FIXME: It would be tidy to make sure that that these cold init
155   ;; functions are called in the same relative order as the toplevel
156   ;; forms of the corresponding source files.
157
158   ;;(show-and-call !package-cold-init)
159   (show-and-call !policy-cold-init-or-resanify)
160   (/show0 "back from !POLICY-COLD-INIT-OR-RESANIFY")
161
162   (show-and-call !constantp-cold-init)
163   (show-and-call !early-proclaim-cold-init)
164
165   ;; KLUDGE: Why are fixups mixed up with toplevel forms? Couldn't
166   ;; fixups be done separately? Wouldn't that be clearer and better?
167   ;; -- WHN 19991204
168   (/show0 "doing cold toplevel forms and fixups")
169   (/show0 "(LISTP *!REVERSED-COLD-TOPLEVELS*)=..")
170   (/hexstr (if (listp *!reversed-cold-toplevels*) "true" "NIL"))
171   (/show0 "about to calculate (LENGTH *!REVERSED-COLD-TOPLEVELS*)")
172   (/show0 "(LENGTH *!REVERSED-COLD-TOPLEVELS*)=..")
173   #!+sb-show (let ((r-c-tl-length (length *!reversed-cold-toplevels*)))
174                (/show0 "(length calculated..)")
175                (let ((hexstr (hexstr r-c-tl-length)))
176                  (/show0 "(hexstr calculated..)")
177                  (/primitive-print hexstr)))
178   (let (#!+sb-show (index-in-cold-toplevels 0))
179     #!+sb-show (declare (type fixnum index-in-cold-toplevels))
180
181     (dolist (toplevel-thing (prog1
182                                 (nreverse *!reversed-cold-toplevels*)
183                               ;; (Now that we've NREVERSEd it, it's
184                               ;; somewhat scrambled, so keep anyone
185                               ;; else from trying to get at it.)
186                               (makunbound '*!reversed-cold-toplevels*)))
187       #!+sb-show
188       (when (zerop (mod index-in-cold-toplevels 1024))
189         (/show0 "INDEX-IN-COLD-TOPLEVELS=..")
190         (/hexstr index-in-cold-toplevels))
191       #!+sb-show
192       (setf index-in-cold-toplevels
193             (the fixnum (1+ index-in-cold-toplevels)))
194       (typecase toplevel-thing
195         (function
196          (funcall toplevel-thing))
197         (cons
198          (case (first toplevel-thing)
199            (:load-time-value
200             (setf (svref *!load-time-values* (third toplevel-thing))
201                   (funcall (second toplevel-thing))))
202            (:load-time-value-fixup
203             (setf (sap-ref-word (int-sap (get-lisp-obj-address (second toplevel-thing)))
204                                 (third toplevel-thing))
205                   (get-lisp-obj-address
206                    (svref *!load-time-values* (fourth toplevel-thing)))))
207            (t
208             (!cold-lose "bogus fixup code in *!REVERSED-COLD-TOPLEVELS*"))))
209         (t (!cold-lose "bogus function in *!REVERSED-COLD-TOPLEVELS*")))))
210   (/show0 "done with loop over cold toplevel forms and fixups")
211
212   ;; Set sane values again, so that the user sees sane values instead
213   ;; of whatever is left over from the last DECLAIM/PROCLAIM.
214   (show-and-call !policy-cold-init-or-resanify)
215
216   ;; Only do this after toplevel forms have run, 'cause that's where
217   ;; DEFTYPEs are.
218   (setf *type-system-initialized* t)
219
220   ;; now that the type system is definitely initialized, fixup UNKNOWN
221   ;; types that have crept in.
222   (show-and-call !fixup-type-cold-init)
223   ;; run the PROCLAIMs.
224   (show-and-call !late-proclaim-cold-init)
225
226   (show-and-call os-cold-init-or-reinit)
227   (show-and-call !pathname-cold-init)
228   (show-and-call !debug-info-cold-init)
229
230   (show-and-call stream-cold-init-or-reset)
231   (show-and-call !loader-cold-init)
232   (show-and-call !foreign-cold-init)
233   #!-(and win32 (not sb-thread))
234   (show-and-call signal-cold-init-or-reinit)
235   (/show0 "enabling internal errors")
236   (setf (sb!alien:extern-alien "internal_errors_enabled" boolean) t)
237
238   (show-and-call float-cold-init-or-reinit)
239
240   (show-and-call !class-finalize)
241
242   ;; The reader and printer are initialized very late, so that they
243   ;; can do hairy things like invoking the compiler as part of their
244   ;; initialization.
245   (let ((*readtable* (make-readtable)))
246     (show-and-call !reader-cold-init)
247     (show-and-call !sharpm-cold-init)
248     (show-and-call !backq-cold-init)
249     ;; The *STANDARD-READTABLE* is assigned at last because the above
250     ;; functions would operate on the standard readtable otherwise---
251     ;; which would result in an error.
252     (setf *standard-readtable* *readtable*))
253   (setf *readtable* (copy-readtable *standard-readtable*))
254   (setf sb!debug:*debug-readtable* (copy-readtable *standard-readtable*))
255   (sb!pretty:!pprint-cold-init)
256
257   ;; the ANSI-specified initial value of *PACKAGE*
258   (setf *package* (find-package "COMMON-LISP-USER"))
259
260   (/show0 "done initializing, setting *COLD-INIT-COMPLETE-P*")
261   (setf *cold-init-complete-p* t)
262
263   ; hppa heap is segmented, lisp and c uses a stub to call eachother
264   #!+hpux (sb!sys:%primitive sb!vm::setup-return-from-lisp-stub)
265   ;; The system is finally ready for GC.
266   (/show0 "enabling GC")
267   (setq *gc-inhibit* nil)
268   (/show0 "doing first GC")
269   (gc :full t)
270   (/show0 "back from first GC")
271
272   ;; The show is on.
273   (terpri)
274   (/show0 "going into toplevel loop")
275   (handling-end-of-the-world
276     (toplevel-init)
277     (critically-unreachable "after TOPLEVEL-INIT")))
278
279 (define-deprecated-function :early "1.0.56.55" quit (exit sb!thread:abort-thread)
280     (&key recklessly-p (unix-status 0))
281   (if (or recklessly-p (sb!thread:main-thread-p))
282       (exit :code unix-status :abort recklessly-p)
283       (sb!thread:abort-thread))
284   (critically-unreachable "after trying to die in QUIT"))
285
286 (declaim (ftype (sfunction (&key (:code (or null exit-code))
287                                  (:timeout (or null real))
288                                  (:abort t))
289                            nil)
290                 exit))
291 (defun exit (&key code abort (timeout *exit-timeout*))
292   #!+sb-doc
293   "Terminates the process, causing SBCL to exit with CODE. CODE
294 defaults to 0 when ABORT is false, and 1 when it is true.
295
296 When ABORT is false (the default), current thread is first unwound,
297 *EXIT-HOOKS* are run, other threads are terminated, and standard
298 output streams are flushed before SBCL calls exit(3) -- at which point
299 atexit(3) functions will run. If multiple threads call EXIT with ABORT
300 being false, the first one to call it will complete the protocol.
301
302 When ABORT is true, SBCL exits immediately by calling _exit(2) without
303 unwinding stack, or calling exit hooks. Note that _exit(2) does not
304 call atexit(3) functions unlike exit(3).
305
306 Recursive calls to EXIT cause EXIT to behave as it ABORT was true.
307
308 TIMEOUT controls waiting for other threads to terminate when ABORT is
309 NIL. Once current thread has been unwound and *EXIT-HOOKS* have been
310 run, spawning new threads is prevented and all other threads are
311 terminated by calling TERMINATE-THREAD on them. The system then waits
312 for them to finish using JOIN-THREAD, waiting at most a total TIMEOUT
313 seconds for all threads to join. Those threads that do not finish
314 in time are simply ignored while the exit protocol continues. TIMEOUT
315 defaults to *EXIT-TIMEOUT*, which in turn defaults to 60. TIMEOUT NIL
316 means to wait indefinitely.
317
318 Note that TIMEOUT applies only to JOIN-THREAD, not *EXIT-HOOKS*. Since
319 TERMINATE-THREAD is asynchronous, getting multithreaded application
320 termination with complex cleanups right using it can be tricky. To
321 perform an orderly synchronous shutdown use an exit hook instead of
322 relying on implicit thread termination.
323
324 Consequences are unspecified if serious conditions occur during EXIT
325 excepting errors from *EXIT-HOOKS*, which cause warnings and stop
326 execution of the hook that signaled, but otherwise allow the exit
327 process to continue normally."
328   (if (or abort *exit-in-process*)
329       (os-exit (or code 1) :abort t)
330       (let ((code (or code 0)))
331         (with-deadline (:seconds nil :override t)
332           (sb!thread:grab-mutex *exit-lock*))
333         (setf *exit-in-process* code
334               *exit-timeout* timeout)
335         (throw '%end-of-the-world t)))
336   (critically-unreachable "After trying to die in EXIT."))
337 \f
338 ;;;; initialization functions
339
340 (defun thread-init-or-reinit ()
341   (sb!thread::init-initial-thread)
342   (sb!thread::init-job-control)
343   (sb!thread::get-foreground))
344
345 (defun reinit ()
346   #!+win32
347   (setf sb!win32::*ansi-codepage* nil)
348   (setf *default-external-format* nil)
349   (setf sb!alien::*default-c-string-external-format* nil)
350   ;; WITHOUT-GCING implies WITHOUT-INTERRUPTS.
351   (without-gcing
352     ;; Initialize streams first, so that any errors can be printed later
353     (stream-reinit t)
354     (os-cold-init-or-reinit)
355     (thread-init-or-reinit)
356     #!-(and win32 (not sb-thread))
357     (signal-cold-init-or-reinit)
358     (setf (sb!alien:extern-alien "internal_errors_enabled" boolean) t)
359     (float-cold-init-or-reinit))
360   (gc-reinit)
361   (foreign-reinit)
362   (time-reinit)
363   ;; If the debugger was disabled in the saved core, we need to
364   ;; re-disable ldb again.
365   (when (eq *invoke-debugger-hook* 'sb!debug::debugger-disabled-hook)
366     (sb!debug::disable-debugger))
367   (call-hooks "initialization" *init-hooks*))
368 \f
369 ;;;; some support for any hapless wretches who end up debugging cold
370 ;;;; init code
371
372 ;;; Decode THING into hexadecimal notation using only machinery
373 ;;; available early in cold init.
374 #!+sb-show
375 (defun hexstr (thing)
376   (/noshow0 "entering HEXSTR")
377   (let* ((addr (get-lisp-obj-address thing))
378          (nchars (* sb!vm:n-word-bytes 2))
379          (str (make-string (+ nchars 2) :element-type 'base-char)))
380     (/noshow0 "ADDR and STR calculated")
381     (setf (char str 0) #\0
382           (char str 1) #\x)
383     (/noshow0 "CHARs 0 and 1 set")
384     (dotimes (i nchars)
385       (/noshow0 "at head of DOTIMES loop")
386       (let* ((nibble (ldb (byte 4 0) addr))
387              (chr (char "0123456789abcdef" nibble)))
388         (declare (type (unsigned-byte 4) nibble)
389                  (base-char chr))
390         (/noshow0 "NIBBLE and CHR calculated")
391         (setf (char str (- (1+ nchars) i)) chr
392               addr (ash addr -4))))
393     str))
394
395 #!+sb-show
396 (defun cold-print (x)
397   (labels ((%cold-print (obj depthoid)
398              (if (> depthoid 4)
399                  (sb!sys:%primitive print "...")
400                  (typecase obj
401                    (simple-string
402                     (sb!sys:%primitive print obj))
403                    (symbol
404                     (sb!sys:%primitive print (symbol-name obj)))
405                    (cons
406                     (sb!sys:%primitive print "cons:")
407                     (let ((d (1+ depthoid)))
408                       (%cold-print (car obj) d)
409                       (%cold-print (cdr obj) d)))
410                    (t
411                     (sb!sys:%primitive print (hexstr obj)))))))
412     (%cold-print x 0))
413   (values))