X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcompiler%2Fgeneric%2Fgenesis.lisp;h=12b5b01f001012b4c2435a3a5b5677370cbb05aa;hb=e4d1085d9572b5ebf110093a04914725e4c583d4;hp=bfe95ecfb579d2c02611da3c8e110cc1bc263071;hpb=4eb1a6d3ad2b7dcc19ac0ec979a1eb1eb049659a;p=sbcl.git diff --git a/src/compiler/generic/genesis.lisp b/src/compiler/generic/genesis.lisp index bfe95ec..12b5b01 100644 --- a/src/compiler/generic/genesis.lisp +++ b/src/compiler/generic/genesis.lisp @@ -12,7 +12,7 @@ ;;;; for !COLD-INIT to be called at cold load time. !COLD-INIT is ;;;; responsible for explicitly initializing anything which has to be ;;;; initialized early before it transfers control to the ordinary -;;;; top-level forms. +;;;; top level forms. ;;;; ;;;; (In CMU CL, and in SBCL as of 0.6.9 anyway, functions not defined ;;;; by DEFUN aren't set up specially by GENESIS. In particular, @@ -160,7 +160,7 @@ (ash (descriptor-low des) (- 1 sb!vm:n-lowtag-bits))))) (format stream - "for fixnum: ~D" + "for fixnum: ~W" (if (> unsigned #x1FFFFFFF) (- unsigned #x40000000) unsigned)))) @@ -285,7 +285,7 @@ (defun make-fixnum-descriptor (num) (when (>= (integer-length num) (1+ (- sb!vm:n-word-bits sb!vm:n-lowtag-bits))) - (error "~D is too big for a fixnum." num)) + (error "~W is too big for a fixnum." num)) (make-random-descriptor (ash num (1- sb!vm:n-lowtag-bits)))) (defun make-other-immediate-descriptor (data type) @@ -344,32 +344,6 @@ ;;; pathname), or NIL if we're not currently cold loading any object file (defvar *cold-load-filename* nil) (declaim (type (or string null) *cold-load-filename*)) - -;;; This is vestigial support for the CMU CL byte-swapping code. CMU -;;; CL code tested for whether it needed to swap bytes in GENESIS by -;;; comparing the byte order of *BACKEND* to the byte order of -;;; *NATIVE-BACKEND*, a concept which doesn't exist in SBCL. Instead, -;;; in SBCL byte order swapping would need to be explicitly requested -;;; with a &KEY argument to GENESIS. -;;; -;;; I'm not sure whether this is a problem or not, and I don't have a -;;; machine with different byte order to test to find out for sure. -;;; The version of the system which is fed to the cross-compiler is -;;; now written in a subset of Common Lisp which doesn't require -;;; dumping a lot of things in such a way that machine byte order -;;; matters. (Mostly this is a matter of not using any specialized -;;; array type unless there's portable, high-level code to dump it.) -;;; If it *is* a problem, and you're trying to resurrect this code, -;;; please test particularly carefully, since I haven't had a chance -;;; to test the byte-swapping code at all. -- WHN 19990816 -;;; -;;; When this variable is non-NIL, byte-swapping is enabled wherever -;;; classic GENESIS would have done it. I.e. the value of this variable -;;; is the logical complement of -;;; (EQ (SB!C:BACKEND-BYTE-ORDER SB!C:*NATIVE-BACKEND*) -;;; (SB!C:BACKEND-BYTE-ORDER SB!C:*BACKEND*)) -;;; from CMU CL. -(defvar *genesis-byte-order-swap-p*) ;;;; miscellaneous stuff to read and write the core memory @@ -379,58 +353,44 @@ "Push THING onto the given cold-load LIST." `(setq ,list (cold-cons ,thing ,list))) -(defun maybe-byte-swap (word) - (declare (type (unsigned-byte 32) word)) - (aver (= sb!vm:n-word-bits 32)) - (aver (= sb!vm:n-byte-bits 8)) - (if (not *genesis-byte-order-swap-p*) - word - (logior (ash (ldb (byte 8 0) word) 24) - (ash (ldb (byte 8 8) word) 16) - (ash (ldb (byte 8 16) word) 8) - (ldb (byte 8 24) word)))) - -(defun maybe-byte-swap-short (short) - (declare (type (unsigned-byte 16) short)) - (aver (= sb!vm:n-word-bits 32)) - (aver (= sb!vm:n-byte-bits 8)) - (if (not *genesis-byte-order-swap-p*) - short - (logior (ash (ldb (byte 8 0) short) 8) - (ldb (byte 8 8) short)))) - ;;; BYTE-VECTOR-REF-32 and friends. These are like SAP-REF-n, except ;;; that instead of a SAP we use a byte vector (macrolet ((make-byte-vector-ref-n (n) (let* ((name (intern (format nil "BYTE-VECTOR-REF-~A" n))) (number-octets (/ n 8)) - (ash-list + (ash-list-le (loop for i from 0 to (1- number-octets) collect `(ash (aref byte-vector (+ byte-index ,i)) ,(* i 8)))) - (setf-list + (ash-list-be + (loop for i from 0 to (1- number-octets) + collect `(ash (aref byte-vector (+ byte-index + ,(- number-octets 1 i))) + ,(* i 8)))) + (setf-list-le (loop for i from 0 to (1- number-octets) append `((aref byte-vector (+ byte-index ,i)) - (ldb (byte 8 ,(* i 8)) new-value))))) + (ldb (byte 8 ,(* i 8)) new-value)))) + (setf-list-be + (loop for i from 0 to (1- number-octets) + append + `((aref byte-vector (+ byte-index ,i)) + (ldb (byte 8 ,(- n 8 (* i 8))) new-value))))) `(progn (defun ,name (byte-vector byte-index) - (aver (= sb!vm:n-word-bits 32)) - (aver (= sb!vm:n-byte-bits 8)) - (ecase sb!c:*backend-byte-order* - (:little-endian - (logior ,@ash-list)) - (:big-endian - (error "stub: no big-endian ports of SBCL (yet?)")))) - (defun (setf ,name) (new-value byte-vector byte-index) - (aver (= sb!vm:n-word-bits 32)) - (aver (= sb!vm:n-byte-bits 8)) - (ecase sb!c:*backend-byte-order* - (:little-endian - (setf ,@setf-list)) - (:big-endian - (error "stub: no big-endian ports of SBCL (yet?)")))))))) + (aver (= sb!vm:n-word-bits 32)) + (aver (= sb!vm:n-byte-bits 8)) + (logior ,@(ecase sb!c:*backend-byte-order* + (:little-endian ash-list-le) + (:big-endian ash-list-be)))) + (defun (setf ,name) (new-value byte-vector byte-index) + (aver (= sb!vm:n-word-bits 32)) + (aver (= sb!vm:n-byte-bits 8)) + (setf ,@(ecase sb!c:*backend-byte-order* + (:little-endian setf-list-le) + (:big-endian setf-list-be)))))))) (make-byte-vector-ref-n 8) (make-byte-vector-ref-n 16) (make-byte-vector-ref-n 32)) @@ -443,11 +403,7 @@ (bytes (gspace-bytes gspace)) (byte-index (ash (+ index (descriptor-word-offset address)) sb!vm:word-shift)) - ;; KLUDGE: Do we really need to do byte swap here? It seems - ;; as though we shouldn't.. (This attempts to be a literal - ;; translation of CMU CL code, and I don't have a big-endian - ;; machine to test it.) -- WHN 19990817 - (value (maybe-byte-swap (byte-vector-ref-32 bytes byte-index)))) + (value (byte-vector-ref-32 bytes byte-index))) (make-random-descriptor value))) (declaim (ftype (function (descriptor) descriptor) read-memory)) @@ -457,12 +413,13 @@ (read-wordindexed address 0)) ;;; (Note: In CMU CL, this function expected a SAP-typed ADDRESS -;;; value, instead of the SAPINT we use here.) -(declaim (ftype (function (sb!vm:word descriptor) (values)) note-load-time-value-reference)) +;;; value, instead of the SAP-INT we use here.) +(declaim (ftype (function (sb!vm:word descriptor) (values)) + note-load-time-value-reference)) (defun note-load-time-value-reference (address marker) (cold-push (cold-cons (cold-intern :load-time-value-fixup) - (cold-cons (sapint-to-core address) + (cold-cons (sap-int-to-core address) (cold-cons (number-to-core (descriptor-word-offset marker)) *nil-descriptor*))) @@ -486,15 +443,11 @@ sb!vm:lowtag-mask) (ash index sb!vm:word-shift)) value) - ;; Note: There's a MAYBE-BYTE-SWAP in here in CMU CL, which I - ;; think is unnecessary now that we're doing the write - ;; byte-by-byte at high level. (I can't test this, though..) -- - ;; WHN 19990817 (let* ((bytes (gspace-bytes (descriptor-intuit-gspace address))) (byte-index (ash (+ index (descriptor-word-offset address)) sb!vm:word-shift))) (setf (byte-vector-ref-32 bytes byte-index) - (maybe-byte-swap (descriptor-bits value)))))) + (descriptor-bits value))))) (declaim (ftype (function (descriptor descriptor)) write-memory)) (defun write-memory (address value) @@ -593,7 +546,7 @@ ((> index words) (unless (zerop (integer-length remainder)) ;; FIXME: Shouldn't this be a fatal error? - (warn "~D words of ~D were written, but ~D bits were left over." + (warn "~W words of ~W were written, but ~W bits were left over." words n remainder))) (let ((word (ldb (byte sb!vm:n-word-bits 0) remainder))) (write-wordindexed handle index @@ -713,15 +666,15 @@ (float (float-to-core number)) (t (error "~S isn't a cold-loadable number at all!" number)))) -(declaim (ftype (function (sb!vm:word) descriptor) sap-to-core)) -(defun sapint-to-core (sapint) +(declaim (ftype (function (sb!vm:word) descriptor) sap-int-to-core)) +(defun sap-int-to-core (sap-int) (let ((des (allocate-unboxed-object *dynamic* sb!vm:n-word-bits (1- sb!vm:sap-size) sb!vm:sap-widetag))) (write-wordindexed des sb!vm:sap-pointer-slot - (make-random-descriptor sapint)) + (make-random-descriptor sap-int)) des)) ;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR. @@ -760,7 +713,7 @@ (write-wordindexed symbol sb!vm:symbol-hash-slot (make-fixnum-descriptor - (1+ (random sb!vm:*target-most-positive-fixnum*)))) + (1+ (random sb!xc:most-positive-fixnum)))) (write-wordindexed symbol sb!vm:symbol-plist-slot *nil-descriptor*) (write-wordindexed symbol sb!vm:symbol-name-slot (string-to-core name *dynamic*)) @@ -1001,8 +954,8 @@ (defvar *cold-package-symbols*) (declaim (type list *cold-package-symbols*)) -;;; a map from descriptors to symbols, so that we can back up. The key is the -;;; address in the target core. +;;; a map from descriptors to symbols, so that we can back up. The key +;;; is the address in the target core. (defvar *cold-symbols*) (declaim (type hash-table *cold-symbols*)) @@ -1013,7 +966,7 @@ (defun cold-intern (symbol &optional (package (symbol-package symbol))) ;; Anything on the cross-compilation host which refers to the target - ;; machinery through the host SB-XC package can be translated to + ;; machinery through the host SB-XC package should be translated to ;; something on the target which refers to the same machinery ;; through the target COMMON-LISP package. (let ((p (find-package "SB-XC"))) @@ -1022,6 +975,31 @@ (when (eq (symbol-package symbol) p) (setf symbol (intern (symbol-name symbol) *cl-package*)))) + ;; Make sure that the symbol has an appropriate package. In + ;; particular, catch the so-easy-to-make error of typing something + ;; like SB-KERNEL:%BYTE-BLT in cold sources when what you really + ;; need is SB!KERNEL:%BYTE-BLT. + (let ((package-name (package-name package))) + (cond ((find package-name '("COMMON-LISP" "KEYWORD") :test #'string=) + ;; Cold interning things in these standard packages is OK. + ;; (Cold interning things in the other standard package, + ;; CL-USER, isn't OK. We just use CL-USER to expose symbols + ;; whose homes are in other packages. Thus, trying to cold + ;; intern a symbol whose home package is CL-USER probably + ;; means that a coding error has been made somewhere.) + (values)) + ((string= package-name "SB!" :end1 3 :end2 3) + ;; That looks OK, too. (All the target-code packages + ;; have names like that.) + (values)) + (t + ;; looks bad: maybe COMMON-LISP-USER? maybe an extension + ;; package in the xc host? something we can't think of + ;; a valid reason to cold intern, anyway... + (bug + "internal error: PACKAGE-NAME=~S looks too much like a typo." + package-name)))) + (let (;; Information about each cold-interned symbol is stored ;; in COLD-INTERN-INFO. ;; (CAR COLD-INTERN-INFO) = descriptor of symbol @@ -1108,7 +1086,7 @@ (descriptor-low *nil-descriptor*)))) (unless (= offset-wanted offset-found) ;; FIXME: should be fatal - (warn "Offset from ~S to ~S is ~D, not ~D" + (warn "Offset from ~S to ~S is ~W, not ~W" symbol nil offset-found @@ -1136,13 +1114,17 @@ ;;; intern it. (defun finish-symbols () - ;; FIXME: Why use SETQ (setting symbol value) instead of just using - ;; the function values for these things?? I.e. why do we need this - ;; section at all? Is it because all the FDEFINITION stuff gets in - ;; the way of reading function values and is too hairy to rely on at - ;; cold boot? FIXME: Most of these are in *STATIC-SYMBOLS* in - ;; parms.lisp, but %HANDLE-FUN-END-BREAKPOINT is not. Why? - ;; Explain. + ;; I think the point of setting these functions into SYMBOL-VALUEs + ;; here, instead of using SYMBOL-FUNCTION, is that in CMU CL + ;; SYMBOL-FUNCTION reduces to FDEFINITION, which is a pretty + ;; hairy operation (involving globaldb.lisp etc.) which we don't + ;; want to invoke early in cold init. -- WHN 2001-12-05 + ;; + ;; FIXME: So OK, that's a reasonable reason to do something weird like + ;; this, but this is still a weird thing to do, and we should change + ;; the names to highlight that something weird is going on. Perhaps + ;; *MAYBE-GC-FUN*, *INTERNAL-ERROR-FUN*, *HANDLE-BREAKPOINT-FUN*, + ;; and *HANDLE-FUN-END-BREAKPOINT-FUN*... (macrolet ((frob (symbol) `(cold-set ',symbol (cold-fdefinition-object (cold-intern ',symbol))))) @@ -1153,7 +1135,6 @@ (cold-set '*current-catch-block* (make-fixnum-descriptor 0)) (cold-set '*current-unwind-protect-block* (make-fixnum-descriptor 0)) - (cold-set '*eval-stack-top* (make-fixnum-descriptor 0)) (cold-set '*free-interrupt-context-index* (make-fixnum-descriptor 0)) @@ -1399,28 +1380,29 @@ sb!vm:word-shift)))) (#.sb!vm:closure-header-widetag (make-random-descriptor - (cold-foreign-symbol-address-as-integer "closure_tramp"))))) + (cold-foreign-symbol-address-as-integer + "closure_tramp"))))) fdefn)) (defun initialize-static-fns () (let ((*cold-fdefn-gspace* *static*)) - (dolist (sym sb!vm:*static-functions*) + (dolist (sym sb!vm:*static-funs*) (let* ((fdefn (cold-fdefinition-object (cold-intern sym))) (offset (- (+ (- (descriptor-low fdefn) sb!vm:other-pointer-lowtag) (* sb!vm:fdefn-raw-addr-slot sb!vm:n-word-bytes)) (descriptor-low *nil-descriptor*))) - (desired (sb!vm:static-function-offset sym))) + (desired (sb!vm:static-fun-offset sym))) (unless (= offset desired) ;; FIXME: should be fatal - (warn "Offset from FDEFN ~S to ~S is ~D, not ~D." + (warn "Offset from FDEFN ~S to ~S is ~W, not ~W." sym nil offset desired)))))) (defun list-all-fdefn-objects () (let ((result *nil-descriptor*)) - (maphash #'(lambda (key value) - (declare (ignore key)) - (cold-push value result)) + (maphash (lambda (key value) + (declare (ignore key)) + (cold-push value result)) *cold-fdefn-objects*) result)) @@ -1582,11 +1564,7 @@ (:alpha (ecase kind (:jmp-hint - (assert (zerop (ldb (byte 2 0) value))) - #+nil ;; was commented out in cmucl source too. Don't know what - ;; it does -dan 2001.05.03 - (setf (sap-ref-16 sap 0) - (logior (sap-ref-16 sap 0) (ldb (byte 14 0) (ash value -2))))) + (assert (zerop (ldb (byte 2 0) value)))) (:bits-63-48 (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)) (value (if (logbitp 31 value) (+ value (ash 1 32)) value)) @@ -1613,6 +1591,34 @@ (ldb (byte 8 0) value) (byte-vector-ref-8 gspace-bytes (1+ gspace-byte-offset)) (ldb (byte 8 8) value))))) + (:ppc + (ecase kind + (:ba + (setf (byte-vector-ref-32 gspace-bytes gspace-byte-offset) + (dpb (ash value -2) (byte 24 2) + (byte-vector-ref-32 gspace-bytes gspace-byte-offset)))) + (:ha + (let* ((h (ldb (byte 16 16) value)) + (l (ldb (byte 16 0) value))) + (setf (byte-vector-ref-16 gspace-bytes (+ gspace-byte-offset 2)) + (if (logbitp 15 l) (ldb (byte 16 0) (1+ h)) h)))) + (:l + (setf (byte-vector-ref-16 gspace-bytes (+ gspace-byte-offset 2)) + (ldb (byte 16 0) value))))) + (:sparc + (ecase kind + (:call + (error "Can't deal with call fixups yet.")) + (:sethi + (setf (byte-vector-ref-32 gspace-bytes gspace-byte-offset) + (dpb (ldb (byte 22 10) value) + (byte 22 0) + (byte-vector-ref-32 gspace-bytes gspace-byte-offset)))) + (:add + (setf (byte-vector-ref-32 gspace-bytes gspace-byte-offset) + (dpb (ldb (byte 10 0) value) + (byte 10 0) + (byte-vector-ref-32 gspace-bytes gspace-byte-offset)))))) (:x86 (let* ((un-fixed-up (byte-vector-ref-32 gspace-bytes gspace-byte-offset)) @@ -1686,41 +1692,43 @@ ;;;; general machinery for cold-loading FASL files ;;; FOP functions for cold loading -(defvar *cold-fop-functions* - ;; We start out with a copy of the ordinary *FOP-FUNCTIONS*. The - ;; ones which aren't appropriate for cold load will be destructively +(defvar *cold-fop-funs* + ;; We start out with a copy of the ordinary *FOP-FUNS*. The ones + ;; which aren't appropriate for cold load will be destructively ;; modified. - (copy-seq *fop-functions*)) + (copy-seq *fop-funs*)) -(defvar *normal-fop-functions*) +(defvar *normal-fop-funs*) ;;; Cause a fop to have a special definition for cold load. ;;; ;;; This is similar to DEFINE-FOP, but unlike DEFINE-FOP, this version ;;; (1) looks up the code for this name (created by a previous ;; DEFINE-FOP) instead of creating a code, and -;;; (2) stores its definition in the *COLD-FOP-FUNCTIONS* vector, -;;; instead of storing in the *FOP-FUNCTIONS* vector. -(defmacro define-cold-fop ((name &optional (pushp t)) &rest forms) - (aver (member pushp '(nil t :nope))) +;;; (2) stores its definition in the *COLD-FOP-FUNS* vector, +;;; instead of storing in the *FOP-FUNS* vector. +(defmacro define-cold-fop ((name &key (pushp t) (stackp t)) &rest forms) + (aver (member pushp '(nil t))) + (aver (member stackp '(nil t))) (let ((code (get name 'fop-code)) (fname (symbolicate "COLD-" name))) (unless code (error "~S is not a defined FOP." name)) `(progn (defun ,fname () - ,@(if (eq pushp :nope) - forms - `((with-fop-stack ,pushp ,@forms)))) - (setf (svref *cold-fop-functions* ,code) #',fname)))) - -(defmacro clone-cold-fop ((name &optional (pushp t)) (small-name) &rest forms) - (aver (member pushp '(nil t :nope))) + ,@(if stackp + `((with-fop-stack ,pushp ,@forms)) + forms)) + (setf (svref *cold-fop-funs* ,code) #',fname)))) + +(defmacro clone-cold-fop ((name &key (pushp t) (stackp t)) (small-name) &rest forms) + (aver (member pushp '(nil t))) + (aver (member stackp '(nil t))) `(progn (macrolet ((clone-arg () '(read-arg 4))) - (define-cold-fop (,name ,pushp) ,@forms)) + (define-cold-fop (,name :pushp ,pushp :stackp ,stackp) ,@forms)) (macrolet ((clone-arg () '(read-arg 1))) - (define-cold-fop (,small-name ,pushp) ,@forms)))) + (define-cold-fop (,small-name :pushp ,pushp :stackp ,stackp) ,@forms)))) ;;; Cause a fop to be undefined in cold load. (defmacro not-cold-fop (name) @@ -1733,8 +1741,8 @@ (defun cold-load (filename) #!+sb-doc "Load the file named by FILENAME into the cold load image being built." - (let* ((*normal-fop-functions* *fop-functions*) - (*fop-functions* *cold-fop-functions*) + (let* ((*normal-fop-funs* *fop-funs*) + (*fop-funs* *cold-fop-funs*) (*cold-load-filename* (etypecase filename (string filename) (pathname (namestring filename))))) @@ -1753,14 +1761,14 @@ (define-cold-fop (fop-empty-list) *nil-descriptor*) (define-cold-fop (fop-truth) (cold-intern t)) -(define-cold-fop (fop-normal-load :nope) - (setq *fop-functions* *normal-fop-functions*)) +(define-cold-fop (fop-normal-load :stackp nil) + (setq *fop-funs* *normal-fop-funs*)) -(define-fop (fop-maybe-cold-load 82 :nope) +(define-fop (fop-maybe-cold-load 82 :stackp nil) (when *cold-load-filename* - (setq *fop-functions* *cold-fop-functions*))) + (setq *fop-funs* *cold-fop-funs*))) -(define-cold-fop (fop-maybe-cold-load :nope)) +(define-cold-fop (fop-maybe-cold-load :stackp nil)) (clone-cold-fop (fop-struct) (fop-small-struct) @@ -1948,7 +1956,7 @@ (8 sb!vm:simple-array-unsigned-byte-8-widetag) (16 sb!vm:simple-array-unsigned-byte-16-widetag) (32 sb!vm:simple-array-unsigned-byte-32-widetag) - (t (error "losing element size: ~D" sizebits)))) + (t (error "losing element size: ~W" sizebits)))) (result (allocate-vector-object *dynamic* sizebits len type)) (start (+ (descriptor-byte-offset result) (ash sb!vm:vector-data-offset sb!vm:word-shift))) @@ -2020,7 +2028,7 @@ ;;;; cold fops for loading numbers (defmacro define-cold-number-fop (fop) - `(define-cold-fop (,fop :nope) + `(define-cold-fop (,fop :stackp nil) ;; Invoke the ordinary warm version of this fop to push the ;; number. (,fop) @@ -2187,7 +2195,7 @@ *load-time-value-counter* sb!vm:simple-vector-widetag))) -(define-cold-fop (fop-funcall-for-effect nil) +(define-cold-fop (fop-funcall-for-effect :pushp nil) (if (= (read-arg 1) 0) (cold-push (pop-stack) *current-reversed-cold-toplevels*) @@ -2195,17 +2203,17 @@ ;;;; cold fops for fixing up circularities -(define-cold-fop (fop-rplaca nil) +(define-cold-fop (fop-rplaca :pushp nil) (let ((obj (svref *current-fop-table* (read-arg 4))) (idx (read-arg 4))) (write-memory (cold-nthcdr idx obj) (pop-stack)))) -(define-cold-fop (fop-rplacd nil) +(define-cold-fop (fop-rplacd :pushp nil) (let ((obj (svref *current-fop-table* (read-arg 4))) (idx (read-arg 4))) (write-wordindexed (cold-nthcdr idx obj) 1 (pop-stack)))) -(define-cold-fop (fop-svset nil) +(define-cold-fop (fop-svset :pushp nil) (let ((obj (svref *current-fop-table* (read-arg 4))) (idx (read-arg 4))) (write-wordindexed obj @@ -2215,12 +2223,14 @@ (#.sb!vm:other-pointer-lowtag 2))) (pop-stack)))) -(define-cold-fop (fop-structset nil) +(define-cold-fop (fop-structset :pushp nil) (let ((obj (svref *current-fop-table* (read-arg 4))) (idx (read-arg 4))) (write-wordindexed obj (1+ idx) (pop-stack)))) -(define-cold-fop (fop-nthcdr t) +;;; In the original CMUCL code, this actually explicitly declared PUSHP +;;; to be T, even though that's what it defaults to in DEFINE-COLD-FOP. +(define-cold-fop (fop-nthcdr) (cold-nthcdr (read-arg 4) (pop-stack))) (defun cold-nthcdr (index obj) @@ -2238,7 +2248,7 @@ ;; (SETF CAR). (make-hash-table :test 'equal)) -(define-cold-fop (fop-fset nil) +(define-cold-fop (fop-fset :pushp nil) (let* ((fn (pop-stack)) (cold-name (pop-stack)) (warm-name (warm-fun-name cold-name))) @@ -2303,7 +2313,7 @@ #!+sb-show (when *show-pre-fixup-code-p* (format *trace-output* - "~&/raw code from code-fop ~D ~D:~%" + "~&/raw code from code-fop ~W ~W:~%" nconst code-size) (do ((i start (+ i sb!vm:n-word-bytes))) @@ -2318,14 +2328,14 @@ (define-cold-code-fop fop-small-code (read-arg 1) (read-arg 2)) -(clone-cold-fop (fop-alter-code nil) +(clone-cold-fop (fop-alter-code :pushp nil) (fop-byte-alter-code) (let ((slot (clone-arg)) (value (pop-stack)) (code (pop-stack))) (write-wordindexed code slot value))) -(define-cold-fop (fop-function-entry) +(define-cold-fop (fop-fun-entry) (let* ((type (pop-stack)) (arglist (pop-stack)) (name (pop-stack)) @@ -2336,8 +2346,7 @@ sb!vm:fun-pointer-lowtag)) (next (read-wordindexed code-object sb!vm:code-entry-points-slot))) (unless (zerop (logand offset sb!vm:lowtag-mask)) - ;; FIXME: This should probably become a fatal error. - (warn "unaligned function entry: ~S at #X~X" name offset)) + (error "unaligned function entry: ~S at #X~X" name offset)) (write-wordindexed code-object sb!vm:code-entry-points-slot fn) (write-memory fn (make-other-immediate-descriptor @@ -2362,8 +2371,7 @@ ;; code instead of a pointer back to the object ;; itself.) Ask on the mailing list whether ;; this is documented somewhere, and if not, - ;; try to reverse engineer some documentation - ;; before release. + ;; try to reverse engineer some documentation. #!-x86 ;; a pointer back to the function object, as ;; described in CMU CL @@ -2556,8 +2564,8 @@ (maybe-record-with-translated-name '("-START" "-END") 6))))) (setf constants (sort constants - #'(lambda (const1 const2) - (if (= (second const1) (second const2)) + (lambda (const1 const2) + (if (= (second const1) (second const2)) (< (third const1) (third const2)) (< (second const1) (second const2)))))) (let ((prev-priority (second (car constants)))) @@ -2596,20 +2604,36 @@ (format t " /* 0x~X */~@[ /* ~A */~]~%" value doc)))) (terpri)) - ;; writing codes/strings for internal errors - (format t "#define ERRORS { \\~%") - ;; FIXME: Is this just DOVECTOR? + ;; writing information about internal errors (let ((internal-errors sb!c:*backend-internal-errors*)) (dotimes (i (length internal-errors)) - (format t " ~S, /*~D*/ \\~%" (cdr (aref internal-errors i)) i))) - (format t " NULL \\~%}~%") + (let ((current-error (aref internal-errors i))) + ;; FIXME: this UNLESS should go away (see also FIXME in + ;; interr.lisp) -- APD, 2002-03-05 + (unless (eq nil (car current-error)) + (format t "#define ~A ~D~%" + (substitute #\_ #\- (symbol-name (car current-error))) + i))))) (terpri) + ;; FIXME: The SPARC has a PSEUDO-ATOMIC-TRAP that differs between + ;; platforms. If we export this from the SB!VM package, it gets + ;; written out as #define trap_PseudoAtomic, which is confusing as + ;; the runtime treats trap_ as the prefix for illegal instruction + ;; type things. We therefore don't export it, but instead do + #!+sparc + (when (boundp 'sb!vm::pseudo-atomic-trap) + (format t "#define PSEUDO_ATOMIC_TRAP ~D /* 0x~:*~X */~%" sb!vm::pseudo-atomic-trap) + (terpri)) + ;; possibly this is another candidate for a rename (to + ;; pseudo-atomic-trap-number or pseudo-atomic-magic-constant + ;; [possibly applicable to other platforms]) + ;; writing primitive object layouts (let ((structs (sort (copy-list sb!vm:*primitive-objects*) #'string< - :key #'(lambda (obj) - (symbol-name - (sb!vm:primitive-object-name obj)))))) + :key (lambda (obj) + (symbol-name + (sb!vm:primitive-object-name obj)))))) (format t "#ifndef LANGUAGE_ASSEMBLY~2%") (format t "#define LISPOBJ(x) ((lispobj)x)~2%") (dolist (obj structs) @@ -2642,12 +2666,12 @@ ;; writing static symbol offsets (dolist (symbol (cons nil sb!vm:*static-symbols*)) - ;; FIXME: It would be nice to use longer names NIL and (particularly) T - ;; in #define statements. + ;; FIXME: It would be nice to use longer names than NIL and + ;; (particularly) T in #define statements. (format t "#define ~A LISPOBJ(0x~X)~%" (nsubstitute #\_ #\- - (remove-if #'(lambda (char) - (member char '(#\% #\* #\. #\!))) + (remove-if (lambda (char) + (member char '(#\% #\* #\. #\!))) (symbol-name symbol))) (if *static* ; if we ran GENESIS ;; We actually ran GENESIS, use the real value. @@ -2676,16 +2700,16 @@ (format t "#X~8,'0X: ~S~%" (cdr routine) (car routine))) (let ((funs nil) (undefs nil)) - (maphash #'(lambda (name fdefn) - (let ((fun (read-wordindexed fdefn - sb!vm:fdefn-fun-slot))) - (if (= (descriptor-bits fun) - (descriptor-bits *nil-descriptor*)) - (push name undefs) - (let ((addr (read-wordindexed - fdefn sb!vm:fdefn-raw-addr-slot))) - (push (cons name (descriptor-bits addr)) - funs))))) + (maphash (lambda (name fdefn) + (let ((fun (read-wordindexed fdefn + sb!vm:fdefn-fun-slot))) + (if (= (descriptor-bits fun) + (descriptor-bits *nil-descriptor*)) + (push name undefs) + (let ((addr (read-wordindexed + fdefn sb!vm:fdefn-raw-addr-slot))) + (push (cons name (descriptor-bits addr)) + funs))))) *cold-fdefn-objects*) (format t "~%~|~%initially defined functions:~2%") (setf funs (sort funs #'< :key #'cdr)) @@ -2711,10 +2735,10 @@ initially undefined function references:~2%") (format t "~%~|~%layout names:~2%") (collect ((stuff)) - (maphash #'(lambda (name gorp) - (declare (ignore name)) - (stuff (cons (descriptor-bits (car gorp)) - (cdr gorp)))) + (maphash (lambda (name gorp) + (declare (ignore name)) + (stuff (cons (descriptor-bits (car gorp)) + (cdr gorp)))) *cold-layouts*) (dolist (x (sort (stuff) #'< :key #'car)) (apply #'format t "~8,'0X: ~S[~D]~%~10T~S~%" x)))) @@ -2733,11 +2757,11 @@ initially undefined function references:~2%") (defparameter validate-entry-type-code 3845) (defparameter directory-entry-type-code 3841) (defparameter new-directory-entry-type-code 3861) -(defparameter initial-function-entry-type-code 3863) +(defparameter initial-fun-entry-type-code 3863) (defparameter end-entry-type-code 3840) -(declaim (ftype (function (sb!vm:word) sb!vm:word) write-long)) -(defun write-long (num) ; FIXME: WRITE-WORD would be a better name. +(declaim (ftype (function (sb!vm:word) sb!vm:word) write-word)) +(defun write-word (num) (ecase sb!c:*backend-byte-order* (:little-endian (dotimes (i 4) @@ -2785,14 +2809,14 @@ initially undefined function references:~2%") ;; DATA PAGE ;; ADDRESS ;; PAGE COUNT - (write-long (gspace-identifier gspace)) - (write-long (gspace-free-word-index gspace)) - (write-long *data-page*) + (write-word (gspace-identifier gspace)) + (write-word (gspace-free-word-index gspace)) + (write-word *data-page*) (multiple-value-bind (floor rem) (floor (gspace-byte-address gspace) sb!c:*backend-page-size*) (aver (zerop rem)) - (write-long floor)) - (write-long pages) + (write-word floor)) + (write-word pages) (incf *data-page* pages))) @@ -2817,36 +2841,36 @@ initially undefined function references:~2%") :if-exists :rename-and-delete) ;; Write the magic number. - (write-long core-magic) + (write-word core-magic) ;; Write the Version entry. - (write-long version-entry-type-code) - (write-long 3) - (write-long sbcl-core-version-integer) + (write-word version-entry-type-code) + (write-word 3) + (write-word sbcl-core-version-integer) ;; Write the New Directory entry header. - (write-long new-directory-entry-type-code) - (write-long 17) ; length = (5 words/space) * 3 spaces + 2 for header. + (write-word new-directory-entry-type-code) + (write-word 17) ; length = (5 words/space) * 3 spaces + 2 for header. (output-gspace *read-only*) (output-gspace *static*) (output-gspace *dynamic*) ;; Write the initial function. - (write-long initial-function-entry-type-code) - (write-long 3) + (write-word initial-fun-entry-type-code) + (write-word 3) (let* ((cold-name (cold-intern '!cold-init)) (cold-fdefn (cold-fdefinition-object cold-name)) - (initial-function (read-wordindexed cold-fdefn - sb!vm:fdefn-fun-slot))) + (initial-fun (read-wordindexed cold-fdefn + sb!vm:fdefn-fun-slot))) (format t - "~&/(DESCRIPTOR-BITS INITIAL-FUNCTION)=#X~X~%" - (descriptor-bits initial-function)) - (write-long (descriptor-bits initial-function))) + "~&/(DESCRIPTOR-BITS INITIAL-FUN)=#X~X~%" + (descriptor-bits initial-fun)) + (write-word (descriptor-bits initial-fun))) ;; Write the End entry. - (write-long end-entry-type-code) - (write-long 2))) + (write-word end-entry-type-code) + (write-word 2))) (format t "done]~%") (force-output) @@ -2874,16 +2898,6 @@ initially undefined function references:~2%") ;;; the executable which will load the core. ;;; MAP-FILE-NAME gets (?) a map file. (dunno about this -- WHN 19990815) ;;; -;;; other arguments: -;;; BYTE-ORDER-SWAP-P controls whether GENESIS tries to swap bytes -;;; in some places in the output. It's only appropriate when -;;; cross-compiling from a machine with one byte order to a -;;; machine with the opposite byte order, which is irrelevant in -;;; current (19990816) SBCL, since only the X86 architecture is -;;; supported. If you're trying to add support for more -;;; architectures, see the comments on DEFVAR -;;; *GENESIS-BYTE-ORDER-SWAP-P* for more information. -;;; ;;; FIXME: GENESIS doesn't belong in SB!VM. Perhaps in %KERNEL for now, ;;; perhaps eventually in SB-LD or SB-BOOT. (defun sb!vm:genesis (&key @@ -2891,8 +2905,7 @@ initially undefined function references:~2%") symbol-table-file-name core-file-name map-file-name - c-header-file-name - byte-order-swap-p) + c-header-file-name) (when (and core-file-name (not symbol-table-file-name)) @@ -2934,7 +2947,6 @@ initially undefined function references:~2%") (let* ((*foreign-symbol-placeholder-value* (if core-file-name nil 0)) (*load-time-value-counter* 0) - (*genesis-byte-order-swap-p* byte-order-swap-p) (*cold-fdefn-objects* (make-hash-table :test 'equal)) (*cold-symbols* (make-hash-table :test 'equal)) (*cold-package-symbols* nil) @@ -2946,7 +2958,8 @@ initially undefined function references:~2%") sb!vm:static-space-start)) (*dynamic* (make-gspace :dynamic dynamic-space-id - sb!vm:dynamic-space-start)) + #!+gencgc sb!vm:dynamic-space-start + #!-gencgc sb!vm:dynamic-0-space-start)) (*nil-descriptor* (make-nil-descriptor)) (*current-reversed-cold-toplevels* *nil-descriptor*) (*unbound-marker* (make-other-immediate-descriptor