1 ;;;; parts of the loader which make sense in the cross-compilation
2 ;;;; host (and which are useful in the host, because they're used by
5 ;;;; based on the CMU CL load.lisp code, written by Skef Wholey and
8 ;;;; This software is part of the SBCL system. See the README file for
11 ;;;; This software is derived from the CMU CL system, which was
12 ;;;; written at Carnegie Mellon University and released into the
13 ;;;; public domain. The software is in the public domain and is
14 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
15 ;;;; files for more information.
17 (in-package "SB!FASL")
19 ;;;; There looks to be an exciting amount of state being modified
20 ;;;; here: certainly enough that I (dan, 2003.1.22) don't want to mess
21 ;;;; around deciding how to thread-safetify it. So we use a Big Lock.
22 ;;;; Because this code is mutually recursive with the compiler, we use
23 ;;;; the *big-compiler-lock*
25 ;;;; miscellaneous load utilities
27 ;;; Output the current number of semicolons after a fresh-line.
28 ;;; FIXME: non-mnemonic name
29 (defun load-fresh-line ()
31 (let ((semicolons ";;;;;;;;;;;;;;;;"))
32 (do ((count *load-depth* (- count (length semicolons))))
33 ((< count (length semicolons))
34 (write-string semicolons *standard-output* :end count))
35 (declare (fixnum count))
36 (write-string semicolons))
37 (write-char #\space)))
39 ;;; If VERBOSE, output (to *STANDARD-OUTPUT*) a message about how
40 ;;; we're loading from STREAM-WE-ARE-LOADING-FROM.
41 (defun maybe-announce-load (stream-we-are-loading-from verbose)
44 (let ((name #-sb-xc-host (file-name stream-we-are-loading-from)
47 (format t "loading ~S~%" name)
48 (format t "loading stuff from ~S~%" stream-we-are-loading-from)))))
50 ;;;; utilities for reading from fasl files
52 #!-sb-fluid (declaim (inline read-byte))
54 ;;; This expands into code to read an N-byte unsigned integer using
56 (defmacro fast-read-u-integer (n)
57 (declare (optimize (speed 0)))
58 (do ((res '(fast-read-byte)
59 `(logior (fast-read-byte)
64 ;;; like FAST-READ-U-INTEGER, but the size may be determined at run time
65 (defmacro fast-read-var-u-integer (n)
66 (let ((n-pos (gensym))
69 `(do ((,n-pos 8 (+ ,n-pos 8))
70 (,n-cnt (1- ,n) (1- ,n-cnt))
73 (dpb (fast-read-byte) (byte 8 ,n-pos) ,n-res)))
74 ((zerop ,n-cnt) ,n-res)
75 (declare (type index ,n-pos ,n-cnt)))))
77 ;;; Read a signed integer.
78 (defmacro fast-read-s-integer (n)
79 (declare (optimize (speed 0)))
80 (let ((n-last (gensym)))
81 (do ((res `(let ((,n-last (fast-read-byte)))
82 (if (zerop (logand ,n-last #x80))
84 (logior ,n-last #x-100)))
85 `(logior (fast-read-byte)
86 (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
90 ;;; Read an N-byte unsigned integer from the *FASL-INPUT-STREAM*
91 (defmacro read-arg (n)
92 (declare (optimize (speed 0)))
94 `(the (unsigned-byte 8) (read-byte *fasl-input-stream*))
95 `(prepare-for-fast-read-byte *fasl-input-stream*
97 (fast-read-u-integer ,n)
98 (done-with-fast-read-byte)))))
100 ;;; FIXME: This deserves a more descriptive name, and should probably
101 ;;; be implemented as an ordinary function, not a macro.
103 ;;; (for the names: There seem to be only two cases, so it could be
104 ;;; named READ-U-INTEGER-8 and READ-U-INTEGER-32 or something.)
108 ;;; The table is implemented as a simple-vector indexed by the table
109 ;;; offset. We may need to have several, since LOAD can be called
112 ;;; a list of free fop tables for the fasloader
114 ;;; FIXME: Is it really a win to have this permanently bound?
115 ;;; Couldn't we just bind it on entry to LOAD-AS-FASL?
116 (defvar *free-fop-tables* (list (make-array 1000)))
118 ;;; the current fop table
119 (defvar *current-fop-table*)
120 (declaim (simple-vector *current-fop-table*))
122 ;;; the length of the current fop table
123 (defvar *current-fop-table-size*)
124 (declaim (type index *current-fop-table-size*))
126 ;;; the index in the fop-table of the next entry to be used
127 (defvar *current-fop-table-index*)
128 (declaim (type index *current-fop-table-index*))
130 (defun grow-fop-table ()
131 (let* ((new-size (* *current-fop-table-size* 2))
132 (new-table (make-array new-size)))
133 (declare (fixnum new-size) (simple-vector new-table))
134 (replace new-table (the simple-vector *current-fop-table*))
135 (setq *current-fop-table* new-table)
136 (setq *current-fop-table-size* new-size)))
138 (defmacro push-fop-table (thing)
139 (let ((n-index (gensym)))
140 `(let ((,n-index *current-fop-table-index*))
141 (declare (fixnum ,n-index))
142 (when (= ,n-index (the fixnum *current-fop-table-size*))
144 (setq *current-fop-table-index* (1+ ,n-index))
145 (setf (svref *current-fop-table* ,n-index) ,thing))))
149 ;;; (This is in a SIMPLE-VECTOR, but it grows down, since it is
150 ;;; somewhat cheaper to test for overflow that way.)
151 (defvar *fop-stack* (make-array 100))
152 (declaim (simple-vector *fop-stack*))
154 ;;; the index of the most recently pushed item on the fop stack
155 (defvar *fop-stack-pointer* 100)
157 ;;; the current index into the fop stack when we last recursively
159 (defvar *fop-stack-pointer-on-entry*)
160 (declaim (type index *fop-stack-pointer* *fop-stack-pointer-on-entry*))
162 (defun grow-fop-stack ()
163 (let* ((size (length (the simple-vector *fop-stack*)))
164 (new-size (* size 2))
165 (new-stack (make-array new-size)))
166 (declare (fixnum size new-size) (simple-vector new-stack))
167 (replace new-stack (the simple-vector *fop-stack*) :start1 size)
168 (incf *fop-stack-pointer-on-entry* size)
169 (setq *fop-stack-pointer* size)
170 (setq *fop-stack* new-stack)))
172 ;;; Cache information about the fop stack in local variables. Define a
173 ;;; local macro to pop from the stack. Push the result of evaluation
175 (defmacro with-fop-stack (pushp &body forms)
176 (aver (member pushp '(nil t :nope)))
177 (let ((n-stack (gensym))
180 `(let ((,n-stack *fop-stack*)
181 (,n-index *fop-stack-pointer*))
182 (declare (simple-vector ,n-stack) (type index ,n-index))
183 (macrolet ((pop-stack ()
185 (svref ,',n-stack ,',n-index)
187 (call-with-popped-things (fun n)
188 (let ((n-start (gensym)))
189 `(let ((,n-start (+ ,',n-index ,n)))
190 (declare (type index ,n-start))
191 (setq ,',n-index ,n-start)
192 (,fun ,@(make-list n :initial-element
194 (decf ,n-start))))))))
196 `(let ((,n-res (progn ,@forms)))
197 (when (zerop ,n-index)
199 (setq ,n-index *fop-stack-pointer*
200 ,n-stack *fop-stack*))
202 (setq *fop-stack-pointer* ,n-index)
203 (setf (svref ,n-stack ,n-index) ,n-res))
206 (setq *fop-stack-pointer* ,n-index)))))))
210 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
211 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
212 ;;;; it's needed not only in the target Lisp, but also in the
213 ;;;; cross-compilation host.
215 ;;; a helper function for LOAD-FASL-GROUP
217 ;;; Return true if we successfully read a FASL header from the stream,
218 ;;; or NIL if EOF was hit before anything was read. Signal an error if
219 ;;; we encounter garbage.
220 (defun check-fasl-header (stream)
222 (let ((byte (read-byte stream nil)))
225 ;; Read the string part of the fasl header, or die.
226 (let* ((fhsss *fasl-header-string-start-string*)
227 (fhsss-length (length fhsss)))
228 (unless (= byte (char-code (schar fhsss 0)))
229 (error "illegal first byte in fasl file header"))
230 (do ((byte (read-byte stream) (read-byte stream))
231 (count 1 (1+ count)))
232 ((= byte +fasl-header-string-stop-char-code+)
234 (declare (fixnum byte count))
235 (when (and (< count fhsss-length)
236 (not (eql byte (char-code (schar fhsss count)))))
238 "illegal subsequent (not first) byte in fasl file header"))))
240 ;; Read and validate implementation and version, or die.
241 (let* ((implementation-length (read-arg 4))
242 (implementation-string (make-string implementation-length))
243 (ignore (read-string-as-bytes stream implementation-string))
244 (implementation (keywordicate implementation-string))
245 ;; FIXME: The logic above to read a keyword from the fasl file
246 ;; could probably be shared with the read-a-keyword fop.
247 (version (read-arg 4)))
248 (declare (ignore ignore))
249 (flet ((check-version (variant possible-implementation needed-version)
250 (when (string= possible-implementation implementation)
251 (unless (= version needed-version)
252 (error "~@<~S is in ~A fasl file format version ~W, ~
253 but this version of SBCL uses ~
254 format version ~W.~:@>"
260 (or (check-version "native code"
261 +backend-fasl-file-implementation+
263 (error "~S was compiled for implementation ~A, but this is a ~A."
266 +backend-fasl-file-implementation+)))))))
268 ;; Setting this variable gives you a trace of fops as they are loaded and
271 (defvar *show-fops-p* nil)
273 ;;; a helper function for LOAD-AS-FASL
275 ;;; Return true if we successfully load a group from the stream, or
276 ;;; NIL if EOF was encountered while trying to read from the stream.
277 ;;; Dispatch to the right function for each fop. Special-case
278 ;;; FOP-BYTE-PUSH since it is real common.
279 (defun load-fasl-group (stream)
280 (when (check-fasl-header stream)
281 (catch 'fasl-group-end
282 (let ((*current-fop-table-index* 0))
284 (let ((byte (read-byte stream)))
286 ;; Do some debugging output.
289 (let ((ptr *fop-stack-pointer*)
291 (fresh-line *trace-output*)
292 ;; The FOP operations are stack based, so it's sorta
293 ;; logical to display the operand before the operator.
294 ;; ("reverse Polish notation")
295 (unless (= ptr (length stack))
296 (write-char #\space *trace-output*)
297 (prin1 (svref stack ptr) *trace-output*)
298 (terpri *trace-output*))
299 ;; Display the operator.
300 (format *trace-output*
301 "~&~S (#X~X at ~D) (~S)~%"
302 (svref *fop-names* byte)
304 (1- (file-position stream))
305 (svref *fop-funs* byte))))
307 ;; Actually execute the fop.
309 ;; FIXME: This is the special case for FOP-BYTE-PUSH.
310 ;; Benchmark to see whether it's really worth special
311 ;; casing it. If it is, at least express the test in
312 ;; terms of a symbolic name for the FOP-BYTE-PUSH code,
313 ;; not a bare '3' (!). Failing that, remove the special
314 ;; case (and the comment at the head of this function
315 ;; which mentions it).
316 (let ((index *fop-stack-pointer*))
317 (declare (type index index))
320 (setq index *fop-stack-pointer*))
322 (setq *fop-stack-pointer* index)
323 (setf (svref *fop-stack* index)
324 (svref *current-fop-table* (read-byte stream))))
325 (funcall (the function (svref *fop-funs* byte))))))))))
327 (defun load-as-fasl (stream verbose print)
328 ;; KLUDGE: ANSI says it's good to do something with the :PRINT
329 ;; argument to LOAD when we're fasloading a file, but currently we
330 ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
331 ;; just disabled that instead of rewriting it.) -- WHN 20000131
332 (declare (ignore print))
333 (when (zerop (file-length stream))
334 (error "attempt to load an empty FASL file:~% ~S" (namestring stream)))
335 (maybe-announce-load stream verbose)
336 (sb!thread:with-recursive-lock (sb!c::*big-compiler-lock*)
337 (let* ((*fasl-input-stream* stream)
338 (*current-fop-table* (or (pop *free-fop-tables*) (make-array 1000)))
339 (*current-fop-table-size* (length *current-fop-table*))
340 (*fop-stack-pointer-on-entry* *fop-stack-pointer*))
342 (loop while (load-fasl-group stream))
343 (setq *fop-stack-pointer* *fop-stack-pointer-on-entry*)
344 (push *current-fop-table* *free-fop-tables*)
345 ;; NIL out the stack and table, so that we don't hold onto garbage.
347 ;; FIXME: Couldn't we just get rid of the free fop table pool so
348 ;; that some of this NILing out would go away?
349 (fill *fop-stack* nil :end *fop-stack-pointer-on-entry*)
350 (fill *current-fop-table* nil))))
353 ;;; This is used in in target-load and also genesis, using
354 ;;; *COLD-FOREIGN-SYMBOL-TABLE*. All the speculative prefix-adding
355 ;;; code for foreign symbol lookup should be here.
356 (defun find-foreign-symbol-in-table (name table)
358 #!+(or osf1 sunos linux freebsd) #("" "ldso_stub__")
360 (declare (notinline some)) ; to suppress bug 117 bogowarning
361 (some (lambda (prefix)
362 (gethash (concatenate 'string prefix name)
367 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
370 (defvar *fop-counts* (make-array 256 :initial-element 0))
371 (defvar *fop-times* (make-array 256 :initial-element 0))
372 (defvar *print-fops* nil)
374 (defun clear-counts ()
375 (fill (the simple-vector *fop-counts*) 0)
376 (fill (the simple-vector *fop-times*) 0)
379 (defun analyze-counts ()
384 (macrolet ((breakdown (lvar tvar vec)
388 (let ((n (svref ,vec i)))
389 (push (cons (svref *fop-names* i) n) ,lvar)
391 (setq ,lvar (subseq (sort ,lvar (lambda (x y)
392 (> (cdr x) (cdr y))))
395 (breakdown counts total-count *fop-counts*)
396 (breakdown times total-time *fop-times*)
397 (format t "Total fop count is ~D~%" total-count)
399 (format t "~30S: ~4D~%" (car c) (cdr c)))
400 (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
402 (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))