3e989908eca1fc014aa397f7a1aefd40dfad4a2b
[sbcl.git] / src / code / load.lisp
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
3 ;;;; GENESIS)
4 ;;;;
5 ;;;; based on the CMU CL load.lisp code, written by Skef Wholey and
6 ;;;; Rob Maclachlan
7
8 ;;;; This software is part of the SBCL system. See the README file for
9 ;;;; more information.
10 ;;;;
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.
16
17 (in-package "SB!IMPL")
18 \f
19 ;;;; variables
20
21 ;;; FIXME: It's awkward having LOAD stuff in SB!IMPL and dump stuff in
22 ;;; SB!C. Among other things, it makes it hard to figure out where
23 ;;; *FASL-HEADER-STRING-START-STRING* and
24 ;;; *FASL-HEADER-STRING-STOP-CHAR-CODE* should go. Perhaps we should
25 ;;; make a package called SB-DUMP or SB-LD which includes all
26 ;;; knowledge of both loading and dumping.
27
28 ;;; This value is used to identify fasl files. Even though this is not
29 ;;; declared as a constant (because ANSI Common Lisp has no facility
30 ;;; for declaring values which are constant under EQUAL but not EQL),
31 ;;; obviously you shouldn't mess with it lightly. If you do set a new
32 ;;; value for some reason, keep these things in mind:
33 ;;; * To avoid confusion with the similar but incompatible CMU CL
34 ;;;   fasl file format, the value should not be "FASL FILE", which
35 ;;;   is what CMU CL used for the same purpose.
36 ;;; * Since its presence at the head of a file is used by LOAD to
37 ;;;   decide whether a file is to be fasloaded or just loaded
38 ;;;   ordinarily (as source), the value should be something which
39 ;;;   can't legally appear at the head of a Lisp source file.
40 ;;; * The value should not contain any line-terminating characters,
41 ;;;   because they're hard to express portably and because the LOAD
42 ;;;   code might reasonably use READ-LINE to get the value to compare
43 ;;;   against.
44 (defparameter sb!c:*fasl-header-string-start-string* "# FASL"
45   #!+sb-doc
46   "a string which appears at the start of a fasl file header")
47
48 (defparameter sb!c:*fasl-header-string-stop-char-code* 255
49   #!+sb-doc
50   "the code for a character which terminates a fasl file header")
51
52 (defvar *load-depth* 0
53   #!+sb-doc
54   "the current number of recursive loads")
55 (declaim (type index *load-depth*))
56
57 ;;; the FASL file we're reading from
58 (defvar *fasl-file*)
59 (declaim (type lisp-stream *fasl-file*))
60
61 (defvar *load-print* nil
62   #!+sb-doc
63   "the default for the :PRINT argument to LOAD")
64 (defvar *load-verbose* nil
65   ;; Note that CMU CL's default for this was T, and ANSI says it's
66   ;; implementation-dependent. We choose NIL on the theory that it's
67   ;; a nicer default behavior for Unix programs.
68   #!+sb-doc
69   "the default for the :VERBOSE argument to LOAD")
70 \f
71 ;;;; miscellaneous load utilities
72
73 ;;; Output the current number of semicolons after a fresh-line.
74 ;;; FIXME: non-mnemonic name
75 (defun load-fresh-line ()
76   (fresh-line)
77   (let ((semicolons ";;;;;;;;;;;;;;;;"))
78     (do ((count *load-depth* (- count (length semicolons))))
79         ((< count (length semicolons))
80          (write-string semicolons *standard-output* :end count))
81       (declare (fixnum count))
82       (write-string semicolons))
83     (write-char #\space)))
84
85 ;;; If VERBOSE, output (to *STANDARD-OUTPUT*) a message about how we're
86 ;;; loading from STREAM-WE-ARE-LOADING-FROM.
87 ;;; FIXME: non-mnemonic name
88 (defun do-load-verbose (stream-we-are-loading-from verbose)
89   (when verbose
90     (load-fresh-line)
91     (let ((name #-sb-xc-host (file-name stream-we-are-loading-from)
92                 #+sb-xc-host nil))
93       (if name
94           (format t "loading ~S~%" name)
95           (format t "loading stuff from ~S~%" stream-we-are-loading-from)))))
96 \f
97 ;;;; utilities for reading from fasl files
98
99 #!-sb-fluid (declaim (inline read-byte))
100
101 ;;;    Expands into code to read an N-byte unsigned integer using
102 ;;; fast-read-byte.
103 (defmacro fast-read-u-integer (n)
104   (declare (optimize (speed 0)))
105   (do ((res '(fast-read-byte)
106             `(logior (fast-read-byte)
107                      (ash ,res 8)))
108        (cnt 1 (1+ cnt)))
109       ((>= cnt n) res)))
110
111 ;;; Like Fast-Read-U-Integer, but the size may be determined at run time.
112 (defmacro fast-read-variable-u-integer (n)
113   (let ((n-pos (gensym))
114         (n-res (gensym))
115         (n-cnt (gensym)))
116     `(do ((,n-pos 8 (+ ,n-pos 8))
117           (,n-cnt (1- ,n) (1- ,n-cnt))
118           (,n-res
119            (fast-read-byte)
120            (dpb (fast-read-byte) (byte 8 ,n-pos) ,n-res)))
121          ((zerop ,n-cnt) ,n-res)
122        (declare (type index ,n-pos ,n-cnt)))))
123
124 ;;; Read a signed integer.
125 (defmacro fast-read-s-integer (n)
126   (declare (optimize (speed 0)))
127   (let ((n-last (gensym)))
128     (do ((res `(let ((,n-last (fast-read-byte)))
129                  (if (zerop (logand ,n-last #x80))
130                      ,n-last
131                      (logior ,n-last #x-100)))
132               `(logior (fast-read-byte)
133                        (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
134          (cnt 1 (1+ cnt)))
135         ((>= cnt n) res))))
136
137 ;;; Read an N-byte unsigned integer from the *FASL-FILE*
138 (defmacro read-arg (n)
139   (declare (optimize (speed 0)))
140   (if (= n 1)
141       `(the (unsigned-byte 8) (read-byte *fasl-file*))
142       `(prepare-for-fast-read-byte *fasl-file*
143          (prog1
144           (fast-read-u-integer ,n)
145           (done-with-fast-read-byte)))))
146
147 ;;; FIXME: This deserves a more descriptive name, and should probably
148 ;;; be implemented as an ordinary function, not a macro.
149 ;;;
150 ;;; (for the names: There seem to be only two cases, so it could be
151 ;;; named READ-U-INTEGER-8 and READ-U-INTEGER-32 or something.)
152 \f
153 ;;;; the fop table
154
155 ;;; The table is implemented as a simple-vector indexed by the table
156 ;;; offset. We may need to have several, since LOAD can be called
157 ;;; recursively.
158
159 ;;; a list of free fop tables for the fasloader
160 ;;;
161 ;;; FIXME: Is it really a win to have this permanently bound?
162 ;;; Couldn't we just bind it on entry to LOAD-AS-FASL?
163 (defvar *free-fop-tables* (list (make-array 1000)))
164
165 ;;; the current fop table
166 (defvar *current-fop-table*)
167 (declaim (simple-vector *current-fop-table*))
168
169 ;;; the length of the current fop table
170 (defvar *current-fop-table-size*)
171 (declaim (type index *current-fop-table-size*))
172
173 ;;; the index in the fop-table of the next entry to be used
174 (defvar *current-fop-table-index*)
175 (declaim (type index *current-fop-table-index*))
176
177 (defun grow-fop-table ()
178   (let* ((new-size (* *current-fop-table-size* 2))
179          (new-table (make-array new-size)))
180     (declare (fixnum new-size) (simple-vector new-table))
181     (replace new-table (the simple-vector *current-fop-table*))
182     (setq *current-fop-table* new-table)
183     (setq *current-fop-table-size* new-size)))
184
185 (defmacro push-fop-table (thing)
186   (let ((n-index (gensym)))
187     `(let ((,n-index *current-fop-table-index*))
188        (declare (fixnum ,n-index))
189        (when (= ,n-index (the fixnum *current-fop-table-size*))
190          (grow-fop-table))
191        (setq *current-fop-table-index* (1+ ,n-index))
192        (setf (svref *current-fop-table* ,n-index) ,thing))))
193 \f
194 ;;;; the fop stack
195
196 ;;; (This is in a SIMPLE-VECTOR, but it grows down, since it is
197 ;;; somewhat cheaper to test for overflow that way.)
198 (defvar *fop-stack* (make-array 100))
199 (declaim (simple-vector *fop-stack*))
200
201 ;;; the index of the most recently pushed item on the fop stack
202 (defvar *fop-stack-pointer* 100)
203
204 ;;; the current index into the fop stack when we last recursively
205 ;;; entered LOAD
206 (defvar *fop-stack-pointer-on-entry*)
207 (declaim (type index *fop-stack-pointer* *fop-stack-pointer-on-entry*))
208
209 (defun grow-fop-stack ()
210   (let* ((size (length (the simple-vector *fop-stack*)))
211          (new-size (* size 2))
212          (new-stack (make-array new-size)))
213     (declare (fixnum size new-size) (simple-vector new-stack))
214     (replace new-stack (the simple-vector *fop-stack*) :start1 size)
215     (incf *fop-stack-pointer-on-entry* size)
216     (setq *fop-stack-pointer* size)
217     (setq *fop-stack* new-stack)))
218
219 ;;; Cache information about the fop stack in local variables. Define a
220 ;;; local macro to pop from the stack. Push the result of evaluation
221 ;;; if specified.
222 (defmacro with-fop-stack (pushp &body forms)
223   (aver (member pushp '(nil t :nope)))
224   (let ((n-stack (gensym))
225         (n-index (gensym))
226         (n-res (gensym)))
227     `(let ((,n-stack *fop-stack*)
228            (,n-index *fop-stack-pointer*))
229        (declare (simple-vector ,n-stack) (type index ,n-index))
230        (macrolet ((pop-stack ()
231                     `(prog1
232                       (svref ,',n-stack ,',n-index)
233                       (incf ,',n-index)))
234                   (call-with-popped-things (fun n)
235                     (let ((n-start (gensym)))
236                       `(let ((,n-start (+ ,',n-index ,n)))
237                          (declare (type index ,n-start))
238                          (setq ,',n-index ,n-start)
239                          (,fun ,@(make-list n :initial-element
240                                             `(svref ,',n-stack
241                                                     (decf ,n-start))))))))
242          ,(if pushp
243               `(let ((,n-res (progn ,@forms)))
244                  (when (zerop ,n-index)
245                    (grow-fop-stack)
246                    (setq ,n-index *fop-stack-pointer*
247                          ,n-stack *fop-stack*))
248                  (decf ,n-index)
249                  (setq *fop-stack-pointer* ,n-index)
250                  (setf (svref ,n-stack ,n-index) ,n-res))
251               `(prog1
252                 (progn ,@forms)
253                 (setq *fop-stack-pointer* ,n-index)))))))
254 \f
255 ;;;; LOAD-AS-FASL
256 ;;;;
257 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
258 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
259 ;;;; it's needed not only in the target Lisp, but also in the
260 ;;;; cross-compilation host.
261
262 ;;; a helper function for LOAD-FASL-GROUP
263 ;;;
264 ;;; Return true if we successfully read a FASL header from the stream,
265 ;;; or NIL if EOF was hit before anything was read. Signal an error if
266 ;;; we encounter garbage.
267 (defun check-fasl-header (stream)
268
269   (let ((byte (read-byte stream nil)))
270     (when byte
271
272       ;; Read the string part of the fasl header, or die.
273       (let* ((fhsss sb!c:*fasl-header-string-start-string*)
274              (fhsss-length (length fhsss)))
275         (unless (= byte (char-code (schar fhsss 0)))
276           (error "illegal first byte in fasl file header"))
277         (do ((byte (read-byte stream) (read-byte stream))
278              (count 1 (1+ count)))
279             ((= byte sb!c:*fasl-header-string-stop-char-code*)
280              t)
281           (declare (fixnum byte count))
282           (when (and (< count fhsss-length)
283                      (not (eql byte (char-code (schar fhsss count)))))
284             (error
285              "illegal subsequent (not first) byte in fasl file header"))))
286
287       ;; Read and validate implementation and version, or die.
288       (let* ((implementation-length (read-arg 4))
289              (implementation-string (make-string implementation-length))
290              (ignore (read-string-as-bytes stream implementation-string))
291              (implementation (keywordicate implementation-string))
292              ;; FIXME: The logic above to read a keyword from the fasl file
293              ;; could probably be shared with the read-a-keyword fop.
294              (version (read-arg 4)))
295         (declare (ignore ignore))
296         (flet ((check-version (variant possible-implementation needed-version)
297                  (when (string= possible-implementation implementation)
298                    (unless (= version needed-version)
299                      (error "~@<~S is in ~A fasl file format version ~D, ~
300                              but this version of SBCL uses ~
301                              format version ~D.~:@>"
302                             stream
303                             variant
304                             version
305                             needed-version))
306                    t)))
307           (or (check-version "native code"
308                              #.sb!c:*backend-fasl-file-implementation*
309                              #.sb!c:*backend-fasl-file-version*)
310               (check-version "byte code"
311                              #.(sb!c:backend-byte-fasl-file-implementation)
312                              sb!c:byte-fasl-file-version)
313               (error "~S was compiled for implementation ~A, but this is a ~A."
314                      stream
315                      implementation
316                      sb!c:*backend-fasl-file-implementation*)))))))
317
318 ;; Setting this variable gives you a trace of fops as they are loaded and
319 ;; executed.
320 #!+sb-show
321 (defvar *show-fops-p* nil)
322
323 ;;; a helper function for LOAD-AS-FASL
324 ;;;
325 ;;; Return true if we successfully load a group from the stream, or
326 ;;; NIL if EOF was encountered while trying to read from the stream.
327 ;;; Dispatch to the right function for each fop. Special-case
328 ;;; FOP-BYTE-PUSH since it is real common.
329 (defun load-fasl-group (stream)
330   (when (check-fasl-header stream)
331     (catch 'fasl-group-end
332       (let ((*current-fop-table-index* 0))
333         (loop
334           (let ((byte (read-byte stream)))
335
336             ;; Do some debugging output.
337             #!+sb-show
338             (when *show-fops-p*
339               (let ((ptr *fop-stack-pointer*)
340                     (stack *fop-stack*))
341                 (fresh-line *trace-output*)
342                 ;; The FOP operations are stack based, so it's sorta
343                 ;; logical to display the operand before the operator.
344                 ;; ("reverse Polish notation")
345                 (unless (= ptr (length stack))
346                   (write-char #\space *trace-output*)
347                   (prin1 (svref stack ptr) *trace-output*)
348                   (terpri *trace-output*))
349                 ;; Display the operator.
350                 (format *trace-output*
351                         "~&~S (#X~X at ~D) (~S)~%"
352                         (svref *fop-names* byte)
353                         byte
354                         (1- (file-position stream))
355                         (svref *fop-functions* byte))))
356
357             ;; Actually execute the fop.
358             (if (eql byte 3)
359               ;; FIXME: This is the special case for FOP-BYTE-PUSH.
360               ;; Benchmark to see whether it's really worth special
361               ;; casing it. If it is, at least express the test in
362               ;; terms of a symbolic name for the FOP-BYTE-PUSH code,
363               ;; not a bare '3' (!). Failing that, remove the special
364               ;; case (and the comment at the head of this function
365               ;; which mentions it).
366               (let ((index *fop-stack-pointer*))
367                 (declare (type index index))
368                 (when (zerop index)
369                   (grow-fop-stack)
370                   (setq index *fop-stack-pointer*))
371                 (decf index)
372                 (setq *fop-stack-pointer* index)
373                 (setf (svref *fop-stack* index)
374                       (svref *current-fop-table* (read-byte stream))))
375               (funcall (the function (svref *fop-functions* byte))))))))))
376
377 (defun load-as-fasl (stream verbose print)
378   ;; KLUDGE: ANSI says it's good to do something with the :PRINT
379   ;; argument to LOAD when we're fasloading a file, but currently we
380   ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
381   ;; just disabled that instead of rewriting it.) -- WHN 20000131
382   (declare (ignore print))
383
384   ;; FIXME: In sbcl-0.6.12.8 the OpenBSD implementation of FILE-LENGTH
385   ;; broke because changed handling of Unix stat(2) stuff couldn't
386   ;; deal with OpenBSD's 64-bit size slot. Once that's fixed, this
387   ;; code can be restored.
388   #!-openbsd
389   (when (zerop (file-length stream))
390     (error "attempt to load an empty FASL file:~%  ~S" (namestring stream)))
391
392   (do-load-verbose stream verbose)
393   (let* ((*fasl-file* stream)
394          (*current-fop-table* (or (pop *free-fop-tables*) (make-array 1000)))
395          (*current-fop-table-size* (length *current-fop-table*))
396          (*fop-stack-pointer-on-entry* *fop-stack-pointer*))
397     (unwind-protect
398         ;; FIXME: This should probably become
399         ;;   (LOOP WHILE (LOAD-FASL-GROUP-STREAM))
400         ;; but as a LOOP newbie I don't want to do that until I can
401         ;; test it.
402         (do ((loaded-group (load-fasl-group stream) (load-fasl-group stream)))
403             ((not loaded-group)))
404       (setq *fop-stack-pointer* *fop-stack-pointer-on-entry*)
405       (push *current-fop-table* *free-fop-tables*)
406       ;; NIL out the stack and table, so that we don't hold onto garbage.
407       ;;
408       ;; FIXME: Couldn't we just get rid of the free fop table pool so
409       ;; that some of this NILing out would go away?
410       (fill *fop-stack* nil :end *fop-stack-pointer-on-entry*)
411       (fill *current-fop-table* nil)))
412   t)
413 \f
414 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
415
416 #|
417 (defvar *fop-counts* (make-array 256 :initial-element 0))
418 (defvar *fop-times* (make-array 256 :initial-element 0))
419 (defvar *print-fops* nil)
420
421 (defun clear-counts ()
422   (fill (the simple-vector *fop-counts*) 0)
423   (fill (the simple-vector *fop-times*) 0)
424   t)
425
426 (defun analyze-counts ()
427   (let ((counts ())
428         (total-count 0)
429         (times ())
430         (total-time 0))
431     (macrolet ((breakdown (lvar tvar vec)
432                  `(progn
433                    (dotimes (i 255)
434                      (declare (fixnum i))
435                      (let ((n (svref ,vec i)))
436                        (push (cons (svref *fop-names* i) n) ,lvar)
437                        (incf ,tvar n)))
438                    (setq ,lvar (subseq (sort ,lvar #'(lambda (x y)
439                                                        (> (cdr x) (cdr y))))
440                                        0 10)))))
441
442       (breakdown counts total-count *fop-counts*)
443       (breakdown times total-time *fop-times*)
444       (format t "Total fop count is ~D~%" total-count)
445       (dolist (c counts)
446         (format t "~30S: ~4D~%" (car c) (cdr c)))
447       (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
448       (dolist (m times)
449         (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))
450 |#
451