From: William Harold Newman Date: Thu, 14 Jul 2005 18:35:32 +0000 (+0000) Subject: 0.9.2.44: X-Git-Url: http://repo.macrolet.net/gitweb/?a=commitdiff_plain;h=f1ffbf976aaa50b7b22f126b97e34afe06a91210;p=sbcl.git 0.9.2.44: another slice of whitespace canonicalization (Anyone who ends up here with "cvs annotate" probably wants to look at the "tabby" tagged version.) --- diff --git a/src/compiler/alpha/subprim.lisp b/src/compiler/alpha/subprim.lisp index d81cf12..b3185d1 100644 --- a/src/compiler/alpha/subprim.lisp +++ b/src/compiler/alpha/subprim.lisp @@ -20,7 +20,7 @@ (:temporary (:scs (descriptor-reg) :from (:argument 0)) ptr) (:temporary (:scs (non-descriptor-reg)) temp) (:temporary (:scs (any-reg) :type fixnum :to (:result 0) :target result) - count) + count) (:results (result :scs (any-reg descriptor-reg))) (:policy :fast-safe) (:vop-var vop) @@ -28,24 +28,24 @@ (:generator 50 (move object ptr) (move zero-tn count) - + LOOP - + (inst cmpeq ptr null-tn temp) (inst bne temp done) - + (inst and ptr lowtag-mask temp) (inst xor temp list-pointer-lowtag temp) (inst bne temp not-list) - + (loadw ptr ptr cons-cdr-slot list-pointer-lowtag) (inst addq count (fixnumize 1) count) (inst br zero-tn loop) - + NOT-LIST (cerror-call vop done object-not-list-error ptr) - + DONE (move count result))) - + (define-static-fun length (object) :translate length) diff --git a/src/compiler/alpha/system.lisp b/src/compiler/alpha/system.lisp index a57b8b2..70c7c47 100644 --- a/src/compiler/alpha/system.lisp +++ b/src/compiler/alpha/system.lisp @@ -54,7 +54,7 @@ OTHER-PTR (load-type result object (- other-pointer-lowtag)) - + DONE)) (define-vop (fun-subtype) @@ -70,7 +70,7 @@ (:translate (setf fun-subtype)) (:policy :fast-safe) (:args (type :scs (unsigned-reg) :target result) - (function :scs (descriptor-reg))) + (function :scs (descriptor-reg))) (:arg-types positive-fixnum *) (:temporary (:scs (non-descriptor-reg)) temp) (:results (result :scs (unsigned-reg))) @@ -107,7 +107,7 @@ (:translate set-header-data) (:policy :fast-safe) (:args (x :scs (descriptor-reg) :target res) - (data :scs (any-reg immediate zero))) + (data :scs (any-reg immediate zero))) (:arg-types * positive-fixnum) (:results (res :scs (descriptor-reg))) (:temporary (:scs (non-descriptor-reg)) t1 t2) @@ -120,11 +120,11 @@ (inst bis t1 t2 t1)) (immediate (let ((c (ash (tn-value data) n-widetag-bits))) - (cond ((<= 0 c (1- (ash 1 8))) - (inst bis t1 c t1)) - (t - (inst li c t2) - (inst bis t1 t2 t1))))) + (cond ((<= 0 c (1- (ash 1 8))) + (inst bis t1 c t1)) + (t + (inst li c t2) + (inst bis t1 t2 t1))))) (zero)) (storew t1 x 0 other-pointer-lowtag) (move x res))) @@ -141,8 +141,8 @@ (define-vop (make-other-immediate-type) (:args (val :scs (any-reg descriptor-reg)) - (type :scs (any-reg descriptor-reg immediate) - :target temp)) + (type :scs (any-reg descriptor-reg immediate) + :target temp)) (:results (res :scs (any-reg descriptor-reg))) (:temporary (:scs (non-descriptor-reg)) temp) (:generator 2 @@ -201,7 +201,7 @@ (define-vop (compute-fun) (:args (code :scs (descriptor-reg)) - (offset :scs (signed-reg unsigned-reg))) + (offset :scs (signed-reg unsigned-reg))) (:arg-types * positive-fixnum) (:results (func :scs (descriptor-reg))) (:temporary (:scs (non-descriptor-reg)) ndescr) @@ -239,8 +239,8 @@ (:temporary (:scs (non-descriptor-reg)) count) (:generator 1 (let ((offset - (- (* (+ index vector-data-offset) n-word-bytes) - other-pointer-lowtag))) + (- (* (+ index vector-data-offset) n-word-bytes) + other-pointer-lowtag))) (inst ldl count offset count-vector) (inst addq count 1 count) (inst stl count offset count-vector)))) diff --git a/src/compiler/alpha/type-vops.lisp b/src/compiler/alpha/type-vops.lisp index d8723b1..fe03197 100644 --- a/src/compiler/alpha/type-vops.lisp +++ b/src/compiler/alpha/type-vops.lisp @@ -24,66 +24,66 @@ (inst and value fixnum-tag-mask temp) (inst beq temp (if not-p drop-through target))) (%test-headers value target not-p nil headers - :drop-through drop-through :temp temp))) + :drop-through drop-through :temp temp))) (defun %test-immediate (value target not-p immediate &key temp) (assemble () (inst and value 255 temp) (inst xor temp immediate temp) (if not-p - (inst bne temp target) - (inst beq temp target)))) + (inst bne temp target) + (inst beq temp target)))) (defun %test-lowtag (value target not-p lowtag &key temp) (assemble () (inst and value lowtag-mask temp) (inst xor temp lowtag temp) (if not-p - (inst bne temp target) - (inst beq temp target)))) + (inst bne temp target) + (inst beq temp target)))) (defun %test-headers (value target not-p function-p headers - &key (drop-through (gen-label)) temp) + &key (drop-through (gen-label)) temp) (let ((lowtag (if function-p fun-pointer-lowtag other-pointer-lowtag))) (multiple-value-bind - (when-true when-false) - ;; WHEN-TRUE and WHEN-FALSE are the labels to branch to when - ;; we know it's true and when we know it's false respectively. - (if not-p - (values drop-through target) - (values target drop-through)) + (when-true when-false) + ;; WHEN-TRUE and WHEN-FALSE are the labels to branch to when + ;; we know it's true and when we know it's false respectively. + (if not-p + (values drop-through target) + (values target drop-through)) (assemble () - (%test-lowtag value when-false t lowtag :temp temp) - (load-type temp value (- lowtag)) - (let ((delta 0)) - (do ((remaining headers (cdr remaining))) - ((null remaining)) - (let ((header (car remaining)) - (last (null (cdr remaining)))) - (cond - ((atom header) - (inst subq temp (- header delta) temp) - (setf delta header) - (if last - (if not-p - (inst bne temp target) - (inst beq temp target)) - (inst beq temp when-true))) - (t - (let ((start (car header)) - (end (cdr header))) - (unless (= start bignum-widetag) - (inst subq temp (- start delta) temp) - (setf delta start) - (inst blt temp when-false)) - (inst subq temp (- end delta) temp) - (setf delta end) - (if last - (if not-p - (inst bgt temp target) - (inst ble temp target)) - (inst ble temp when-true)))))))) - (emit-label drop-through))))) + (%test-lowtag value when-false t lowtag :temp temp) + (load-type temp value (- lowtag)) + (let ((delta 0)) + (do ((remaining headers (cdr remaining))) + ((null remaining)) + (let ((header (car remaining)) + (last (null (cdr remaining)))) + (cond + ((atom header) + (inst subq temp (- header delta) temp) + (setf delta header) + (if last + (if not-p + (inst bne temp target) + (inst beq temp target)) + (inst beq temp when-true))) + (t + (let ((start (car header)) + (end (cdr header))) + (unless (= start bignum-widetag) + (inst subq temp (- start delta) temp) + (setf delta start) + (inst blt temp when-false)) + (inst subq temp (- end delta) temp) + (setf delta end) + (if last + (if not-p + (inst bgt temp target) + (inst ble temp target)) + (inst ble temp when-true)))))))) + (emit-label drop-through))))) ;;;; Type checking and testing: @@ -106,24 +106,24 @@ (if (> (apply #'max type-codes) lowtag-limit) 7 2))) (defmacro !define-type-vops (pred-name check-name ptype error-code - (&rest type-codes) - &key &allow-other-keys) + (&rest type-codes) + &key &allow-other-keys) (let ((cost (cost-to-test-types (mapcar #'eval type-codes)))) `(progn ,@(when pred-name - `((define-vop (,pred-name type-predicate) - (:translate ,pred-name) - (:generator ,cost - (test-type value target not-p (,@type-codes) :temp temp))))) + `((define-vop (,pred-name type-predicate) + (:translate ,pred-name) + (:generator ,cost + (test-type value target not-p (,@type-codes) :temp temp))))) ,@(when check-name - `((define-vop (,check-name check-type) - (:generator ,cost - (let ((err-lab - (generate-error-code vop ,error-code value))) - (test-type value err-lab t (,@type-codes) :temp temp) - (move value result)))))) + `((define-vop (,check-name check-type) + (:generator ,cost + (let ((err-lab + (generate-error-code vop ,error-code value))) + (test-type value err-lab t (,@type-codes) :temp temp) + (move value result)))))) ,@(when ptype - `((primitive-type-vop ,check-name (:check) ,ptype)))))) + `((primitive-type-vop ,check-name (:check) ,ptype)))))) ;;;; Other integer ranges. @@ -134,8 +134,8 @@ (multiple-value-bind (yep nope) (if not-p - (values not-target target) - (values target not-target)) + (values not-target target) + (values target not-target)) (assemble () (inst and value fixnum-tag-mask temp) (inst beq temp yep) @@ -146,8 +146,8 @@ (inst li (+ (ash 1 n-widetag-bits) bignum-widetag) temp1) (inst xor temp temp1 temp) (if not-p - (inst bne temp target) - (inst beq temp target)))) + (inst bne temp target) + (inst beq temp target)))) (values)) (define-vop (signed-byte-32-p type-predicate) @@ -161,7 +161,7 @@ (:temporary (:scs (non-descriptor-reg)) temp1) (:generator 45 (let ((loose (generate-error-code vop object-not-signed-byte-32-error - value))) + value))) (signed-byte-32-test value temp temp1 t loose okay)) OKAY (move value result))) @@ -172,9 +172,9 @@ (defun unsigned-byte-32-test (value temp temp1 not-p target not-target) (multiple-value-bind (yep nope) - (if not-p - (values not-target target) - (values target not-target)) + (if not-p + (values not-target target) + (values target not-target)) (assemble () ;; Is it a fixnum? (inst and value fixnum-tag-mask temp1) @@ -193,8 +193,8 @@ (inst beq temp single-word) ;; If it's other than two, we can't be an (unsigned-byte 32) (inst li (logxor (+ (ash 1 n-widetag-bits) bignum-widetag) - (+ (ash 2 n-widetag-bits) bignum-widetag)) - temp1) + (+ (ash 2 n-widetag-bits) bignum-widetag)) + temp1) (inst xor temp temp1 temp) (inst bne temp nope) ;; Get the second digit. @@ -202,7 +202,7 @@ ;; All zeros, its an (unsigned-byte 32). (inst beq temp yep) (inst br zero-tn nope) - + SINGLE-WORD ;; Get the single digit. (loadw temp value bignum-digits-offset other-pointer-lowtag) @@ -210,8 +210,8 @@ ;; positive implies (unsigned-byte 32). FIXNUM (if not-p - (inst blt temp target) - (inst bge temp target)))) + (inst blt temp target) + (inst bge temp target)))) (values)) (define-vop (unsigned-byte-32-p type-predicate) @@ -225,7 +225,7 @@ (:temporary (:scs (non-descriptor-reg)) temp1) (:generator 45 (let ((loose (generate-error-code vop object-not-unsigned-byte-32-error - value))) + value))) (unsigned-byte-32-test value temp temp1 t loose okay)) OKAY (move value result))) @@ -233,7 +233,7 @@ ;;;; List/symbol types: -;;; +;;; ;;; symbolp (or symbol (eq nil)) ;;; consp (and list (not (eq nil))) @@ -255,7 +255,7 @@ (test-type value error t (symbol-header-widetag) :temp temp)) DROP-THRU (move value result))) - + (define-vop (consp type-predicate) (:translate consp) (:temporary (:scs (non-descriptor-reg)) temp) diff --git a/src/compiler/alpha/values.lisp b/src/compiler/alpha/values.lisp index 6b385a4..c0fc37f 100644 --- a/src/compiler/alpha/values.lisp +++ b/src/compiler/alpha/values.lisp @@ -18,8 +18,8 @@ (define-vop (%%nip-values) (:args (last-nipped-ptr :scs (any-reg) :target dest) - (last-preserved-ptr :scs (any-reg) :target src) - (moved-ptrs :scs (any-reg) :more t)) + (last-preserved-ptr :scs (any-reg) :target src) + (moved-ptrs :scs (any-reg) :more t)) (:results (r-moved-ptrs :scs (any-reg) :more t)) (:temporary (:sc any-reg) src) (:temporary (:sc any-reg) dest) @@ -41,14 +41,14 @@ (inst lda csp-tn 0 dest) (inst subq src dest src) (loop for moved = moved-ptrs then (tn-ref-across moved) - while moved - do (sc-case (tn-ref-tn moved) + while moved + do (sc-case (tn-ref-tn moved) ((descriptor-reg any-reg) - (inst subq (tn-ref-tn moved) src (tn-ref-tn moved))) - ((control-stack) - (load-stack-tn temp (tn-ref-tn moved)) - (inst subq temp src temp) - (store-stack-tn (tn-ref-tn moved) temp)))))) + (inst subq (tn-ref-tn moved) src (tn-ref-tn moved))) + ((control-stack) + (load-stack-tn temp (tn-ref-tn moved)) + (inst subq temp src temp) + (store-stack-tn (tn-ref-tn moved) temp)))))) ;;; Push some values onto the stack, returning the start and number of ;;; values pushed as results. It is assumed that the Vals are wired to @@ -68,22 +68,22 @@ (:info nvals) (:temporary (:scs (descriptor-reg)) temp) (:temporary (:scs (descriptor-reg) - :to (:result 0) - :target start) - start-temp) + :to (:result 0) + :target start) + start-temp) (:generator 20 (move csp-tn start-temp) (inst lda csp-tn (* nvals n-word-bytes) csp-tn) (do ((val vals (tn-ref-across val)) - (i 0 (1+ i))) - ((null val)) + (i 0 (1+ i))) + ((null val)) (let ((tn (tn-ref-tn val))) - (sc-case tn - (descriptor-reg - (storew tn start-temp i)) - (control-stack - (load-stack-tn temp tn) - (storew temp start-temp i))))) + (sc-case tn + (descriptor-reg + (storew tn start-temp i)) + (control-stack + (load-stack-tn temp tn) + (storew temp start-temp i))))) (move start-temp start) (inst li (fixnumize nvals) count))) @@ -94,7 +94,7 @@ (:arg-types list) (:policy :fast-safe) (:results (start :scs (any-reg)) - (count :scs (any-reg))) + (count :scs (any-reg))) (:temporary (:scs (descriptor-reg) :type list :from (:argument 0)) list) (:temporary (:scs (non-descriptor-reg)) temp) (:temporary (:scs (non-descriptor-reg)) ndescr) @@ -103,7 +103,7 @@ (:generator 0 (move arg list) (move csp-tn start) - + LOOP (inst cmpeq list null-tn temp) (inst bne temp done) @@ -115,7 +115,7 @@ (inst xor ndescr list-pointer-lowtag ndescr) (inst beq ndescr loop) (error-call vop bogus-arg-to-values-list-error list) - + DONE (inst subq csp-tn start count))) diff --git a/src/compiler/alpha/vm.lisp b/src/compiler/alpha/vm.lisp index d693269..ab416a3 100644 --- a/src/compiler/alpha/vm.lisp +++ b/src/compiler/alpha/vm.lisp @@ -21,15 +21,15 @@ `(eval-when (:compile-toplevel :load-toplevel :execute) (def!constant ,offset-sym ,offset) (setf (svref *register-names* ,offset-sym) - ,(symbol-name name))))) + ,(symbol-name name))))) (defregset (name &rest regs) `(eval-when (:compile-toplevel :load-toplevel :execute) (defparameter ,name (list ,@(mapcar (lambda (name) - (symbolicate name "-OFFSET")) + (symbolicate name "-OFFSET")) regs)))))) ;; c.f. src/runtime/alpha-lispregs.h - + ;; Ra (defreg lip 0) ;; Caller saved 0-7 @@ -73,13 +73,13 @@ (defreg nsp 30) ;; Wired zero (defreg zero 31) - + (defregset non-descriptor-regs nl0 nl1 nl2 nl3 nl4 nl5 nfp cfunc) - + (defregset descriptor-regs fdefn lexenv nargs ocfp lra a0 a1 a2 a3 a4 a5 l0 l1 l2) - + (defregset *register-arg-offsets* a0 a1 a2 a3 a4 a5) (defparameter register-arg-names '(a0 a1 a2 a3 a4 a5))) @@ -96,22 +96,22 @@ (defmacro !define-storage-classes (&rest classes) (do ((forms (list 'progn) - (let* ((class (car classes)) - (sc-name (car class)) - (constant-name (intern (concatenate 'simple-string - (string sc-name) - "-SC-NUMBER")))) - (list* `(define-storage-class ,sc-name ,index - ,@(cdr class)) - `(def!constant ,constant-name ,index) - ;; (The CMU CL version of this macro did - ;; `(EXPORT ',CONSTANT-NAME) - ;; here, but in SBCL we try to have package - ;; structure described statically in one - ;; master source file, instead of building it - ;; dynamically by letting all the system code - ;; modify it as the system boots.) - forms))) + (let* ((class (car classes)) + (sc-name (car class)) + (constant-name (intern (concatenate 'simple-string + (string sc-name) + "-SC-NUMBER")))) + (list* `(define-storage-class ,sc-name ,index + ,@(cdr class)) + `(def!constant ,constant-name ,index) + ;; (The CMU CL version of this macro did + ;; `(EXPORT ',CONSTANT-NAME) + ;; here, but in SBCL we try to have package + ;; structure described statically in one + ;; master source file, instead of building it + ;; dynamically by letting all the system code + ;; modify it as the system boots.) + forms))) (index 0 (1+ index)) (classes classes (cdr classes))) ((null classes) @@ -141,15 +141,15 @@ ;; The non-descriptor stacks. (signed-stack non-descriptor-stack - :element-size 2 :alignment 2) ; (signed-byte 64) + :element-size 2 :alignment 2) ; (signed-byte 64) (unsigned-stack non-descriptor-stack - :element-size 2 :alignment 2) ; (unsigned-byte 64) + :element-size 2 :alignment 2) ; (unsigned-byte 64) (character-stack non-descriptor-stack) ; non-descriptor characters. (sap-stack non-descriptor-stack - :element-size 2 :alignment 2) ; System area pointers. + :element-size 2 :alignment 2) ; System area pointers. (single-stack non-descriptor-stack) ; single-floats (double-stack non-descriptor-stack - :element-size 2 :alignment 2) ; double floats. + :element-size 2 :alignment 2) ; double floats. (complex-single-stack non-descriptor-stack :element-size 2) (complex-double-stack non-descriptor-stack :element-size 4 :alignment 2) @@ -248,8 +248,8 @@ (tn-sym (symbolicate name "-TN"))) `(defparameter ,tn-sym (make-random-tn :kind :normal - :sc (sc-or-lose ',sc) - :offset ,offset-sym))))) + :sc (sc-or-lose ',sc) + :offset ,offset-sym))))) ;; These, we access by foo-TN only @@ -271,12 +271,12 @@ ;; and some floating point values.. (defparameter fp-single-zero-tn (make-random-tn :kind :normal - :sc (sc-or-lose 'single-reg) - :offset 31)) + :sc (sc-or-lose 'single-reg) + :offset 31)) (defparameter fp-double-zero-tn (make-random-tn :kind :normal - :sc (sc-or-lose 'double-reg) - :offset 31)) + :sc (sc-or-lose 'double-reg) + :offset 31)) ;;; If value can be represented as an immediate constant, then return ;;; the appropriate SC number, otherwise return NIL. @@ -287,20 +287,20 @@ (null (sc-number-or-lose 'null )) ((or (integer #.sb!xc:most-negative-fixnum #.sb!xc:most-positive-fixnum) - system-area-pointer character) + system-area-pointer character) (sc-number-or-lose 'immediate )) (symbol (if (static-symbol-p value) - (sc-number-or-lose 'immediate ) - nil)) + (sc-number-or-lose 'immediate ) + nil)) (single-float (if (eql value 0f0) - (sc-number-or-lose 'fp-single-zero ) - nil)) + (sc-number-or-lose 'fp-single-zero ) + nil)) (double-float (if (eql value 0d0) - (sc-number-or-lose 'fp-double-zero ) - nil)))) + (sc-number-or-lose 'fp-double-zero ) + nil)))) ;;;; function call parameters @@ -327,10 +327,10 @@ ;;; a list of TN's describing the register arguments (defparameter *register-arg-tns* (mapcar (lambda (n) - (make-random-tn :kind :normal - :sc (sc-or-lose 'descriptor-reg) - :offset n)) - *register-arg-offsets*)) + (make-random-tn :kind :normal + :sc (sc-or-lose 'descriptor-reg) + :offset n)) + *register-arg-offsets*)) ;;; This is used by the debugger. (def!constant single-value-return-byte-offset 4) @@ -341,10 +341,10 @@ (!def-vm-support-routine location-print-name (tn) ; (declare (type tn tn)) (let ((sb (sb-name (sc-sb (tn-sc tn)))) - (offset (tn-offset tn))) + (offset (tn-offset tn))) (ecase sb (registers (or (svref *register-names* offset) - (format nil "R~D" offset))) + (format nil "R~D" offset))) (float-registers (format nil "F~D" offset)) (control-stack (format nil "CS~D" offset)) (non-descriptor-stack (format nil "NS~D" offset)) diff --git a/src/compiler/generic/array.lisp b/src/compiler/generic/array.lisp index 36f2d49..25df53b 100644 --- a/src/compiler/generic/array.lisp +++ b/src/compiler/generic/array.lisp @@ -15,7 +15,7 @@ (:translate data-vector-ref) (:policy :fast-safe) (:args (object :scs (descriptor-reg)) - (index :scs (unsigned-reg))) + (index :scs (unsigned-reg))) (:arg-types simple-array-nil positive-fixnum) (:results (value :scs (descriptor-reg))) (:result-types *) @@ -39,8 +39,8 @@ (:translate data-vector-set) (:policy :fast-safe) (:args (object :scs (descriptor-reg)) - (index :scs (unsigned-reg)) - (value :scs (descriptor-reg))) + (index :scs (unsigned-reg)) + (value :scs (descriptor-reg))) (:arg-types simple-array-nil positive-fixnum *) (:results (result :scs (descriptor-reg))) (:result-types *) diff --git a/src/compiler/generic/core.lisp b/src/compiler/generic/core.lisp index f5b58ef..c5d9411 100644 --- a/src/compiler/generic/core.lisp +++ b/src/compiler/generic/core.lisp @@ -14,11 +14,11 @@ ;;; A CORE-OBJECT structure holds the state needed to resolve cross-component ;;; references during in-core compilation. (defstruct (core-object - (:constructor make-core-object ()) - #-no-ansi-print-object - (:print-object (lambda (x s) - (print-unreadable-object (x s :type t)))) - (:copier nil)) + (:constructor make-core-object ()) + #-no-ansi-print-object + (:print-object (lambda (x s) + (print-unreadable-object (x s :type t)))) + (:copier nil)) ;; A hashtable translating ENTRY-INFO structures to the corresponding actual ;; FUNCTIONs for functions in this compilation. (entry-table (make-hash-table :test 'eq) :type hash-table) @@ -33,7 +33,7 @@ ;;; Note the existence of FUNCTION. (defun note-fun (info function object) (declare (type function function) - (type core-object object)) + (type core-object object)) (let ((patch-table (core-object-patch-table object))) (dolist (patch (gethash info patch-table)) (setf (code-header-ref (car patch) (the index (cdr patch))) function)) @@ -46,41 +46,41 @@ (declare (list fixup-notes)) (dolist (note fixup-notes) (let* ((kind (fixup-note-kind note)) - (fixup (fixup-note-fixup note)) - (position (fixup-note-position note)) - (name (fixup-name fixup)) - (flavor (fixup-flavor fixup)) - (value (ecase flavor - (:assembly-routine - (aver (symbolp name)) - (or (gethash name *assembler-routines*) - (error "undefined assembler routine: ~S" name))) - (:foreign - (aver (stringp name)) - ;; FOREIGN-SYMBOL-ADDRESS signals an error - ;; if the symbol isn't found. - (foreign-symbol-address name)) - #!+linkage-table - (:foreign-dataref - (aver (stringp name)) - (foreign-symbol-address name t)) - #!+(or x86 x86-64) - (:code-object - (aver (null name)) - (values (get-lisp-obj-address code) t))))) + (fixup (fixup-note-fixup note)) + (position (fixup-note-position note)) + (name (fixup-name fixup)) + (flavor (fixup-flavor fixup)) + (value (ecase flavor + (:assembly-routine + (aver (symbolp name)) + (or (gethash name *assembler-routines*) + (error "undefined assembler routine: ~S" name))) + (:foreign + (aver (stringp name)) + ;; FOREIGN-SYMBOL-ADDRESS signals an error + ;; if the symbol isn't found. + (foreign-symbol-address name)) + #!+linkage-table + (:foreign-dataref + (aver (stringp name)) + (foreign-symbol-address name t)) + #!+(or x86 x86-64) + (:code-object + (aver (null name)) + (values (get-lisp-obj-address code) t))))) (sb!vm:fixup-code-object code position value kind)))) ;;; Stick a reference to the function FUN in CODE-OBJECT at index I. If the ;;; function hasn't been compiled yet, make a note in the patch table. (defun reference-core-fun (code-obj i fun object) (declare (type core-object object) (type functional fun) - (type index i)) + (type index i)) (let* ((info (leaf-info fun)) - (found (gethash info (core-object-entry-table object)))) + (found (gethash info (core-object-entry-table object)))) (if found - (setf (code-header-ref code-obj i) found) - (push (cons code-obj i) - (gethash info (core-object-patch-table object))))) + (setf (code-header-ref code-obj i) found) + (push (cons code-obj i) + (gethash info (core-object-patch-table object))))) (values)) ;;; Call the top level lambda function dumped for ENTRY, returning the @@ -88,15 +88,15 @@ (defun core-call-toplevel-lambda (entry object) (declare (type functional entry) (type core-object object)) (funcall (or (gethash (leaf-info entry) - (core-object-entry-table object)) - (error "Unresolved forward reference.")))) + (core-object-entry-table object)) + (error "Unresolved forward reference.")))) ;;; Backpatch all the DEBUG-INFOs dumped so far with the specified ;;; SOURCE-INFO list. We also check that there are no outstanding ;;; forward references to functions. (defun fix-core-source-info (info object &optional function) (declare (type core-object object) - (type (or null function) function)) + (type (or null function) function)) (aver (zerop (hash-table-count (core-object-patch-table object)))) (let ((source (debug-source-for-info info))) (setf (debug-source-function source) function) diff --git a/src/compiler/generic/early-objdef.lisp b/src/compiler/generic/early-objdef.lisp index c728fad..9ce39f8 100644 --- a/src/compiler/generic/early-objdef.lisp +++ b/src/compiler/generic/early-objdef.lisp @@ -20,12 +20,12 @@ ;;; 'def.*even-fixnum-lowtag' can find them. ;;; Tags for the main low-level types are stored in the low n (usually three) -;;; bits to identify the type of a machine word. Certain constraints +;;; bits to identify the type of a machine word. Certain constraints ;;; apply: ;;; * EVEN-FIXNUM-LOWTAG and ODD-FIXNUM-LOWTAG must be 0 and 4: code ;;; which shifts left two places to convert raw integers to tagged ;;; fixnums is ubiquitous. -;;; * LIST-POINTER-LOWTAG + N-WORD-BYTES = OTHER-POINTER-LOWTAG: NIL +;;; * LIST-POINTER-LOWTAG + N-WORD-BYTES = OTHER-POINTER-LOWTAG: NIL ;;; is both a cons and a symbol (at the same address) and depends on this. ;;; See the definition of SYMBOL in objdef.lisp ;;; * OTHER-POINTER-LOWTAG > 4: Some code in the SPARC backend, @@ -33,7 +33,7 @@ ;;; PSEUDO-ATOMIC is on, doesn't strip the low bits of reg_ALLOC ;;; before ORing in OTHER-POINTER-LOWTAG within a PSEUDO-ATOMIC ;;; section. -;;; * OTHER-IMMEDIATE-0-LOWTAG are spaced 4 apart: various code wants to +;;; * OTHER-IMMEDIATE-0-LOWTAG are spaced 4 apart: various code wants to ;;; iterate through these ;;; * Allocation code on Alpha wants lowtags for heap-allocated ;;; objects to be odd. @@ -110,13 +110,13 @@ ;;; ANDcc tag, 0xA6, tag ;;; JNE tag, label ;;; -;;; rather than two separate tests and jumps +;;; rather than two separate tests and jumps (defenum (:suffix -widetag ;; The first widetag must be greater than SB!VM:LOWTAG-LIMIT ;; otherwise code in generic/early-type-vops will suffer ;; a long, horrible death. --njf, 2004-08-09 - :start (+ (ash 1 n-lowtag-bits) other-immediate-0-lowtag) - :step 4) + :start (+ (ash 1 n-lowtag-bits) other-immediate-0-lowtag) + :step 4) ;; NOTE: the binary numbers off to the side are only valid for 32-bit ;; ports; add #b1000 if you want to know the values for 64-bit ports. ;; And note that the numbers get a little scrambled further down. diff --git a/src/compiler/generic/early-type-vops.lisp b/src/compiler/generic/early-type-vops.lisp index 8f289da..7709680 100644 --- a/src/compiler/generic/early-type-vops.lisp +++ b/src/compiler/generic/early-type-vops.lisp @@ -12,112 +12,112 @@ (defparameter *immediate-types* (list* unbound-marker-widetag character-widetag - (when (= sb!vm::n-word-bits 64) - (list single-float-widetag)))) + (when (= sb!vm::n-word-bits 64) + (list single-float-widetag)))) (defparameter *fun-header-widetags* (list funcallable-instance-header-widetag - simple-fun-header-widetag - closure-header-widetag)) + simple-fun-header-widetag + closure-header-widetag)) (defun canonicalize-headers (headers) (collect ((results)) (let ((start nil) - (prev nil) - (delta (- other-immediate-1-lowtag other-immediate-0-lowtag))) + (prev nil) + (delta (- other-immediate-1-lowtag other-immediate-0-lowtag))) (flet ((emit-test () - (results (if (= start prev) - start - (cons start prev))))) - (dolist (header (sort headers #'<)) - (cond ((null start) - (setf start header) - (setf prev header)) - ((= header (+ prev delta)) - (setf prev header)) - (t - (emit-test) - (setf start header) - (setf prev header)))) - (emit-test))) + (results (if (= start prev) + start + (cons start prev))))) + (dolist (header (sort headers #'<)) + (cond ((null start) + (setf start header) + (setf prev header)) + ((= header (+ prev delta)) + (setf prev header)) + (t + (emit-test) + (setf start header) + (setf prev header)))) + (emit-test))) (results))) (defmacro test-type (value target not-p - (&rest type-codes) - &rest other-args - &key &allow-other-keys) + (&rest type-codes) + &rest other-args + &key &allow-other-keys) ;; Determine what interesting combinations we need to test for. (let* ((type-codes (mapcar #'eval type-codes)) - (fixnump (and (member even-fixnum-lowtag type-codes) - (member odd-fixnum-lowtag type-codes) - t)) - (lowtags (remove lowtag-limit type-codes :test #'<)) - (extended (remove lowtag-limit type-codes :test #'>)) - (immediates (intersection extended *immediate-types* :test #'eql)) - (headers (set-difference extended *immediate-types* :test #'eql)) - (function-p (if (intersection headers *fun-header-widetags*) - (if (subsetp headers *fun-header-widetags*) - t - (error "can't test for mix of function subtypes ~ + (fixnump (and (member even-fixnum-lowtag type-codes) + (member odd-fixnum-lowtag type-codes) + t)) + (lowtags (remove lowtag-limit type-codes :test #'<)) + (extended (remove lowtag-limit type-codes :test #'>)) + (immediates (intersection extended *immediate-types* :test #'eql)) + (headers (set-difference extended *immediate-types* :test #'eql)) + (function-p (if (intersection headers *fun-header-widetags*) + (if (subsetp headers *fun-header-widetags*) + t + (error "can't test for mix of function subtypes ~ and normal header types")) - nil))) + nil))) (unless type-codes (error "At least one type must be supplied for TEST-TYPE.")) (cond (fixnump (when (remove-if (lambda (x) - (or (= x even-fixnum-lowtag) - (= x odd-fixnum-lowtag))) - lowtags) - (error "can't mix fixnum testing with other lowtags")) + (or (= x even-fixnum-lowtag) + (= x odd-fixnum-lowtag))) + lowtags) + (error "can't mix fixnum testing with other lowtags")) (when function-p - (error "can't mix fixnum testing with function subtype testing")) + (error "can't mix fixnum testing with function subtype testing")) (cond - ((and (= sb!vm:n-word-bits 64) immediates headers) - `(%test-fixnum-immediate-and-headers ,value ,target ,not-p - ,(car immediates) - ',(canonicalize-headers - headers) - ,@other-args)) - (immediates - (if (= sb!vm:n-word-bits 64) - `(%test-fixnum-and-immediate ,value ,target ,not-p - ,(car immediates) - ,@other-args) - (error "can't mix fixnum testing with other immediates"))) - (headers - `(%test-fixnum-and-headers ,value ,target ,not-p - ',(canonicalize-headers headers) - ,@other-args)) - (t - `(%test-fixnum ,value ,target ,not-p - ,@other-args)))) + ((and (= sb!vm:n-word-bits 64) immediates headers) + `(%test-fixnum-immediate-and-headers ,value ,target ,not-p + ,(car immediates) + ',(canonicalize-headers + headers) + ,@other-args)) + (immediates + (if (= sb!vm:n-word-bits 64) + `(%test-fixnum-and-immediate ,value ,target ,not-p + ,(car immediates) + ,@other-args) + (error "can't mix fixnum testing with other immediates"))) + (headers + `(%test-fixnum-and-headers ,value ,target ,not-p + ',(canonicalize-headers headers) + ,@other-args)) + (t + `(%test-fixnum ,value ,target ,not-p + ,@other-args)))) (immediates (cond - (headers - (if (= sb!vm:n-word-bits 64) - `(%test-immediate-and-headers ,value ,target ,not-p - ,(car immediates) - ',(canonicalize-headers headers) - ,@other-args) - (error "can't mix testing of immediates with testing of headers"))) - (lowtags - (error "can't mix testing of immediates with testing of lowtags")) - ((cdr immediates) - (error "can't test multiple immediates at the same time")) - (t - `(%test-immediate ,value ,target ,not-p ,(car immediates) - ,@other-args)))) + (headers + (if (= sb!vm:n-word-bits 64) + `(%test-immediate-and-headers ,value ,target ,not-p + ,(car immediates) + ',(canonicalize-headers headers) + ,@other-args) + (error "can't mix testing of immediates with testing of headers"))) + (lowtags + (error "can't mix testing of immediates with testing of lowtags")) + ((cdr immediates) + (error "can't test multiple immediates at the same time")) + (t + `(%test-immediate ,value ,target ,not-p ,(car immediates) + ,@other-args)))) (lowtags (when (cdr lowtags) - (error "can't test multiple lowtags at the same time")) + (error "can't test multiple lowtags at the same time")) (when headers - (error "can't test non-fixnum lowtags and headers at the same time")) + (error "can't test non-fixnum lowtags and headers at the same time")) `(%test-lowtag ,value ,target ,not-p ,(car lowtags) ,@other-args)) (headers `(%test-headers ,value ,target ,not-p ,function-p - ',(canonicalize-headers headers) - ,@other-args)) + ',(canonicalize-headers headers) + ,@other-args)) (t (error "nothing to test?"))))) diff --git a/src/compiler/generic/early-vm.lisp b/src/compiler/generic/early-vm.lisp index 9b854ea..670e0ad 100644 --- a/src/compiler/generic/early-vm.lisp +++ b/src/compiler/generic/early-vm.lisp @@ -37,7 +37,7 @@ ;;; a mask to extract the type from a data block header word (def!constant widetag-mask (1- (ash 1 n-widetag-bits))) -(def!constant sb!xc:most-positive-fixnum +(def!constant sb!xc:most-positive-fixnum (1- (ash 1 (- n-word-bits n-lowtag-bits))) #!+sb-doc "the fixnum closest in value to positive infinity") diff --git a/src/compiler/generic/genesis.lisp b/src/compiler/generic/genesis.lisp index 6e3ab05..fa3c971 100644 --- a/src/compiler/generic/genesis.lisp +++ b/src/compiler/generic/genesis.lisp @@ -35,9 +35,9 @@ ;;; a magic number used to identify our core files (defconstant core-magic (logior (ash (sb!xc:char-code #\S) 24) - (ash (sb!xc:char-code #\B) 16) - (ash (sb!xc:char-code #\C) 8) - (sb!xc:char-code #\L))) + (ash (sb!xc:char-code #\B) 16) + (ash (sb!xc:char-code #\C) 8) + (sb!xc:char-code #\L))) ;;; the current version of SBCL core files ;;; @@ -109,15 +109,15 @@ (multiple-value-bind (outer-index inner-index) (floor index +smallvec-length+) (aref (the smallvec - (svref (bigvec-outer-vector bigvec) outer-index)) - inner-index))) + (svref (bigvec-outer-vector bigvec) outer-index)) + inner-index))) (defun (setf bvref) (new-value bigvec index) (multiple-value-bind (outer-index inner-index) (floor index +smallvec-length+) (setf (aref (the smallvec - (svref (bigvec-outer-vector bigvec) outer-index)) - inner-index) - new-value))) + (svref (bigvec-outer-vector bigvec) outer-index)) + inner-index) + new-value))) ;;; analogous to LENGTH, but for a BIGVEC ;;; @@ -130,29 +130,29 @@ ;;; analogous to WRITE-SEQUENCE, but for a BIGVEC (defun write-bigvec-as-sequence (bigvec stream &key (start 0) end) (loop for i of-type index from start below (or end (bvlength bigvec)) do - (write-byte (bvref bigvec i) - stream))) + (write-byte (bvref bigvec i) + stream))) ;;; analogous to READ-SEQUENCE-OR-DIE, but for a BIGVEC (defun read-bigvec-as-sequence-or-die (bigvec stream &key (start 0) end) (loop for i of-type index from start below (or end (bvlength bigvec)) do - (setf (bvref bigvec i) - (read-byte stream)))) + (setf (bvref bigvec i) + (read-byte stream)))) ;;; Grow BIGVEC (exponentially, so that large increases in size have ;;; asymptotic logarithmic cost per byte). (defun expand-bigvec (bigvec) (let* ((old-outer-vector (bigvec-outer-vector bigvec)) - (length-old-outer-vector (length old-outer-vector)) - (new-outer-vector (make-array (* 2 length-old-outer-vector)))) + (length-old-outer-vector (length old-outer-vector)) + (new-outer-vector (make-array (* 2 length-old-outer-vector)))) (dotimes (i length-old-outer-vector) (setf (svref new-outer-vector i) - (svref old-outer-vector i))) + (svref old-outer-vector i))) (loop for i from length-old-outer-vector below (length new-outer-vector) do - (setf (svref new-outer-vector i) - (make-smallvec))) + (setf (svref new-outer-vector i) + (make-smallvec))) (setf (bigvec-outer-vector bigvec) - new-outer-vector)) + new-outer-vector)) bigvec) ;;;; looking up bytes and multi-byte values in a BIGVEC (considering @@ -168,31 +168,31 @@ (loop for i from 0 to (1- number-octets) collect `(ash (bvref bigvec (+ byte-index ,i)) ,(* i 8)))) - (ash-list-be - (loop for i from 0 to (1- number-octets) - collect `(ash (bvref bigvec - (+ byte-index - ,(- number-octets 1 i))) - ,(* i 8)))) + (ash-list-be + (loop for i from 0 to (1- number-octets) + collect `(ash (bvref bigvec + (+ byte-index + ,(- number-octets 1 i))) + ,(* i 8)))) (setf-list-le (loop for i from 0 to (1- number-octets) append `((bvref bigvec (+ byte-index ,i)) (ldb (byte 8 ,(* i 8)) new-value)))) - (setf-list-be - (loop for i from 0 to (1- number-octets) + (setf-list-be + (loop for i from 0 to (1- number-octets) append - `((bvref bigvec (+ byte-index ,i)) - (ldb (byte 8 ,(- n 8 (* i 8))) new-value))))) + `((bvref bigvec (+ byte-index ,i)) + (ldb (byte 8 ,(- n 8 (* i 8))) new-value))))) `(progn (defun ,name (bigvec byte-index) - (logior ,@(ecase sb!c:*backend-byte-order* - (:little-endian ash-list-le) - (:big-endian ash-list-be)))) - (defun (setf ,name) (new-value bigvec byte-index) - (setf ,@(ecase sb!c:*backend-byte-order* - (:little-endian setf-list-le) - (:big-endian setf-list-be)))))))) + (logior ,@(ecase sb!c:*backend-byte-order* + (:little-endian ash-list-le) + (:big-endian ash-list-be)))) + (defun (setf ,name) (new-value bigvec byte-index) + (setf ,@(ecase sb!c:*backend-byte-order* + (:little-endian setf-list-le) + (:big-endian setf-list-be)))))))) (make-bvref-n 8) (make-bvref-n 16) (make-bvref-n 32) @@ -238,7 +238,7 @@ ;;; a GENESIS-time representation of a memory space (e.g. read-only ;;; space, dynamic space, or static space) (defstruct (gspace (:constructor %make-gspace) - (:copier nil)) + (:copier nil)) ;; name and identifier for this GSPACE (name (missing-arg) :type symbol :read-only t) (identifier (missing-arg) :type fixnum :read-only t) @@ -266,18 +266,18 @@ (defun make-gspace (name identifier byte-address) (unless (zerop (rem byte-address target-space-alignment)) (error "The byte address #X~X is not aligned on a #X~X-byte boundary." - byte-address - target-space-alignment)) + byte-address + target-space-alignment)) (%make-gspace :name name - :identifier identifier - :word-address (ash byte-address (- sb!vm:word-shift)))) + :identifier identifier + :word-address (ash byte-address (- sb!vm:word-shift)))) ;;;; representation of descriptors (defstruct (descriptor - (:constructor make-descriptor - (high low &optional gspace word-offset)) - (:copier nil)) + (:constructor make-descriptor + (high low &optional gspace word-offset)) + (:copier nil)) ;; the GSPACE that this descriptor is allocated in, or NIL if not set yet. (gspace nil :type (or gspace null)) ;; the offset in words from the start of GSPACE, or NIL if not set yet @@ -296,37 +296,37 @@ (let ((lowtag (descriptor-lowtag des))) (print-unreadable-object (des stream :type t) (cond ((or (= lowtag sb!vm:even-fixnum-lowtag) - (= lowtag sb!vm:odd-fixnum-lowtag)) - (let ((unsigned (logior (ash (descriptor-high des) - (1+ (- descriptor-low-bits - sb!vm:n-lowtag-bits))) - (ash (descriptor-low des) - (- 1 sb!vm:n-lowtag-bits))))) - (format stream - "for fixnum: ~W" - (if (> unsigned #x1FFFFFFF) - (- unsigned #x40000000) - unsigned)))) - ((or (= lowtag sb!vm:other-immediate-0-lowtag) - (= lowtag sb!vm:other-immediate-1-lowtag) + (= lowtag sb!vm:odd-fixnum-lowtag)) + (let ((unsigned (logior (ash (descriptor-high des) + (1+ (- descriptor-low-bits + sb!vm:n-lowtag-bits))) + (ash (descriptor-low des) + (- 1 sb!vm:n-lowtag-bits))))) + (format stream + "for fixnum: ~W" + (if (> unsigned #x1FFFFFFF) + (- unsigned #x40000000) + unsigned)))) + ((or (= lowtag sb!vm:other-immediate-0-lowtag) + (= lowtag sb!vm:other-immediate-1-lowtag) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (= lowtag sb!vm:other-immediate-2-lowtag) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (= lowtag sb!vm:other-immediate-3-lowtag)) - (format stream - "for other immediate: #X~X, type #b~8,'0B" - (ash (descriptor-bits des) (- sb!vm:n-widetag-bits)) - (logand (descriptor-low des) sb!vm:widetag-mask))) - (t - (format stream - "for pointer: #X~X, lowtag #b~3,'0B, ~A" - (logior (ash (descriptor-high des) descriptor-low-bits) - (logandc2 (descriptor-low des) sb!vm:lowtag-mask)) - lowtag - (let ((gspace (descriptor-gspace des))) - (if gspace - (gspace-name gspace) - "unknown")))))))) + (format stream + "for other immediate: #X~X, type #b~8,'0B" + (ash (descriptor-bits des) (- sb!vm:n-widetag-bits)) + (logand (descriptor-low des) sb!vm:widetag-mask))) + (t + (format stream + "for pointer: #X~X, lowtag #b~3,'0B, ~A" + (logior (ash (descriptor-high des) descriptor-low-bits) + (logandc2 (descriptor-low des) sb!vm:lowtag-mask)) + lowtag + (let ((gspace (descriptor-gspace des))) + (if gspace + (gspace-name gspace) + "unknown")))))))) ;;; Return a descriptor for a block of LENGTH bytes out of GSPACE. The ;;; free word index is boosted as necessary, and if additional memory @@ -334,27 +334,27 @@ ;;; pointer of type LOWTAG. (defun allocate-cold-descriptor (gspace length lowtag) (let* ((bytes (round-up length (ash 1 sb!vm:n-lowtag-bits))) - (old-free-word-index (gspace-free-word-index gspace)) - (new-free-word-index (+ old-free-word-index - (ash bytes (- sb!vm:word-shift))))) + (old-free-word-index (gspace-free-word-index gspace)) + (new-free-word-index (+ old-free-word-index + (ash bytes (- sb!vm:word-shift))))) ;; Grow GSPACE as necessary until it's big enough to handle ;; NEW-FREE-WORD-INDEX. (do () - ((>= (bvlength (gspace-bytes gspace)) - (* new-free-word-index sb!vm:n-word-bytes))) + ((>= (bvlength (gspace-bytes gspace)) + (* new-free-word-index sb!vm:n-word-bytes))) (expand-bigvec (gspace-bytes gspace))) ;; Now that GSPACE is big enough, we can meaningfully grab a chunk of it. (setf (gspace-free-word-index gspace) new-free-word-index) (let ((ptr (+ (gspace-word-address gspace) old-free-word-index))) (make-descriptor (ash ptr (- sb!vm:word-shift descriptor-low-bits)) - (logior (ash (logand ptr - (1- (ash 1 - (- descriptor-low-bits - sb!vm:word-shift)))) - sb!vm:word-shift) - lowtag) - gspace - old-free-word-index)))) + (logior (ash (logand ptr + (1- (ash 1 + (- descriptor-low-bits + sb!vm:word-shift)))) + sb!vm:word-shift) + lowtag) + gspace + old-free-word-index)))) (defun descriptor-lowtag (des) #!+sb-doc @@ -363,7 +363,7 @@ (defun descriptor-bits (des) (logior (ash (descriptor-high des) descriptor-low-bits) - (descriptor-low des))) + (descriptor-low des))) (defun descriptor-fixnum (des) (let ((bits (descriptor-bits des))) @@ -383,9 +383,9 @@ ;; representation. (let ((lowtag (descriptor-lowtag des))) (if (or (= lowtag sb!vm:even-fixnum-lowtag) - (= lowtag sb!vm:odd-fixnum-lowtag)) - (make-random-descriptor (descriptor-fixnum des)) - (read-wordindexed des 1)))) + (= lowtag sb!vm:odd-fixnum-lowtag)) + (make-random-descriptor (descriptor-fixnum des)) + (read-wordindexed des 1)))) ;;; common idioms (defun descriptor-bytes (des) @@ -406,61 +406,61 @@ ;; code from CMU CL's DESCRIPTOR-SAP function. Some explanation ;; would be nice. -- WHN 19990817 (let ((lowtag (descriptor-lowtag des)) - (high (descriptor-high des)) - (low (descriptor-low des))) + (high (descriptor-high des)) + (low (descriptor-low des))) (if (or (eql lowtag sb!vm:fun-pointer-lowtag) - (eql lowtag sb!vm:instance-pointer-lowtag) - (eql lowtag sb!vm:list-pointer-lowtag) - (eql lowtag sb!vm:other-pointer-lowtag)) - (dolist (gspace (list *dynamic* *static* *read-only*) - (error "couldn't find a GSPACE for ~S" des)) - ;; This code relies on the fact that GSPACEs are aligned - ;; such that the descriptor-low-bits low bits are zero. - (when (and (>= high (ash (gspace-word-address gspace) - (- sb!vm:word-shift descriptor-low-bits))) - (<= high (ash (+ (gspace-word-address gspace) - (gspace-free-word-index gspace)) - (- sb!vm:word-shift descriptor-low-bits)))) - (setf (descriptor-gspace des) gspace) - (setf (descriptor-word-offset des) - (+ (ash (- high (ash (gspace-word-address gspace) - (- sb!vm:word-shift - descriptor-low-bits))) - (- descriptor-low-bits sb!vm:word-shift)) - (ash (logandc2 low sb!vm:lowtag-mask) - (- sb!vm:word-shift)))) - (return gspace))) - (error "don't even know how to look for a GSPACE for ~S" des))))) + (eql lowtag sb!vm:instance-pointer-lowtag) + (eql lowtag sb!vm:list-pointer-lowtag) + (eql lowtag sb!vm:other-pointer-lowtag)) + (dolist (gspace (list *dynamic* *static* *read-only*) + (error "couldn't find a GSPACE for ~S" des)) + ;; This code relies on the fact that GSPACEs are aligned + ;; such that the descriptor-low-bits low bits are zero. + (when (and (>= high (ash (gspace-word-address gspace) + (- sb!vm:word-shift descriptor-low-bits))) + (<= high (ash (+ (gspace-word-address gspace) + (gspace-free-word-index gspace)) + (- sb!vm:word-shift descriptor-low-bits)))) + (setf (descriptor-gspace des) gspace) + (setf (descriptor-word-offset des) + (+ (ash (- high (ash (gspace-word-address gspace) + (- sb!vm:word-shift + descriptor-low-bits))) + (- descriptor-low-bits sb!vm:word-shift)) + (ash (logandc2 low sb!vm:lowtag-mask) + (- sb!vm:word-shift)))) + (return gspace))) + (error "don't even know how to look for a GSPACE for ~S" des))))) (defun make-random-descriptor (value) (make-descriptor (logand (ash value (- descriptor-low-bits)) - (1- (ash 1 - (- sb!vm:n-word-bits - descriptor-low-bits)))) - (logand value (1- (ash 1 descriptor-low-bits))))) + (1- (ash 1 + (- sb!vm:n-word-bits + descriptor-low-bits)))) + (logand value (1- (ash 1 descriptor-low-bits))))) (defun make-fixnum-descriptor (num) (when (>= (integer-length num) - (1+ (- sb!vm:n-word-bits sb!vm:n-lowtag-bits))) + (1+ (- sb!vm:n-word-bits sb!vm:n-lowtag-bits))) (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) (make-descriptor (ash data (- sb!vm:n-widetag-bits descriptor-low-bits)) - (logior (logand (ash data (- descriptor-low-bits - sb!vm:n-widetag-bits)) - (1- (ash 1 descriptor-low-bits))) - type))) + (logior (logand (ash data (- descriptor-low-bits + sb!vm:n-widetag-bits)) + (1- (ash 1 descriptor-low-bits))) + type))) (defun make-character-descriptor (data) (make-other-immediate-descriptor data sb!vm:character-widetag)) (defun descriptor-beyond (des offset type) (let* ((low (logior (+ (logandc2 (descriptor-low des) sb!vm:lowtag-mask) - offset) - type)) - (high (+ (descriptor-high des) - (ash low (- descriptor-low-bits))))) + offset) + type)) + (high (+ (descriptor-high des) + (ash low (- descriptor-low-bits))))) (make-descriptor high (logand low (1- (ash 1 descriptor-low-bits)))))) ;;;; miscellaneous variables and other noise @@ -515,10 +515,10 @@ #!+sb-doc "Return the value which is displaced by INDEX words from ADDRESS." (let* ((gspace (descriptor-intuit-gspace address)) - (bytes (gspace-bytes gspace)) - (byte-index (ash (+ index (descriptor-word-offset address)) - sb!vm:word-shift)) - (value (bvref-word bytes byte-index))) + (bytes (gspace-bytes gspace)) + (byte-index (ash (+ index (descriptor-word-offset address)) + sb!vm:word-shift)) + (value (bvref-word bytes byte-index))) (make-random-descriptor value))) (declaim (ftype (function (descriptor) descriptor) read-memory)) @@ -533,12 +533,12 @@ 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 (sap-int-to-core address) - (cold-cons - (number-to-core (descriptor-word-offset marker)) - *nil-descriptor*))) - *current-reversed-cold-toplevels*) + (cold-intern :load-time-value-fixup) + (cold-cons (sap-int-to-core address) + (cold-cons + (number-to-core (descriptor-word-offset marker)) + *nil-descriptor*))) + *current-reversed-cold-toplevels*) (values)) (declaim (ftype (function (descriptor sb!vm:word descriptor)) write-wordindexed)) @@ -553,16 +553,16 @@ ;; perhaps write a comment somewhere explaining why it's not a good ;; idea?) -- WHN 19990817 (if (and (null (descriptor-gspace value)) - (not (null (descriptor-word-offset value)))) + (not (null (descriptor-word-offset value)))) (note-load-time-value-reference (+ (logandc2 (descriptor-bits address) - sb!vm:lowtag-mask) - (ash index sb!vm:word-shift)) - value) + sb!vm:lowtag-mask) + (ash index sb!vm:word-shift)) + value) (let* ((bytes (gspace-bytes (descriptor-intuit-gspace address))) - (byte-index (ash (+ index (descriptor-word-offset address)) - sb!vm:word-shift))) + (byte-index (ash (+ index (descriptor-word-offset address)) + sb!vm:word-shift))) (setf (bvref-word bytes byte-index) - (descriptor-bits value))))) + (descriptor-bits value))))) (declaim (ftype (function (descriptor descriptor)) write-memory)) (defun write-memory (address value) @@ -590,13 +590,13 @@ return an ``other-pointer'' descriptor to them. Initialize the header word with the resultant length and TYPE." (let* ((bytes (/ (* element-bits length) sb!vm:n-byte-bits)) - (des (allocate-cold-descriptor gspace - (+ bytes sb!vm:n-word-bytes) - sb!vm:other-pointer-lowtag))) + (des (allocate-cold-descriptor gspace + (+ bytes sb!vm:n-word-bytes) + sb!vm:other-pointer-lowtag))) (write-memory des - (make-other-immediate-descriptor (ash bytes - (- sb!vm:word-shift)) - type)) + (make-other-immediate-descriptor (ash bytes + (- sb!vm:word-shift)) + type)) des)) (defun allocate-vector-object (gspace element-bits length type) #!+sb-doc @@ -606,13 +606,13 @@ ;; FIXME: Here and in ALLOCATE-UNBOXED-OBJECT, BYTES is calculated using ;; #'/ instead of #'CEILING, which seems wrong. (let* ((bytes (/ (* element-bits length) sb!vm:n-byte-bits)) - (des (allocate-cold-descriptor gspace - (+ bytes (* 2 sb!vm:n-word-bytes)) - sb!vm:other-pointer-lowtag))) + (des (allocate-cold-descriptor gspace + (+ bytes (* 2 sb!vm:n-word-bytes)) + sb!vm:other-pointer-lowtag))) (write-memory des (make-other-immediate-descriptor 0 type)) (write-wordindexed des - sb!vm:vector-length-slot - (make-fixnum-descriptor length)) + sb!vm:vector-length-slot + (make-fixnum-descriptor length)) des)) ;;;; copying simple objects into the cold core @@ -624,44 +624,44 @@ core and return a descriptor to it." ;; (Remember that the system convention for storage of strings leaves an ;; extra null byte at the end to aid in call-out to C.) (let* ((length (length string)) - (des (allocate-vector-object gspace - sb!vm:n-byte-bits - (1+ length) - sb!vm:simple-base-string-widetag)) - (bytes (gspace-bytes gspace)) - (offset (+ (* sb!vm:vector-data-offset sb!vm:n-word-bytes) - (descriptor-byte-offset des)))) + (des (allocate-vector-object gspace + sb!vm:n-byte-bits + (1+ length) + sb!vm:simple-base-string-widetag)) + (bytes (gspace-bytes gspace)) + (offset (+ (* sb!vm:vector-data-offset sb!vm:n-word-bytes) + (descriptor-byte-offset des)))) (write-wordindexed des - sb!vm:vector-length-slot - (make-fixnum-descriptor length)) + sb!vm:vector-length-slot + (make-fixnum-descriptor length)) (dotimes (i length) (setf (bvref bytes (+ offset i)) - (sb!xc:char-code (aref string i)))) + (sb!xc:char-code (aref string i)))) (setf (bvref bytes (+ offset length)) - 0) ; null string-termination character for C + 0) ; null string-termination character for C des)) (defun bignum-to-core (n) #!+sb-doc "Copy a bignum to the cold core." (let* ((words (ceiling (1+ (integer-length n)) sb!vm:n-word-bits)) - (handle (allocate-unboxed-object *dynamic* - sb!vm:n-word-bits - words - sb!vm:bignum-widetag))) + (handle (allocate-unboxed-object *dynamic* + sb!vm:n-word-bits + words + sb!vm:bignum-widetag))) (declare (fixnum words)) (do ((index 1 (1+ index)) - (remainder n (ash remainder (- sb!vm:n-word-bits)))) - ((> index words) - (unless (zerop (integer-length remainder)) - ;; FIXME: Shouldn't this be a fatal error? - (warn "~W words of ~W were written, but ~W bits were left over." - words n remainder))) + (remainder n (ash remainder (- sb!vm:n-word-bits)))) + ((> index words) + (unless (zerop (integer-length remainder)) + ;; FIXME: Shouldn't this be a fatal error? + (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 - (make-descriptor (ash word (- descriptor-low-bits)) - (ldb (byte descriptor-low-bits 0) - word))))) + (write-wordindexed handle index + (make-descriptor (ash word (- descriptor-low-bits)) + (ldb (byte descriptor-low-bits 0) + word))))) handle)) (defun number-pair-to-core (first second type) @@ -674,26 +674,26 @@ core and return a descriptor to it." (defun write-double-float-bits (address index x) (let ((hi (double-float-high-bits x)) - (lo (double-float-low-bits x))) + (lo (double-float-low-bits x))) (ecase sb!vm::n-word-bits (32 (let ((high-bits (make-random-descriptor hi)) - (low-bits (make-random-descriptor lo))) - (ecase sb!c:*backend-byte-order* - (:little-endian - (write-wordindexed address index low-bits) - (write-wordindexed address (1+ index) high-bits)) - (:big-endian - (write-wordindexed address index high-bits) - (write-wordindexed address (1+ index) low-bits))))) + (low-bits (make-random-descriptor lo))) + (ecase sb!c:*backend-byte-order* + (:little-endian + (write-wordindexed address index low-bits) + (write-wordindexed address (1+ index) high-bits)) + (:big-endian + (write-wordindexed address index high-bits) + (write-wordindexed address (1+ index) low-bits))))) (64 (let ((bits (make-random-descriptor - (ecase sb!c:*backend-byte-order* - (:little-endian (logior lo (ash hi 32))) - ;; Just guessing. - #+nil (:big-endian (logior (logand hi #xffffffff) - (ash lo 32))))))) - (write-wordindexed address index bits)))) + (ecase sb!c:*backend-byte-order* + (:little-endian (logior lo (ash hi 32))) + ;; Just guessing. + #+nil (:big-endian (logior (logand hi #xffffffff) + (ash lo 32))))))) + (write-wordindexed address index bits)))) address)) (defun float-to-core (x) @@ -702,74 +702,74 @@ core and return a descriptor to it." ;; 64-bit platforms have immediate single-floats. #!+#.(cl:if (cl:= sb!vm:n-word-bits 64) '(and) '(or)) (make-random-descriptor (logior (ash (single-float-bits x) 32) - sb!vm::single-float-widetag)) + sb!vm::single-float-widetag)) #!-#.(cl:if (cl:= sb!vm:n-word-bits 64) '(and) '(or)) (let ((des (allocate-unboxed-object *dynamic* - sb!vm:n-word-bits - (1- sb!vm:single-float-size) - sb!vm:single-float-widetag))) + sb!vm:n-word-bits + (1- sb!vm:single-float-size) + sb!vm:single-float-widetag))) (write-wordindexed des - sb!vm:single-float-value-slot - (make-random-descriptor (single-float-bits x))) + sb!vm:single-float-value-slot + (make-random-descriptor (single-float-bits x))) des)) (double-float (let ((des (allocate-unboxed-object *dynamic* - sb!vm:n-word-bits - (1- sb!vm:double-float-size) - sb!vm:double-float-widetag))) + sb!vm:n-word-bits + (1- sb!vm:double-float-size) + sb!vm:double-float-widetag))) (write-double-float-bits des sb!vm:double-float-value-slot x))))) (defun complex-single-float-to-core (num) (declare (type (complex single-float) num)) (let ((des (allocate-unboxed-object *dynamic* sb!vm:n-word-bits - (1- sb!vm:complex-single-float-size) - sb!vm:complex-single-float-widetag))) + (1- sb!vm:complex-single-float-size) + sb!vm:complex-single-float-widetag))) (write-wordindexed des sb!vm:complex-single-float-real-slot - (make-random-descriptor (single-float-bits (realpart num)))) + (make-random-descriptor (single-float-bits (realpart num)))) (write-wordindexed des sb!vm:complex-single-float-imag-slot - (make-random-descriptor (single-float-bits (imagpart num)))) + (make-random-descriptor (single-float-bits (imagpart num)))) des)) (defun complex-double-float-to-core (num) (declare (type (complex double-float) num)) (let ((des (allocate-unboxed-object *dynamic* sb!vm:n-word-bits - (1- sb!vm:complex-double-float-size) - sb!vm:complex-double-float-widetag))) + (1- sb!vm:complex-double-float-size) + sb!vm:complex-double-float-widetag))) (write-double-float-bits des sb!vm:complex-double-float-real-slot - (realpart num)) + (realpart num)) (write-double-float-bits des sb!vm:complex-double-float-imag-slot - (imagpart num)))) + (imagpart num)))) ;;; Copy the given number to the core. (defun number-to-core (number) (typecase number - (integer (if (< (integer-length number) - (- (1+ sb!vm:n-word-bits) sb!vm:n-lowtag-bits)) - (make-fixnum-descriptor number) - (bignum-to-core number))) + (integer (if (< (integer-length number) + (- (1+ sb!vm:n-word-bits) sb!vm:n-lowtag-bits)) + (make-fixnum-descriptor number) + (bignum-to-core number))) (ratio (number-pair-to-core (number-to-core (numerator number)) - (number-to-core (denominator number)) - sb!vm:ratio-widetag)) + (number-to-core (denominator number)) + sb!vm:ratio-widetag)) ((complex single-float) (complex-single-float-to-core number)) ((complex double-float) (complex-double-float-to-core number)) #!+long-float ((complex long-float) (error "~S isn't a cold-loadable number at all!" number)) (complex (number-pair-to-core (number-to-core (realpart number)) - (number-to-core (imagpart number)) - sb!vm:complex-widetag)) + (number-to-core (imagpart number)) + sb!vm:complex-widetag)) (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-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))) + 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 sap-int)) + sb!vm:sap-pointer-slot + (make-random-descriptor sap-int)) des)) ;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR. @@ -783,11 +783,11 @@ core and return a descriptor to it." ;;; OBJECTS, and return its descriptor. (defun vector-in-core (&rest objects) (let* ((size (length objects)) - (result (allocate-vector-object *dynamic* sb!vm:n-word-bits size - sb!vm:simple-vector-widetag))) + (result (allocate-vector-object *dynamic* sb!vm:n-word-bits size + sb!vm:simple-vector-widetag))) (dotimes (index size) (write-wordindexed result (+ index sb!vm:vector-data-offset) - (pop objects))) + (pop objects))) result)) ;;;; symbol magic @@ -799,17 +799,17 @@ core and return a descriptor to it." (defun allocate-symbol (name) (declare (simple-string name)) (let ((symbol (allocate-unboxed-object (or *cold-symbol-allocation-gspace* - *dynamic*) - sb!vm:n-word-bits - (1- sb!vm:symbol-size) - sb!vm:symbol-header-widetag))) + *dynamic*) + sb!vm:n-word-bits + (1- sb!vm:symbol-size) + sb!vm:symbol-header-widetag))) (write-wordindexed symbol sb!vm:symbol-value-slot *unbound-marker*) (write-wordindexed symbol - sb!vm:symbol-hash-slot - (make-fixnum-descriptor 0)) + sb!vm:symbol-hash-slot + (make-fixnum-descriptor 0)) (write-wordindexed symbol sb!vm:symbol-plist-slot *nil-descriptor*) (write-wordindexed symbol sb!vm:symbol-name-slot - (base-string-to-core name *dynamic*)) + (base-string-to-core name *dynamic*)) (write-wordindexed symbol sb!vm:symbol-package-slot *nil-descriptor*) symbol)) @@ -820,8 +820,8 @@ core and return a descriptor to it." (declaim (ftype (function ((or descriptor symbol) descriptor)) cold-set)) (defun cold-set (symbol-or-symbol-des value) (let ((symbol-des (etypecase symbol-or-symbol-des - (descriptor symbol-or-symbol-des) - (symbol (cold-intern symbol-or-symbol-des))))) + (descriptor symbol-or-symbol-des) + (symbol (cold-intern symbol-or-symbol-des))))) (write-wordindexed symbol-des sb!vm:symbol-value-slot value))) ;;;; layouts and type system pre-initialization @@ -859,29 +859,29 @@ core and return a descriptor to it." ;;; in X. (defun listify-cold-inherits (x) (let ((len (descriptor-fixnum (read-wordindexed x - sb!vm:vector-length-slot)))) + sb!vm:vector-length-slot)))) (collect ((res)) (dotimes (index len) - (let* ((des (read-wordindexed x (+ sb!vm:vector-data-offset index))) - (found (gethash (descriptor-bits des) *cold-layout-names*))) - (if found - (res found) - (error "unknown descriptor at index ~S (bits = ~8,'0X)" - index - (descriptor-bits des))))) + (let* ((des (read-wordindexed x (+ sb!vm:vector-data-offset index))) + (found (gethash (descriptor-bits des) *cold-layout-names*))) + (if found + (res found) + (error "unknown descriptor at index ~S (bits = ~8,'0X)" + index + (descriptor-bits des))))) (res)))) (declaim (ftype (function (symbol descriptor descriptor descriptor descriptor) - descriptor) - make-cold-layout)) + descriptor) + make-cold-layout)) (defun make-cold-layout (name length inherits depthoid nuntagged) (let ((result (allocate-boxed-object *dynamic* - ;; KLUDGE: Why 1+? -- WHN 19990901 - (1+ target-layout-length) - sb!vm:instance-pointer-lowtag))) + ;; KLUDGE: Why 1+? -- WHN 19990901 + (1+ target-layout-length) + sb!vm:instance-pointer-lowtag))) (write-memory result - (make-other-immediate-descriptor - target-layout-length sb!vm:instance-header-widetag)) + (make-other-immediate-descriptor + target-layout-length sb!vm:instance-header-widetag)) ;; KLUDGE: The offsets into LAYOUT below should probably be pulled out ;; of the cross-compiler's tables at genesis time instead of inserted @@ -918,35 +918,35 @@ core and return a descriptor to it." ;; different algorithm than we use in ordinary operation. (dotimes (i sb!kernel:layout-clos-hash-length) (let (;; The expression here is pretty arbitrary, we just want - ;; to make sure that it's not something which is (1) - ;; evenly distributed and (2) not foreordained to arise in - ;; the target Lisp's (RANDOM-LAYOUT-CLOS-HASH) sequence - ;; and show up as the CLOS-HASH value of some other - ;; LAYOUT. - ;; - ;; FIXME: This expression here can generate a zero value, - ;; and the CMU CL code goes out of its way to generate - ;; strictly positive values (even though the field is - ;; declared as an INDEX). Check that it's really OK to - ;; have zero values in the CLOS-HASH slots. - (hash-value (mod (logxor (logand (random-layout-clos-hash) 15253) - (logandc2 (random-layout-clos-hash) 15253) - 1) - ;; (The MOD here is defensive programming - ;; to make sure we never write an - ;; out-of-range value even if some joker - ;; sets LAYOUT-CLOS-HASH-MAX to other - ;; than 2^n-1 at some time in the - ;; future.) - (1+ sb!kernel:layout-clos-hash-max)))) - (write-wordindexed result - (+ i sb!vm:instance-slots-offset 1) - (make-fixnum-descriptor hash-value)))) + ;; to make sure that it's not something which is (1) + ;; evenly distributed and (2) not foreordained to arise in + ;; the target Lisp's (RANDOM-LAYOUT-CLOS-HASH) sequence + ;; and show up as the CLOS-HASH value of some other + ;; LAYOUT. + ;; + ;; FIXME: This expression here can generate a zero value, + ;; and the CMU CL code goes out of its way to generate + ;; strictly positive values (even though the field is + ;; declared as an INDEX). Check that it's really OK to + ;; have zero values in the CLOS-HASH slots. + (hash-value (mod (logxor (logand (random-layout-clos-hash) 15253) + (logandc2 (random-layout-clos-hash) 15253) + 1) + ;; (The MOD here is defensive programming + ;; to make sure we never write an + ;; out-of-range value even if some joker + ;; sets LAYOUT-CLOS-HASH-MAX to other + ;; than 2^n-1 at some time in the + ;; future.) + (1+ sb!kernel:layout-clos-hash-max)))) + (write-wordindexed result + (+ i sb!vm:instance-slots-offset 1) + (make-fixnum-descriptor hash-value)))) ;; Set other slot values. (let ((base (+ sb!vm:instance-slots-offset - sb!kernel:layout-clos-hash-length - 1))) + sb!kernel:layout-clos-hash-length + 1))) ;; (Offset 0 is CLASS, "the class this is a layout for", which ;; is uninitialized at this point.) (write-wordindexed result (+ base 1) *nil-descriptor*) ; marked invalid @@ -958,12 +958,12 @@ core and return a descriptor to it." (write-wordindexed result (+ base 7) nuntagged)) (setf (gethash name *cold-layouts*) - (list result - name - (descriptor-fixnum length) - (listify-cold-inherits inherits) - (descriptor-fixnum depthoid) - (descriptor-fixnum nuntagged))) + (list result + name + (descriptor-fixnum length) + (listify-cold-inherits inherits) + (descriptor-fixnum depthoid) + (descriptor-fixnum nuntagged))) (setf (gethash (descriptor-bits result) *cold-layout-names*) name) result)) @@ -976,16 +976,16 @@ core and return a descriptor to it." ;; #() as INHERITS, (setq *layout-layout* *nil-descriptor*) (setq *layout-layout* - (make-cold-layout 'layout - (number-to-core target-layout-length) - (vector-in-core) - ;; FIXME: hard-coded LAYOUT-DEPTHOID of LAYOUT.. - (number-to-core 4) - ;; no raw slots in LAYOUT: - (number-to-core 0))) + (make-cold-layout 'layout + (number-to-core target-layout-length) + (vector-in-core) + ;; FIXME: hard-coded LAYOUT-DEPTHOID of LAYOUT.. + (number-to-core 4) + ;; no raw slots in LAYOUT: + (number-to-core 0))) (write-wordindexed *layout-layout* - sb!vm:instance-slots-offset - *layout-layout*) + sb!vm:instance-slots-offset + *layout-layout*) ;; Then we create the layouts that we'll need to make a correct INHERITS ;; vector for the layout of LAYOUT itself.. @@ -993,44 +993,44 @@ core and return a descriptor to it." ;; FIXME: The various LENGTH and DEPTHOID numbers should be taken from ;; the compiler's tables, not set by hand. (let* ((t-layout - (make-cold-layout 't - (number-to-core 0) - (vector-in-core) - (number-to-core 0) - (number-to-core 0))) - (i-layout - (make-cold-layout 'instance - (number-to-core 0) - (vector-in-core t-layout) - (number-to-core 1) - (number-to-core 0))) - (so-layout - (make-cold-layout 'structure-object - (number-to-core 1) - (vector-in-core t-layout i-layout) - (number-to-core 2) - (number-to-core 0))) - (bso-layout - (make-cold-layout 'structure!object - (number-to-core 1) - (vector-in-core t-layout i-layout so-layout) - (number-to-core 3) - (number-to-core 0))) - (layout-inherits (vector-in-core t-layout - i-layout - so-layout - bso-layout))) + (make-cold-layout 't + (number-to-core 0) + (vector-in-core) + (number-to-core 0) + (number-to-core 0))) + (i-layout + (make-cold-layout 'instance + (number-to-core 0) + (vector-in-core t-layout) + (number-to-core 1) + (number-to-core 0))) + (so-layout + (make-cold-layout 'structure-object + (number-to-core 1) + (vector-in-core t-layout i-layout) + (number-to-core 2) + (number-to-core 0))) + (bso-layout + (make-cold-layout 'structure!object + (number-to-core 1) + (vector-in-core t-layout i-layout so-layout) + (number-to-core 3) + (number-to-core 0))) + (layout-inherits (vector-in-core t-layout + i-layout + so-layout + bso-layout))) ;; ..and return to backpatch the layout of LAYOUT. (setf (fourth (gethash 'layout *cold-layouts*)) - (listify-cold-inherits layout-inherits)) + (listify-cold-inherits layout-inherits)) (write-wordindexed *layout-layout* - ;; FIXME: hardcoded offset into layout struct - (+ sb!vm:instance-slots-offset - layout-clos-hash-length - 1 - 2) - layout-inherits))) + ;; FIXME: hardcoded offset into layout struct + (+ sb!vm:instance-slots-offset + layout-clos-hash-length + 1 + 2) + layout-inherits))) ;;;; interning symbols in the cold image @@ -1089,7 +1089,7 @@ core and return a descriptor to it." ;; package in the xc host? something we can't think of ;; a valid reason to cold intern, anyway...) ))) - + ;;; like SYMBOL-PACKAGE, but safe for symbols which end up on the target ;;; ;;; Most host symbols we dump onto the target are created by SBCL @@ -1112,22 +1112,22 @@ core and return a descriptor to it." (multiple-value-bind (cl-symbol cl-status) (find-symbol (symbol-name symbol) *cl-package*) (if (and (eq symbol cl-symbol) - (eq cl-status :external)) - ;; special case, to work around possible xc host weirdness - ;; in COMMON-LISP package - *cl-package* - ;; ordinary case - (let ((result (symbol-package symbol))) - (aver (package-ok-for-target-symbol-p result)) - result)))) + (eq cl-status :external)) + ;; special case, to work around possible xc host weirdness + ;; in COMMON-LISP package + *cl-package* + ;; ordinary case + (let ((result (symbol-package symbol))) + (aver (package-ok-for-target-symbol-p result)) + result)))) ;;; Return a handle on an interned symbol. If necessary allocate the ;;; symbol and record which package the symbol was referenced in. When ;;; we allocate the symbol, make sure we record a reference to the ;;; symbol in the home package so that the package gets set. (defun cold-intern (symbol - &optional - (package (symbol-package-for-target-symbol symbol))) + &optional + (package (symbol-package-for-target-symbol symbol))) (aver (package-ok-for-target-symbol-p package)) @@ -1142,74 +1142,74 @@ core and return a descriptor to it." (setf symbol (intern (symbol-name symbol) *cl-package*)))) (let (;; Information about each cold-interned symbol is stored - ;; in COLD-INTERN-INFO. - ;; (CAR COLD-INTERN-INFO) = descriptor of symbol - ;; (CDR COLD-INTERN-INFO) = list of packages, other than symbol's - ;; own package, referring to symbol - ;; (*COLD-PACKAGE-SYMBOLS* and *COLD-SYMBOLS* store basically the - ;; same information, but with the mapping running the opposite way.) - (cold-intern-info (get symbol 'cold-intern-info))) + ;; in COLD-INTERN-INFO. + ;; (CAR COLD-INTERN-INFO) = descriptor of symbol + ;; (CDR COLD-INTERN-INFO) = list of packages, other than symbol's + ;; own package, referring to symbol + ;; (*COLD-PACKAGE-SYMBOLS* and *COLD-SYMBOLS* store basically the + ;; same information, but with the mapping running the opposite way.) + (cold-intern-info (get symbol 'cold-intern-info))) (unless cold-intern-info (cond ((eq (symbol-package-for-target-symbol symbol) package) - (let ((handle (allocate-symbol (symbol-name symbol)))) - (setf (gethash (descriptor-bits handle) *cold-symbols*) symbol) - (when (eq package *keyword-package*) - (cold-set handle handle)) - (setq cold-intern-info - (setf (get symbol 'cold-intern-info) (cons handle nil))))) - (t - (cold-intern symbol) - (setq cold-intern-info (get symbol 'cold-intern-info))))) + (let ((handle (allocate-symbol (symbol-name symbol)))) + (setf (gethash (descriptor-bits handle) *cold-symbols*) symbol) + (when (eq package *keyword-package*) + (cold-set handle handle)) + (setq cold-intern-info + (setf (get symbol 'cold-intern-info) (cons handle nil))))) + (t + (cold-intern symbol) + (setq cold-intern-info (get symbol 'cold-intern-info))))) (unless (or (null package) - (member package (cdr cold-intern-info))) + (member package (cdr cold-intern-info))) (push package (cdr cold-intern-info)) (let* ((old-cps-entry (assoc package *cold-package-symbols*)) - (cps-entry (or old-cps-entry - (car (push (list package) - *cold-package-symbols*))))) - (unless old-cps-entry - (/show "created *COLD-PACKAGE-SYMBOLS* entry for" package symbol)) - (push symbol (rest cps-entry)))) + (cps-entry (or old-cps-entry + (car (push (list package) + *cold-package-symbols*))))) + (unless old-cps-entry + (/show "created *COLD-PACKAGE-SYMBOLS* entry for" package symbol)) + (push symbol (rest cps-entry)))) (car cold-intern-info))) ;;; Construct and return a value for use as *NIL-DESCRIPTOR*. (defun make-nil-descriptor () (let* ((des (allocate-unboxed-object - *static* - sb!vm:n-word-bits - sb!vm:symbol-size - 0)) - (result (make-descriptor (descriptor-high des) - (+ (descriptor-low des) - (* 2 sb!vm:n-word-bytes) - (- sb!vm:list-pointer-lowtag - sb!vm:other-pointer-lowtag))))) + *static* + sb!vm:n-word-bits + sb!vm:symbol-size + 0)) + (result (make-descriptor (descriptor-high des) + (+ (descriptor-low des) + (* 2 sb!vm:n-word-bytes) + (- sb!vm:list-pointer-lowtag + sb!vm:other-pointer-lowtag))))) (write-wordindexed des - 1 - (make-other-immediate-descriptor - 0 - sb!vm:symbol-header-widetag)) + 1 + (make-other-immediate-descriptor + 0 + sb!vm:symbol-header-widetag)) (write-wordindexed des - (+ 1 sb!vm:symbol-value-slot) - result) + (+ 1 sb!vm:symbol-value-slot) + result) (write-wordindexed des - (+ 2 sb!vm:symbol-value-slot) - result) + (+ 2 sb!vm:symbol-value-slot) + result) (write-wordindexed des - (+ 1 sb!vm:symbol-plist-slot) - result) + (+ 1 sb!vm:symbol-plist-slot) + result) (write-wordindexed des - (+ 1 sb!vm:symbol-name-slot) - ;; This is *DYNAMIC*, and DES is *STATIC*, - ;; because that's the way CMU CL did it; I'm - ;; not sure whether there's an underlying - ;; reason. -- WHN 1990826 - (base-string-to-core "NIL" *dynamic*)) + (+ 1 sb!vm:symbol-name-slot) + ;; This is *DYNAMIC*, and DES is *STATIC*, + ;; because that's the way CMU CL did it; I'm + ;; not sure whether there's an underlying + ;; reason. -- WHN 1990826 + (base-string-to-core "NIL" *dynamic*)) (write-wordindexed des - (+ 1 sb!vm:symbol-package-slot) - result) + (+ 1 sb!vm:symbol-package-slot) + result) (setf (get nil 'cold-intern-info) - (cons result nil)) + (cons result nil)) (cold-intern nil) result)) @@ -1222,16 +1222,16 @@ core and return a descriptor to it." ;; Intern the others. (dolist (symbol sb!vm:*static-symbols*) (let* ((des (cold-intern symbol)) - (offset-wanted (sb!vm:static-symbol-offset symbol)) - (offset-found (- (descriptor-low des) - (descriptor-low *nil-descriptor*)))) - (unless (= offset-wanted offset-found) - ;; FIXME: should be fatal - (warn "Offset from ~S to ~S is ~W, not ~W" - symbol - nil - offset-found - offset-wanted)))) + (offset-wanted (sb!vm:static-symbol-offset symbol)) + (offset-found (- (descriptor-low des) + (descriptor-low *nil-descriptor*)))) + (unless (= offset-wanted offset-found) + ;; FIXME: should be fatal + (warn "Offset from ~S to ~S is ~W, not ~W" + symbol + nil + offset-found + offset-wanted)))) ;; Establish the value of T. (let ((t-symbol (cold-intern t))) (cold-set t-symbol t-symbol)))) @@ -1241,10 +1241,10 @@ core and return a descriptor to it." (defun cold-list-all-layouts () (let ((result *nil-descriptor*)) (maphash (lambda (key stuff) - (cold-push (cold-cons (cold-intern key) - (first stuff)) - result)) - *cold-layouts*) + (cold-push (cold-cons (cold-intern key) + (first stuff)) + result)) + *cold-layouts*) result)) ;;; Establish initial values for magic symbols. @@ -1267,8 +1267,8 @@ core and return a descriptor to it." ;; *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))))) + `(cold-set ',symbol + (cold-fdefinition-object (cold-intern ',symbol))))) (frob sub-gc) (frob internal-error) (frob sb!kernel::control-stack-exhausted-error) @@ -1289,67 +1289,67 @@ core and return a descriptor to it." (let ((initial-symbols *nil-descriptor*)) (dolist (cold-package-symbols-entry *cold-package-symbols*) (let* ((cold-package (car cold-package-symbols-entry)) - (symbols (cdr cold-package-symbols-entry)) - (shadows (package-shadowing-symbols cold-package)) - (documentation (base-string-to-core (documentation cold-package t))) - (internal *nil-descriptor*) - (external *nil-descriptor*) - (imported-internal *nil-descriptor*) - (imported-external *nil-descriptor*) - (shadowing *nil-descriptor*)) - (declare (type package cold-package)) ; i.e. not a target descriptor - (/show "dumping" cold-package symbols) - - ;; FIXME: Add assertions here to make sure that inappropriate stuff - ;; isn't being dumped: - ;; * the CL-USER package - ;; * the SB-COLD package - ;; * any internal symbols in the CL package - ;; * basically any package other than CL, KEYWORD, or the packages - ;; in package-data-list.lisp-expr - ;; and that the structure of the KEYWORD package (e.g. whether - ;; any symbols are internal to it) matches what we want in the - ;; target SBCL. - - ;; FIXME: It seems possible that by looking at the contents of - ;; packages in the target SBCL we could find which symbols in - ;; package-data-lisp.lisp-expr are now obsolete. (If I - ;; understand correctly, only symbols which actually have - ;; definitions or which are otherwise referred to actually end - ;; up in the target packages.) - - (dolist (symbol symbols) - (let ((handle (car (get symbol 'cold-intern-info))) - (imported-p (not (eq (symbol-package-for-target-symbol symbol) - cold-package)))) - (multiple-value-bind (found where) - (find-symbol (symbol-name symbol) cold-package) - (unless (and where (eq found symbol)) - (error "The symbol ~S is not available in ~S." - symbol - cold-package)) - (when (memq symbol shadows) - (cold-push handle shadowing)) - (case where - (:internal (if imported-p - (cold-push handle imported-internal) - (cold-push handle internal))) - (:external (if imported-p - (cold-push handle imported-external) - (cold-push handle external))))))) - (let ((r *nil-descriptor*)) - (cold-push documentation r) - (cold-push shadowing r) - (cold-push imported-external r) - (cold-push imported-internal r) - (cold-push external r) - (cold-push internal r) - (cold-push (make-make-package-args cold-package) r) - ;; FIXME: It would be more space-efficient to use vectors - ;; instead of lists here, and space-efficiency here would be - ;; nice, since it would reduce the peak memory usage in - ;; genesis and cold init. - (cold-push r initial-symbols)))) + (symbols (cdr cold-package-symbols-entry)) + (shadows (package-shadowing-symbols cold-package)) + (documentation (base-string-to-core (documentation cold-package t))) + (internal *nil-descriptor*) + (external *nil-descriptor*) + (imported-internal *nil-descriptor*) + (imported-external *nil-descriptor*) + (shadowing *nil-descriptor*)) + (declare (type package cold-package)) ; i.e. not a target descriptor + (/show "dumping" cold-package symbols) + + ;; FIXME: Add assertions here to make sure that inappropriate stuff + ;; isn't being dumped: + ;; * the CL-USER package + ;; * the SB-COLD package + ;; * any internal symbols in the CL package + ;; * basically any package other than CL, KEYWORD, or the packages + ;; in package-data-list.lisp-expr + ;; and that the structure of the KEYWORD package (e.g. whether + ;; any symbols are internal to it) matches what we want in the + ;; target SBCL. + + ;; FIXME: It seems possible that by looking at the contents of + ;; packages in the target SBCL we could find which symbols in + ;; package-data-lisp.lisp-expr are now obsolete. (If I + ;; understand correctly, only symbols which actually have + ;; definitions or which are otherwise referred to actually end + ;; up in the target packages.) + + (dolist (symbol symbols) + (let ((handle (car (get symbol 'cold-intern-info))) + (imported-p (not (eq (symbol-package-for-target-symbol symbol) + cold-package)))) + (multiple-value-bind (found where) + (find-symbol (symbol-name symbol) cold-package) + (unless (and where (eq found symbol)) + (error "The symbol ~S is not available in ~S." + symbol + cold-package)) + (when (memq symbol shadows) + (cold-push handle shadowing)) + (case where + (:internal (if imported-p + (cold-push handle imported-internal) + (cold-push handle internal))) + (:external (if imported-p + (cold-push handle imported-external) + (cold-push handle external))))))) + (let ((r *nil-descriptor*)) + (cold-push documentation r) + (cold-push shadowing r) + (cold-push imported-external r) + (cold-push imported-internal r) + (cold-push external r) + (cold-push internal r) + (cold-push (make-make-package-args cold-package) r) + ;; FIXME: It would be more space-efficient to use vectors + ;; instead of lists here, and space-efficiency here would be + ;; nice, since it would reduce the peak memory usage in + ;; genesis and cold init. + (cold-push r initial-symbols)))) (cold-set '*!initial-symbols* initial-symbols)) (cold-set '*!initial-fdefn-objects* (list-all-fdefn-objects)) @@ -1367,40 +1367,40 @@ core and return a descriptor to it." ;;; to make a package that is similar to PKG. (defun make-make-package-args (pkg) (let* ((use *nil-descriptor*) - (cold-nicknames *nil-descriptor*) - (res *nil-descriptor*)) + (cold-nicknames *nil-descriptor*) + (res *nil-descriptor*)) (dolist (u (package-use-list pkg)) (when (assoc u *cold-package-symbols*) - (cold-push (base-string-to-core (package-name u)) use))) + (cold-push (base-string-to-core (package-name u)) use))) (let* ((pkg-name (package-name pkg)) - ;; Make the package nickname lists for the standard packages - ;; be the minimum specified by ANSI, regardless of what value - ;; the cross-compilation host happens to use. - (warm-nicknames (cond ((string= pkg-name "COMMON-LISP") - '("CL")) - ((string= pkg-name "COMMON-LISP-USER") - '("CL-USER")) - ((string= pkg-name "KEYWORD") - '()) - ;; For packages other than the - ;; standard packages, the nickname - ;; list was specified by our package - ;; setup code, not by properties of - ;; what cross-compilation host we - ;; happened to use, and we can just - ;; propagate it into the target. - (t - (package-nicknames pkg))))) + ;; Make the package nickname lists for the standard packages + ;; be the minimum specified by ANSI, regardless of what value + ;; the cross-compilation host happens to use. + (warm-nicknames (cond ((string= pkg-name "COMMON-LISP") + '("CL")) + ((string= pkg-name "COMMON-LISP-USER") + '("CL-USER")) + ((string= pkg-name "KEYWORD") + '()) + ;; For packages other than the + ;; standard packages, the nickname + ;; list was specified by our package + ;; setup code, not by properties of + ;; what cross-compilation host we + ;; happened to use, and we can just + ;; propagate it into the target. + (t + (package-nicknames pkg))))) (dolist (warm-nickname warm-nicknames) - (cold-push (base-string-to-core warm-nickname) cold-nicknames))) + (cold-push (base-string-to-core warm-nickname) cold-nicknames))) (cold-push (number-to-core (truncate (package-internal-symbol-count pkg) - 0.8)) - res) + 0.8)) + res) (cold-push (cold-intern :internal-symbols) res) (cold-push (number-to-core (truncate (package-external-symbol-count pkg) - 0.8)) - res) + 0.8)) + res) (cold-push (cold-intern :external-symbols) res) (cold-push cold-nicknames res) @@ -1425,7 +1425,7 @@ core and return a descriptor to it." (defvar *cold-fdefn-gspace* nil) ;;; Given a cold representation of a symbol, return a warm -;;; representation. +;;; representation. (defun warm-symbol (des) ;; Note that COLD-INTERN is responsible for keeping the ;; *COLD-SYMBOLS* table up to date, so if DES happens to refer to an @@ -1438,7 +1438,7 @@ core and return a descriptor to it." (unless found-p (error "no warm symbol")) symbol)) - + ;;; like CL:CAR, CL:CDR, and CL:NULL but for cold values (defun cold-car (des) (aver (= (descriptor-lowtag des) sb!vm:list-pointer-lowtag)) @@ -1449,25 +1449,25 @@ core and return a descriptor to it." (defun cold-null (des) (= (descriptor-bits des) (descriptor-bits *nil-descriptor*))) - + ;;; Given a cold representation of a function name, return a warm ;;; representation. (declaim (ftype (function (descriptor) (or symbol list)) warm-fun-name)) (defun warm-fun-name (des) (let ((result - (ecase (descriptor-lowtag des) - (#.sb!vm:list-pointer-lowtag - (aver (not (cold-null des))) ; function named NIL? please no.. - ;; Do cold (DESTRUCTURING-BIND (COLD-CAR COLD-CADR) DES ..). - (let* ((car-des (cold-car des)) - (cdr-des (cold-cdr des)) - (cadr-des (cold-car cdr-des)) - (cddr-des (cold-cdr cdr-des))) - (aver (cold-null cddr-des)) - (list (warm-symbol car-des) - (warm-symbol cadr-des)))) - (#.sb!vm:other-pointer-lowtag - (warm-symbol des))))) + (ecase (descriptor-lowtag des) + (#.sb!vm:list-pointer-lowtag + (aver (not (cold-null des))) ; function named NIL? please no.. + ;; Do cold (DESTRUCTURING-BIND (COLD-CAR COLD-CADR) DES ..). + (let* ((car-des (cold-car des)) + (cdr-des (cold-cdr des)) + (cadr-des (cold-car cdr-des)) + (cddr-des (cold-cdr cdr-des))) + (aver (cold-null cddr-des)) + (list (warm-symbol car-des) + (warm-symbol cadr-des)))) + (#.sb!vm:other-pointer-lowtag + (warm-symbol des))))) (legal-fun-name-or-type-error result) result)) @@ -1476,69 +1476,69 @@ core and return a descriptor to it." (/show0 "/cold-fdefinition-object") (let ((warm-name (warm-fun-name cold-name))) (or (gethash warm-name *cold-fdefn-objects*) - (let ((fdefn (allocate-boxed-object (or *cold-fdefn-gspace* *dynamic*) - (1- sb!vm:fdefn-size) - sb!vm:other-pointer-lowtag))) - - (setf (gethash warm-name *cold-fdefn-objects*) fdefn) - (write-memory fdefn (make-other-immediate-descriptor - (1- sb!vm:fdefn-size) sb!vm:fdefn-widetag)) - (write-wordindexed fdefn sb!vm:fdefn-name-slot cold-name) - (unless leave-fn-raw - (write-wordindexed fdefn sb!vm:fdefn-fun-slot - *nil-descriptor*) - (write-wordindexed fdefn - sb!vm:fdefn-raw-addr-slot - (make-random-descriptor - (cold-foreign-symbol-address "undefined_tramp")))) - fdefn)))) + (let ((fdefn (allocate-boxed-object (or *cold-fdefn-gspace* *dynamic*) + (1- sb!vm:fdefn-size) + sb!vm:other-pointer-lowtag))) + + (setf (gethash warm-name *cold-fdefn-objects*) fdefn) + (write-memory fdefn (make-other-immediate-descriptor + (1- sb!vm:fdefn-size) sb!vm:fdefn-widetag)) + (write-wordindexed fdefn sb!vm:fdefn-name-slot cold-name) + (unless leave-fn-raw + (write-wordindexed fdefn sb!vm:fdefn-fun-slot + *nil-descriptor*) + (write-wordindexed fdefn + sb!vm:fdefn-raw-addr-slot + (make-random-descriptor + (cold-foreign-symbol-address "undefined_tramp")))) + fdefn)))) ;;; Handle the at-cold-init-time, fset-for-static-linkage operation ;;; requested by FOP-FSET. (defun static-fset (cold-name defn) (declare (type descriptor cold-name)) (let ((fdefn (cold-fdefinition-object cold-name t)) - (type (logand (descriptor-low (read-memory defn)) sb!vm:widetag-mask))) + (type (logand (descriptor-low (read-memory defn)) sb!vm:widetag-mask))) (write-wordindexed fdefn sb!vm:fdefn-fun-slot defn) (write-wordindexed fdefn - sb!vm:fdefn-raw-addr-slot - (ecase type - (#.sb!vm:simple-fun-header-widetag - (/show0 "static-fset (simple-fun)") - #!+sparc - defn - #!-sparc - (make-random-descriptor - (+ (logandc2 (descriptor-bits defn) - sb!vm:lowtag-mask) - (ash sb!vm:simple-fun-code-offset - sb!vm:word-shift)))) - (#.sb!vm:closure-header-widetag - (/show0 "/static-fset (closure)") - (make-random-descriptor - (cold-foreign-symbol-address "closure_tramp"))))) + sb!vm:fdefn-raw-addr-slot + (ecase type + (#.sb!vm:simple-fun-header-widetag + (/show0 "static-fset (simple-fun)") + #!+sparc + defn + #!-sparc + (make-random-descriptor + (+ (logandc2 (descriptor-bits defn) + sb!vm:lowtag-mask) + (ash sb!vm:simple-fun-code-offset + sb!vm:word-shift)))) + (#.sb!vm:closure-header-widetag + (/show0 "/static-fset (closure)") + (make-random-descriptor + (cold-foreign-symbol-address "closure_tramp"))))) fdefn)) (defun initialize-static-fns () (let ((*cold-fdefn-gspace* *static*)) (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-fun-offset sym))) - (unless (= offset desired) - ;; FIXME: should be fatal - (error "Offset from FDEFN ~S to ~S is ~W, not ~W." - sym nil offset desired)))))) + (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-fun-offset sym))) + (unless (= offset desired) + ;; FIXME: should be fatal + (error "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)) - *cold-fdefn-objects*) + (declare (ignore key)) + (cold-push value result)) + *cold-fdefn-objects*) result)) ;;;; fixups and related stuff @@ -1553,49 +1553,49 @@ core and return a descriptor to it." (/show "load-cold-foreign-symbol-table" filename) (with-open-file (file filename) (loop for line = (read-line file nil nil) - while line do - ;; UNIX symbol tables might have tabs in them, and tabs are - ;; not in Common Lisp STANDARD-CHAR, so there seems to be no - ;; nice portable way to deal with them within Lisp, alas. - ;; Fortunately, it's easy to use UNIX command line tools like - ;; sed to remove the problem, so it's not too painful for us - ;; to push responsibility for converting tabs to spaces out to - ;; the caller. - ;; - ;; Other non-STANDARD-CHARs are problematic for the same reason. - ;; Make sure that there aren't any.. - (let ((ch (find-if (lambda (char) - (not (typep char 'standard-char))) - line))) - (when ch - (error "non-STANDARD-CHAR ~S found in foreign symbol table:~%~S" - ch - line))) - (setf line (string-trim '(#\space) line)) - (let ((p1 (position #\space line :from-end nil)) - (p2 (position #\space line :from-end t))) - (if (not (and p1 p2 (< p1 p2))) - ;; KLUDGE: It's too messy to try to understand all - ;; possible output from nm, so we just punt the lines we - ;; don't recognize. We realize that there's some chance - ;; that might get us in trouble someday, so we warn - ;; about it. - (warn "ignoring unrecognized line ~S in ~A" line filename) - (multiple-value-bind (value name) - (if (string= "0x" line :end2 2) - (values (parse-integer line :start 2 :end p1 :radix 16) - (subseq line (1+ p2))) - (values (parse-integer line :end p1 :radix 16) - (subseq line (1+ p2)))) - (multiple-value-bind (old-value found) - (gethash name *cold-foreign-symbol-table*) - (when (and found - (not (= old-value value))) - (warn "redefining ~S from #X~X to #X~X" - name old-value value))) - (/show "adding to *cold-foreign-symbol-table*:" name value) - (setf (gethash name *cold-foreign-symbol-table*) value)))))) - (values)) ;; PROGN + while line do + ;; UNIX symbol tables might have tabs in them, and tabs are + ;; not in Common Lisp STANDARD-CHAR, so there seems to be no + ;; nice portable way to deal with them within Lisp, alas. + ;; Fortunately, it's easy to use UNIX command line tools like + ;; sed to remove the problem, so it's not too painful for us + ;; to push responsibility for converting tabs to spaces out to + ;; the caller. + ;; + ;; Other non-STANDARD-CHARs are problematic for the same reason. + ;; Make sure that there aren't any.. + (let ((ch (find-if (lambda (char) + (not (typep char 'standard-char))) + line))) + (when ch + (error "non-STANDARD-CHAR ~S found in foreign symbol table:~%~S" + ch + line))) + (setf line (string-trim '(#\space) line)) + (let ((p1 (position #\space line :from-end nil)) + (p2 (position #\space line :from-end t))) + (if (not (and p1 p2 (< p1 p2))) + ;; KLUDGE: It's too messy to try to understand all + ;; possible output from nm, so we just punt the lines we + ;; don't recognize. We realize that there's some chance + ;; that might get us in trouble someday, so we warn + ;; about it. + (warn "ignoring unrecognized line ~S in ~A" line filename) + (multiple-value-bind (value name) + (if (string= "0x" line :end2 2) + (values (parse-integer line :start 2 :end p1 :radix 16) + (subseq line (1+ p2))) + (values (parse-integer line :end p1 :radix 16) + (subseq line (1+ p2)))) + (multiple-value-bind (old-value found) + (gethash name *cold-foreign-symbol-table*) + (when (and found + (not (= old-value value))) + (warn "redefining ~S from #X~X to #X~X" + name old-value value))) + (/show "adding to *cold-foreign-symbol-table*:" name value) + (setf (gethash name *cold-foreign-symbol-table*) value)))))) + (values)) ;; PROGN (defun cold-foreign-symbol-address (name) (or (find-foreign-symbol-in-table name *cold-foreign-symbol-table*) @@ -1614,15 +1614,15 @@ core and return a descriptor to it." (defun record-cold-assembler-routine (name address) (/xhow "in RECORD-COLD-ASSEMBLER-ROUTINE" name address) (push (cons name address) - *cold-assembler-routines*)) + *cold-assembler-routines*)) (defun record-cold-assembler-fixup (routine - code-object - offset - &optional - (kind :both)) + code-object + offset + &optional + (kind :both)) (push (list routine code-object offset kind) - *cold-assembler-fixups*)) + *cold-assembler-fixups*)) (defun lookup-assembler-reference (symbol) (let ((value (cdr (assoc symbol *cold-assembler-routines*)))) @@ -1641,7 +1641,7 @@ core and return a descriptor to it." (defun note-load-time-code-fixup (code-object offset value kind) ;; If CODE-OBJECT might be moved (when (= (gspace-identifier (descriptor-intuit-gspace code-object)) - dynamic-core-space-id) + dynamic-core-space-id) ;; FIXME: pushed thing should be a structure, not just a list (push (list code-object offset value kind) *load-time-code-fixups*)) (values)) @@ -1650,21 +1650,21 @@ core and return a descriptor to it." (defun output-load-time-code-fixups () (dolist (fixups *load-time-code-fixups*) (let ((code-object (first fixups)) - (offset (second fixups)) - (value (third fixups)) - (kind (fourth fixups))) + (offset (second fixups)) + (value (third fixups)) + (kind (fourth fixups))) (cold-push (cold-cons - (cold-intern :load-time-code-fixup) - (cold-cons - code-object - (cold-cons - (number-to-core offset) - (cold-cons - (number-to-core value) - (cold-cons - (cold-intern kind) - *nil-descriptor*))))) - *current-reversed-cold-toplevels*)))) + (cold-intern :load-time-code-fixup) + (cold-cons + code-object + (cold-cons + (number-to-core offset) + (cold-cons + (number-to-core value) + (cold-cons + (cold-intern kind) + *nil-descriptor*))))) + *current-reversed-cold-toplevels*)))) ;;; Given a pointer to a code object and an offset relative to the ;;; tail of the code object's header, return an offset relative to the @@ -1677,108 +1677,108 @@ core and return a descriptor to it." (declaim (ftype (function (descriptor sb!vm:word)) calc-offset)) (defun calc-offset (code-object offset-from-tail-of-header) (let* ((header (read-memory code-object)) - (header-n-words (ash (descriptor-bits header) - (- sb!vm:n-widetag-bits))) - (header-n-bytes (ash header-n-words sb!vm:word-shift)) - (result (+ offset-from-tail-of-header header-n-bytes))) + (header-n-words (ash (descriptor-bits header) + (- sb!vm:n-widetag-bits))) + (header-n-bytes (ash header-n-words sb!vm:word-shift)) + (result (+ offset-from-tail-of-header header-n-bytes))) result)) (declaim (ftype (function (descriptor sb!vm:word sb!vm:word keyword)) - do-cold-fixup)) + do-cold-fixup)) (defun do-cold-fixup (code-object after-header value kind) (let* ((offset-within-code-object (calc-offset code-object after-header)) - (gspace-bytes (descriptor-bytes code-object)) - (gspace-byte-offset (+ (descriptor-byte-offset code-object) - offset-within-code-object)) - (gspace-byte-address (gspace-byte-address - (descriptor-gspace code-object)))) + (gspace-bytes (descriptor-bytes code-object)) + (gspace-byte-offset (+ (descriptor-byte-offset code-object) + offset-within-code-object)) + (gspace-byte-address (gspace-byte-address + (descriptor-gspace code-object)))) (ecase +backend-fasl-file-implementation+ ;; See CMU CL source for other formerly-supported architectures ;; (and note that you have to rewrite them to use BVREF-X ;; instead of SAP-REF). (:alpha - (ecase kind + (ecase kind (:jmp-hint (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)) - (value (if (logbitp 47 value) (+ value (ash 1 48)) value))) - (setf (bvref-8 gspace-bytes gspace-byte-offset) + (:bits-63-48 + (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)) + (value (if (logbitp 31 value) (+ value (ash 1 32)) value)) + (value (if (logbitp 47 value) (+ value (ash 1 48)) value))) + (setf (bvref-8 gspace-bytes gspace-byte-offset) (ldb (byte 8 48) value) (bvref-8 gspace-bytes (1+ gspace-byte-offset)) (ldb (byte 8 56) value)))) - (:bits-47-32 - (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)) - (value (if (logbitp 31 value) (+ value (ash 1 32)) value))) - (setf (bvref-8 gspace-bytes gspace-byte-offset) + (:bits-47-32 + (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)) + (value (if (logbitp 31 value) (+ value (ash 1 32)) value))) + (setf (bvref-8 gspace-bytes gspace-byte-offset) (ldb (byte 8 32) value) (bvref-8 gspace-bytes (1+ gspace-byte-offset)) (ldb (byte 8 40) value)))) - (:ldah - (let ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))) - (setf (bvref-8 gspace-bytes gspace-byte-offset) + (:ldah + (let ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))) + (setf (bvref-8 gspace-bytes gspace-byte-offset) (ldb (byte 8 16) value) (bvref-8 gspace-bytes (1+ gspace-byte-offset)) (ldb (byte 8 24) value)))) - (:lda - (setf (bvref-8 gspace-bytes gspace-byte-offset) + (:lda + (setf (bvref-8 gspace-bytes gspace-byte-offset) (ldb (byte 8 0) value) (bvref-8 gspace-bytes (1+ gspace-byte-offset)) (ldb (byte 8 8) value))))) (:hppa (ecase kind - (:load - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (ash (ldb (byte 11 0) value) 1) - (logand (bvref-32 gspace-bytes gspace-byte-offset) - #xffffc000)))) - (:load-short - (let ((low-bits (ldb (byte 11 0) value))) - (assert (<= 0 low-bits (1- (ash 1 4)))) - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (ash low-bits 17) - (logand (bvref-32 gspace-bytes gspace-byte-offset) - #xffe0ffff))))) - (:hi - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (ash (ldb (byte 5 13) value) 16) - (ash (ldb (byte 2 18) value) 14) - (ash (ldb (byte 2 11) value) 12) - (ash (ldb (byte 11 20) value) 1) - (ldb (byte 1 31) value) - (logand (bvref-32 gspace-bytes gspace-byte-offset) - #xffe00000)))) - (:branch - (let ((bits (ldb (byte 9 2) value))) - (assert (zerop (ldb (byte 2 0) value))) - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (ash bits 3) - (logand (bvref-32 gspace-bytes gspace-byte-offset) - #xffe0e002))))))) + (:load + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (ash (ldb (byte 11 0) value) 1) + (logand (bvref-32 gspace-bytes gspace-byte-offset) + #xffffc000)))) + (:load-short + (let ((low-bits (ldb (byte 11 0) value))) + (assert (<= 0 low-bits (1- (ash 1 4)))) + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (ash low-bits 17) + (logand (bvref-32 gspace-bytes gspace-byte-offset) + #xffe0ffff))))) + (:hi + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (ash (ldb (byte 5 13) value) 16) + (ash (ldb (byte 2 18) value) 14) + (ash (ldb (byte 2 11) value) 12) + (ash (ldb (byte 11 20) value) 1) + (ldb (byte 1 31) value) + (logand (bvref-32 gspace-bytes gspace-byte-offset) + #xffe00000)))) + (:branch + (let ((bits (ldb (byte 9 2) value))) + (assert (zerop (ldb (byte 2 0) value))) + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (ash bits 3) + (logand (bvref-32 gspace-bytes gspace-byte-offset) + #xffe0e002))))))) (:mips (ecase kind - (:jump - (assert (zerop (ash value -28))) - (setf (ldb (byte 26 0) - (bvref-32 gspace-bytes gspace-byte-offset)) - (ash value -2))) - (:lui - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (mask-field (byte 16 16) - (bvref-32 gspace-bytes gspace-byte-offset)) - (+ (ash value -16) - (if (logbitp 15 value) 1 0))))) - (:addi - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (logior (mask-field (byte 16 16) - (bvref-32 gspace-bytes gspace-byte-offset)) - (ldb (byte 16 0) value)))))) + (:jump + (assert (zerop (ash value -28))) + (setf (ldb (byte 26 0) + (bvref-32 gspace-bytes gspace-byte-offset)) + (ash value -2))) + (:lui + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (mask-field (byte 16 16) + (bvref-32 gspace-bytes gspace-byte-offset)) + (+ (ash value -16) + (if (logbitp 15 value) 1 0))))) + (:addi + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (logior (mask-field (byte 16 16) + (bvref-32 gspace-bytes gspace-byte-offset)) + (ldb (byte 16 0) value)))))) (:ppc (ecase kind (:ba (setf (bvref-32 gspace-bytes gspace-byte-offset) - (dpb (ash value -2) (byte 24 2) + (dpb (ash value -2) (byte 24 2) (bvref-32 gspace-bytes gspace-byte-offset)))) (:ha (let* ((h (ldb (byte 16 16) value)) @@ -1787,71 +1787,71 @@ core and return a descriptor to it." (if (logbitp 15 l) (ldb (byte 16 0) (1+ h)) h)))) (:l (setf (bvref-16 gspace-bytes (+ gspace-byte-offset 2)) - (ldb (byte 16 0) value))))) + (ldb (byte 16 0) value))))) (:sparc (ecase kind - (:call - (error "can't deal with call fixups yet")) - (:sethi - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (dpb (ldb (byte 22 10) value) - (byte 22 0) - (bvref-32 gspace-bytes gspace-byte-offset)))) - (:add - (setf (bvref-32 gspace-bytes gspace-byte-offset) - (dpb (ldb (byte 10 0) value) - (byte 10 0) - (bvref-32 gspace-bytes gspace-byte-offset)))))) + (:call + (error "can't deal with call fixups yet")) + (:sethi + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (dpb (ldb (byte 22 10) value) + (byte 22 0) + (bvref-32 gspace-bytes gspace-byte-offset)))) + (:add + (setf (bvref-32 gspace-bytes gspace-byte-offset) + (dpb (ldb (byte 10 0) value) + (byte 10 0) + (bvref-32 gspace-bytes gspace-byte-offset)))))) ((:x86 :x86-64) (let* ((un-fixed-up (bvref-word gspace-bytes - gspace-byte-offset)) - (code-object-start-addr (logandc2 (descriptor-bits code-object) - sb!vm:lowtag-mask))) + gspace-byte-offset)) + (code-object-start-addr (logandc2 (descriptor-bits code-object) + sb!vm:lowtag-mask))) (assert (= code-object-start-addr - (+ gspace-byte-address - (descriptor-byte-offset code-object)))) - (ecase kind - (:absolute - (let ((fixed-up (+ value un-fixed-up))) - (setf (bvref-32 gspace-bytes gspace-byte-offset) - fixed-up) - ;; comment from CMU CL sources: - ;; - ;; Note absolute fixups that point within the object. - ;; KLUDGE: There seems to be an implicit assumption in - ;; the old CMU CL code here, that if it doesn't point - ;; before the object, it must point within the object - ;; (not beyond it). It would be good to add an - ;; explanation of why that's true, or an assertion that - ;; it's really true, or both. - (unless (< fixed-up code-object-start-addr) - (note-load-time-code-fixup code-object - after-header - value - kind)))) - (:relative ; (used for arguments to X86 relative CALL instruction) - (let ((fixed-up (- (+ value un-fixed-up) - gspace-byte-address - gspace-byte-offset - 4))) ; "length of CALL argument" - (setf (bvref-32 gspace-bytes gspace-byte-offset) - fixed-up) - ;; Note relative fixups that point outside the code - ;; object, which is to say all relative fixups, since - ;; relative addressing within a code object never needs - ;; a fixup. - (note-load-time-code-fixup code-object - after-header - value - kind)))))))) + (+ gspace-byte-address + (descriptor-byte-offset code-object)))) + (ecase kind + (:absolute + (let ((fixed-up (+ value un-fixed-up))) + (setf (bvref-32 gspace-bytes gspace-byte-offset) + fixed-up) + ;; comment from CMU CL sources: + ;; + ;; Note absolute fixups that point within the object. + ;; KLUDGE: There seems to be an implicit assumption in + ;; the old CMU CL code here, that if it doesn't point + ;; before the object, it must point within the object + ;; (not beyond it). It would be good to add an + ;; explanation of why that's true, or an assertion that + ;; it's really true, or both. + (unless (< fixed-up code-object-start-addr) + (note-load-time-code-fixup code-object + after-header + value + kind)))) + (:relative ; (used for arguments to X86 relative CALL instruction) + (let ((fixed-up (- (+ value un-fixed-up) + gspace-byte-address + gspace-byte-offset + 4))) ; "length of CALL argument" + (setf (bvref-32 gspace-bytes gspace-byte-offset) + fixed-up) + ;; Note relative fixups that point outside the code + ;; object, which is to say all relative fixups, since + ;; relative addressing within a code object never needs + ;; a fixup. + (note-load-time-code-fixup code-object + after-header + value + kind)))))))) (values)) (defun resolve-assembler-fixups () (dolist (fixup *cold-assembler-fixups*) (let* ((routine (car fixup)) - (value (lookup-assembler-reference routine))) + (value (lookup-assembler-reference routine))) (when value - (do-cold-fixup (second fixup) (third fixup) value (fourth fixup)))))) + (do-cold-fixup (second fixup) (third fixup) value (fourth fixup)))))) ;;; *COLD-FOREIGN-SYMBOL-TABLE* becomes *!INITIAL-FOREIGN-SYMBOLS* in ;;; the core. When the core is loaded, !LOADER-COLD-INIT uses this to @@ -1860,16 +1860,16 @@ core and return a descriptor to it." (defun foreign-symbols-to-core () (let ((result *nil-descriptor*)) (maphash (lambda (symbol value) - (cold-push (cold-cons (base-string-to-core symbol) - (number-to-core value)) - result)) - *cold-foreign-symbol-table*) + (cold-push (cold-cons (base-string-to-core symbol) + (number-to-core value)) + result)) + *cold-foreign-symbol-table*) (cold-set (cold-intern 'sb!kernel:*!initial-foreign-symbols*) result)) (let ((result *nil-descriptor*)) (dolist (rtn *cold-assembler-routines*) (cold-push (cold-cons (cold-intern (car rtn)) - (number-to-core (cdr rtn))) - result)) + (number-to-core (cdr rtn))) + result)) (cold-set (cold-intern '*!initial-assembler-routines*) result))) @@ -1885,7 +1885,7 @@ core and return a descriptor to it." (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 @@ -1895,19 +1895,19 @@ core and return a descriptor to it." (aver (member pushp '(nil t))) (aver (member stackp '(nil t))) (let ((code (get name 'fop-code)) - (fname (symbolicate "COLD-" name))) + (fname (symbolicate "COLD-" name))) (unless code (error "~S is not a defined FOP." name)) `(progn (defun ,fname () - ,@(if stackp + ,@(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) + (small-name) + &rest forms) (aver (member pushp '(nil t))) (aver (member stackp '(nil t))) `(progn @@ -1928,10 +1928,10 @@ core and return a descriptor to it." #!+sb-doc "Load the file named by FILENAME into the cold load image being built." (let* ((*normal-fop-funs* *fop-funs*) - (*fop-funs* *cold-fop-funs*) - (*cold-load-filename* (etypecase filename - (string filename) - (pathname (namestring filename))))) + (*fop-funs* *cold-fop-funs*) + (*cold-load-filename* (etypecase filename + (string filename) + (pathname (namestring filename))))) (with-open-file (s filename :element-type '(unsigned-byte 8)) (load-as-fasl s nil nil)))) @@ -1955,36 +1955,36 @@ core and return a descriptor to it." (define-cold-fop (fop-maybe-cold-load :stackp nil)) (clone-cold-fop (fop-struct) - (fop-small-struct) + (fop-small-struct) (let* ((size (clone-arg)) - (result (allocate-boxed-object *dynamic* - (1+ size) - sb!vm:instance-pointer-lowtag)) - (layout (pop-stack)) - (nuntagged - (descriptor-fixnum - (read-wordindexed layout (+ sb!vm:instance-slots-offset 16)))) - (ntagged (- size nuntagged))) + (result (allocate-boxed-object *dynamic* + (1+ size) + sb!vm:instance-pointer-lowtag)) + (layout (pop-stack)) + (nuntagged + (descriptor-fixnum + (read-wordindexed layout (+ sb!vm:instance-slots-offset 16)))) + (ntagged (- size nuntagged))) (write-memory result (make-other-immediate-descriptor - size sb!vm:instance-header-widetag)) + size sb!vm:instance-header-widetag)) (write-wordindexed result sb!vm:instance-slots-offset layout) (do ((index 1 (1+ index))) - ((eql index size)) + ((eql index size)) (declare (fixnum index)) (write-wordindexed result - (+ index sb!vm:instance-slots-offset) - (if (>= index ntagged) - (descriptor-word-sized-integer (pop-stack)) - (pop-stack)))) + (+ index sb!vm:instance-slots-offset) + (if (>= index ntagged) + (descriptor-word-sized-integer (pop-stack)) + (pop-stack)))) result)) (define-cold-fop (fop-layout) (let* ((nuntagged-des (pop-stack)) - (length-des (pop-stack)) - (depthoid-des (pop-stack)) - (cold-inherits (pop-stack)) - (name (pop-stack)) - (old (gethash name *cold-layouts*))) + (length-des (pop-stack)) + (depthoid-des (pop-stack)) + (cold-inherits (pop-stack)) + (name (pop-stack)) + (old (gethash name *cold-layouts*))) (declare (type descriptor length-des depthoid-des cold-inherits)) (declare (type symbol name)) ;; If a layout of this name has been defined already @@ -1992,54 +1992,54 @@ core and return a descriptor to it." ;; Enforce consistency between the previous definition and the ;; current definition, then return the previous definition. (destructuring-bind - ;; FIXME: This would be more maintainable if we used - ;; DEFSTRUCT (:TYPE LIST) to define COLD-LAYOUT. -- WHN 19990825 - (old-layout-descriptor - old-name - old-length - old-inherits-list - old-depthoid - old-nuntagged) - old - (declare (type descriptor old-layout-descriptor)) - (declare (type index old-length old-nuntagged)) - (declare (type fixnum old-depthoid)) - (declare (type list old-inherits-list)) - (aver (eq name old-name)) - (let ((length (descriptor-fixnum length-des)) - (inherits-list (listify-cold-inherits cold-inherits)) - (depthoid (descriptor-fixnum depthoid-des)) - (nuntagged (descriptor-fixnum nuntagged-des))) - (unless (= length old-length) - (error "cold loading a reference to class ~S when the compile~%~ + ;; FIXME: This would be more maintainable if we used + ;; DEFSTRUCT (:TYPE LIST) to define COLD-LAYOUT. -- WHN 19990825 + (old-layout-descriptor + old-name + old-length + old-inherits-list + old-depthoid + old-nuntagged) + old + (declare (type descriptor old-layout-descriptor)) + (declare (type index old-length old-nuntagged)) + (declare (type fixnum old-depthoid)) + (declare (type list old-inherits-list)) + (aver (eq name old-name)) + (let ((length (descriptor-fixnum length-des)) + (inherits-list (listify-cold-inherits cold-inherits)) + (depthoid (descriptor-fixnum depthoid-des)) + (nuntagged (descriptor-fixnum nuntagged-des))) + (unless (= length old-length) + (error "cold loading a reference to class ~S when the compile~%~ time length was ~S and current length is ~S" - name - length - old-length)) - (unless (equal inherits-list old-inherits-list) - (error "cold loading a reference to class ~S when the compile~%~ + name + length + old-length)) + (unless (equal inherits-list old-inherits-list) + (error "cold loading a reference to class ~S when the compile~%~ time inherits were ~S~%~ and current inherits are ~S" - name - inherits-list - old-inherits-list)) - (unless (= depthoid old-depthoid) - (error "cold loading a reference to class ~S when the compile~%~ + name + inherits-list + old-inherits-list)) + (unless (= depthoid old-depthoid) + (error "cold loading a reference to class ~S when the compile~%~ time inheritance depthoid was ~S and current inheritance~%~ depthoid is ~S" - name - depthoid - old-depthoid)) - (unless (= nuntagged old-nuntagged) - (error "cold loading a reference to class ~S when the compile~%~ + name + depthoid + old-depthoid)) + (unless (= nuntagged old-nuntagged) + (error "cold loading a reference to class ~S when the compile~%~ time number of untagged slots was ~S and is currently ~S" - name - nuntagged - old-nuntagged))) - old-layout-descriptor) + name + nuntagged + old-nuntagged))) + old-layout-descriptor) ;; Make a new definition from scratch. (make-cold-layout name length-des cold-inherits depthoid-des - nuntagged-des)))) + nuntagged-des)))) ;;;; cold fops for loading symbols @@ -2051,28 +2051,28 @@ core and return a descriptor to it." (cold-intern (intern string package)))) (macrolet ((frob (name pname-len package-len) - `(define-cold-fop (,name) - (let ((index (read-arg ,package-len))) - (push-fop-table - (cold-load-symbol (read-arg ,pname-len) - (svref *current-fop-table* index))))))) + `(define-cold-fop (,name) + (let ((index (read-arg ,package-len))) + (push-fop-table + (cold-load-symbol (read-arg ,pname-len) + (svref *current-fop-table* index))))))) (frob fop-symbol-in-package-save #.sb!vm:n-word-bytes #.sb!vm:n-word-bytes) (frob fop-small-symbol-in-package-save 1 #.sb!vm:n-word-bytes) (frob fop-symbol-in-byte-package-save #.sb!vm:n-word-bytes 1) (frob fop-small-symbol-in-byte-package-save 1 1)) (clone-cold-fop (fop-lisp-symbol-save) - (fop-lisp-small-symbol-save) + (fop-lisp-small-symbol-save) (push-fop-table (cold-load-symbol (clone-arg) *cl-package*))) (clone-cold-fop (fop-keyword-symbol-save) - (fop-keyword-small-symbol-save) + (fop-keyword-small-symbol-save) (push-fop-table (cold-load-symbol (clone-arg) *keyword-package*))) (clone-cold-fop (fop-uninterned-symbol-save) - (fop-uninterned-small-symbol-save) + (fop-uninterned-small-symbol-save) (let* ((size (clone-arg)) - (name (make-string size))) + (name (make-string size))) (read-string-as-bytes *fasl-input-stream* name) (let ((symbol-des (allocate-symbol name))) (push-fop-table symbol-des)))) @@ -2083,8 +2083,8 @@ core and return a descriptor to it." ;;; cdr of the list is set to LAST. (defmacro cold-stack-list (length last) `(do* ((index ,length (1- index)) - (result ,last (cold-cons (pop-stack) result))) - ((= index 0) result) + (result ,last (cold-cons (pop-stack) result))) + ((= index 0) result) (declare (fixnum index)))) (define-cold-fop (fop-list) @@ -2127,81 +2127,81 @@ core and return a descriptor to it." ;;;; cold fops for loading vectors (clone-cold-fop (fop-base-string) - (fop-small-base-string) + (fop-small-base-string) (let* ((len (clone-arg)) - (string (make-string len))) + (string (make-string len))) (read-string-as-bytes *fasl-input-stream* string) (base-string-to-core string))) #!+sb-unicode (clone-cold-fop (fop-character-string) - (fop-small-character-string) + (fop-small-character-string) (bug "CHARACTER-STRING dumped by cross-compiler.")) (clone-cold-fop (fop-vector) - (fop-small-vector) + (fop-small-vector) (let* ((size (clone-arg)) - (result (allocate-vector-object *dynamic* - sb!vm:n-word-bits - size - sb!vm:simple-vector-widetag))) + (result (allocate-vector-object *dynamic* + sb!vm:n-word-bits + size + sb!vm:simple-vector-widetag))) (do ((index (1- size) (1- index))) - ((minusp index)) + ((minusp index)) (declare (fixnum index)) (write-wordindexed result - (+ index sb!vm:vector-data-offset) - (pop-stack))) + (+ index sb!vm:vector-data-offset) + (pop-stack))) result)) (define-cold-fop (fop-int-vector) (let* ((len (read-word-arg)) - (sizebits (read-byte-arg)) - (type (case sizebits - (0 sb!vm:simple-array-nil-widetag) - (1 sb!vm:simple-bit-vector-widetag) - (2 sb!vm:simple-array-unsigned-byte-2-widetag) - (4 sb!vm:simple-array-unsigned-byte-4-widetag) - (7 (prog1 sb!vm:simple-array-unsigned-byte-7-widetag - (setf sizebits 8))) - (8 sb!vm:simple-array-unsigned-byte-8-widetag) - (15 (prog1 sb!vm:simple-array-unsigned-byte-15-widetag - (setf sizebits 16))) - (16 sb!vm:simple-array-unsigned-byte-16-widetag) - (31 (prog1 sb!vm:simple-array-unsigned-byte-31-widetag - (setf sizebits 32))) - (32 sb!vm:simple-array-unsigned-byte-32-widetag) + (sizebits (read-byte-arg)) + (type (case sizebits + (0 sb!vm:simple-array-nil-widetag) + (1 sb!vm:simple-bit-vector-widetag) + (2 sb!vm:simple-array-unsigned-byte-2-widetag) + (4 sb!vm:simple-array-unsigned-byte-4-widetag) + (7 (prog1 sb!vm:simple-array-unsigned-byte-7-widetag + (setf sizebits 8))) + (8 sb!vm:simple-array-unsigned-byte-8-widetag) + (15 (prog1 sb!vm:simple-array-unsigned-byte-15-widetag + (setf sizebits 16))) + (16 sb!vm:simple-array-unsigned-byte-16-widetag) + (31 (prog1 sb!vm:simple-array-unsigned-byte-31-widetag + (setf sizebits 32))) + (32 sb!vm:simple-array-unsigned-byte-32-widetag) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (63 (prog1 sb!vm:simple-array-unsigned-byte-63-widetag (setf sizebits 64))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (64 sb!vm:simple-array-unsigned-byte-64-widetag) - (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))) - (end (+ start - (ceiling (* len sizebits) - sb!vm:n-byte-bits)))) + (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))) + (end (+ start + (ceiling (* len sizebits) + sb!vm:n-byte-bits)))) (read-bigvec-as-sequence-or-die (descriptor-bytes result) - *fasl-input-stream* - :start start - :end end) + *fasl-input-stream* + :start start + :end end) result)) (define-cold-fop (fop-single-float-vector) (let* ((len (read-word-arg)) - (result (allocate-vector-object - *dynamic* - sb!vm:n-word-bits - len - sb!vm:simple-array-single-float-widetag)) - (start (+ (descriptor-byte-offset result) - (ash sb!vm:vector-data-offset sb!vm:word-shift))) - (end (+ start (* len 4)))) + (result (allocate-vector-object + *dynamic* + sb!vm:n-word-bits + len + sb!vm:simple-array-single-float-widetag)) + (start (+ (descriptor-byte-offset result) + (ash sb!vm:vector-data-offset sb!vm:word-shift))) + (end (+ start (* len 4)))) (read-bigvec-as-sequence-or-die (descriptor-bytes result) - *fasl-input-stream* - :start start - :end end) + *fasl-input-stream* + :start start + :end end) result)) (not-cold-fop fop-double-float-vector) @@ -2212,36 +2212,36 @@ core and return a descriptor to it." (define-cold-fop (fop-array) (let* ((rank (read-word-arg)) - (data-vector (pop-stack)) - (result (allocate-boxed-object *dynamic* - (+ sb!vm:array-dimensions-offset rank) - sb!vm:other-pointer-lowtag))) + (data-vector (pop-stack)) + (result (allocate-boxed-object *dynamic* + (+ sb!vm:array-dimensions-offset rank) + sb!vm:other-pointer-lowtag))) (write-memory result - (make-other-immediate-descriptor rank - sb!vm:simple-array-widetag)) + (make-other-immediate-descriptor rank + sb!vm:simple-array-widetag)) (write-wordindexed result sb!vm:array-fill-pointer-slot *nil-descriptor*) (write-wordindexed result sb!vm:array-data-slot data-vector) (write-wordindexed result sb!vm:array-displacement-slot *nil-descriptor*) (write-wordindexed result sb!vm:array-displaced-p-slot *nil-descriptor*) (let ((total-elements 1)) (dotimes (axis rank) - (let ((dim (pop-stack))) - (unless (or (= (descriptor-lowtag dim) sb!vm:even-fixnum-lowtag) - (= (descriptor-lowtag dim) sb!vm:odd-fixnum-lowtag)) - (error "non-fixnum dimension? (~S)" dim)) - (setf total-elements - (* total-elements - (logior (ash (descriptor-high dim) - (- descriptor-low-bits - (1- sb!vm:n-lowtag-bits))) - (ash (descriptor-low dim) - (- 1 sb!vm:n-lowtag-bits))))) - (write-wordindexed result - (+ sb!vm:array-dimensions-offset axis) - dim))) + (let ((dim (pop-stack))) + (unless (or (= (descriptor-lowtag dim) sb!vm:even-fixnum-lowtag) + (= (descriptor-lowtag dim) sb!vm:odd-fixnum-lowtag)) + (error "non-fixnum dimension? (~S)" dim)) + (setf total-elements + (* total-elements + (logior (ash (descriptor-high dim) + (- descriptor-low-bits + (1- sb!vm:n-lowtag-bits))) + (ash (descriptor-low dim) + (- 1 sb!vm:n-lowtag-bits))))) + (write-wordindexed result + (+ sb!vm:array-dimensions-offset axis) + dim))) (write-wordindexed result - sb!vm:array-elements-slot - (make-fixnum-descriptor total-elements))) + sb!vm:array-elements-slot + (make-fixnum-descriptor total-elements))) result)) @@ -2256,7 +2256,7 @@ core and return a descriptor to it." ;; fop result. (with-fop-stack t (let ((number (pop-stack))) - (number-to-core number))))) + (number-to-core number))))) (define-cold-number-fop fop-single-float) (define-cold-number-fop fop-double-float) @@ -2287,54 +2287,54 @@ core and return a descriptor to it." (error "You can't FOP-FUNCALL arbitrary stuff in cold load.")) (let ((counter *load-time-value-counter*)) (cold-push (cold-cons - (cold-intern :load-time-value) - (cold-cons - (pop-stack) - (cold-cons - (number-to-core counter) - *nil-descriptor*))) - *current-reversed-cold-toplevels*) + (cold-intern :load-time-value) + (cold-cons + (pop-stack) + (cold-cons + (number-to-core counter) + *nil-descriptor*))) + *current-reversed-cold-toplevels*) (setf *load-time-value-counter* (1+ counter)) (make-descriptor 0 0 nil counter))) (defun finalize-load-time-value-noise () (cold-set (cold-intern '*!load-time-values*) - (allocate-vector-object *dynamic* - sb!vm:n-word-bits - *load-time-value-counter* - sb!vm:simple-vector-widetag))) + (allocate-vector-object *dynamic* + sb!vm:n-word-bits + *load-time-value-counter* + sb!vm:simple-vector-widetag))) (define-cold-fop (fop-funcall-for-effect :pushp nil) (if (= (read-byte-arg) 0) (cold-push (pop-stack) - *current-reversed-cold-toplevels*) + *current-reversed-cold-toplevels*) (error "You can't FOP-FUNCALL arbitrary stuff in cold load."))) ;;;; cold fops for fixing up circularities (define-cold-fop (fop-rplaca :pushp nil) (let ((obj (svref *current-fop-table* (read-word-arg))) - (idx (read-word-arg))) + (idx (read-word-arg))) (write-memory (cold-nthcdr idx obj) (pop-stack)))) (define-cold-fop (fop-rplacd :pushp nil) (let ((obj (svref *current-fop-table* (read-word-arg))) - (idx (read-word-arg))) + (idx (read-word-arg))) (write-wordindexed (cold-nthcdr idx obj) 1 (pop-stack)))) (define-cold-fop (fop-svset :pushp nil) (let ((obj (svref *current-fop-table* (read-word-arg))) - (idx (read-word-arg))) + (idx (read-word-arg))) (write-wordindexed obj - (+ idx - (ecase (descriptor-lowtag obj) - (#.sb!vm:instance-pointer-lowtag 1) - (#.sb!vm:other-pointer-lowtag 2))) - (pop-stack)))) + (+ idx + (ecase (descriptor-lowtag obj) + (#.sb!vm:instance-pointer-lowtag 1) + (#.sb!vm:other-pointer-lowtag 2))) + (pop-stack)))) (define-cold-fop (fop-structset :pushp nil) (let ((obj (svref *current-fop-table* (read-word-arg))) - (idx (read-word-arg))) + (idx (read-word-arg))) (write-wordindexed obj (1+ idx) (pop-stack)))) ;;; In the original CMUCL code, this actually explicitly declared PUSHP @@ -2359,11 +2359,11 @@ core and return a descriptor to it." (define-cold-fop (fop-fset :pushp nil) (let* ((fn (pop-stack)) - (cold-name (pop-stack)) - (warm-name (warm-fun-name cold-name))) + (cold-name (pop-stack)) + (warm-name (warm-fun-name cold-name))) (if (gethash warm-name *cold-fset-warm-names*) - (error "duplicate COLD-FSET for ~S" warm-name) - (setf (gethash warm-name *cold-fset-warm-names*) t)) + (error "duplicate COLD-FSET for ~S" warm-name) + (setf (gethash warm-name *cold-fset-warm-names*) t)) (static-fset cold-name fn))) (define-cold-fop (fop-fdefinition) @@ -2384,53 +2384,53 @@ core and return a descriptor to it." (defmacro define-cold-code-fop (name nconst code-size) `(define-cold-fop (,name) (let* ((nconst ,nconst) - (code-size ,code-size) - (raw-header-n-words (+ sb!vm:code-trace-table-offset-slot nconst)) - (header-n-words - ;; Note: we round the number of constants up to ensure - ;; that the code vector will be properly aligned. - (round-up raw-header-n-words 2)) - (des (allocate-cold-descriptor *dynamic* - (+ (ash header-n-words - sb!vm:word-shift) - code-size) - sb!vm:other-pointer-lowtag))) + (code-size ,code-size) + (raw-header-n-words (+ sb!vm:code-trace-table-offset-slot nconst)) + (header-n-words + ;; Note: we round the number of constants up to ensure + ;; that the code vector will be properly aligned. + (round-up raw-header-n-words 2)) + (des (allocate-cold-descriptor *dynamic* + (+ (ash header-n-words + sb!vm:word-shift) + code-size) + sb!vm:other-pointer-lowtag))) (write-memory des - (make-other-immediate-descriptor - header-n-words sb!vm:code-header-widetag)) + (make-other-immediate-descriptor + header-n-words sb!vm:code-header-widetag)) (write-wordindexed des - sb!vm:code-code-size-slot - (make-fixnum-descriptor - (ash (+ code-size (1- (ash 1 sb!vm:word-shift))) - (- sb!vm:word-shift)))) + sb!vm:code-code-size-slot + (make-fixnum-descriptor + (ash (+ code-size (1- (ash 1 sb!vm:word-shift))) + (- sb!vm:word-shift)))) (write-wordindexed des sb!vm:code-entry-points-slot *nil-descriptor*) (write-wordindexed des sb!vm:code-debug-info-slot (pop-stack)) (when (oddp raw-header-n-words) - (write-wordindexed des - raw-header-n-words - (make-random-descriptor 0))) + (write-wordindexed des + raw-header-n-words + (make-random-descriptor 0))) (do ((index (1- raw-header-n-words) (1- index))) - ((< index sb!vm:code-trace-table-offset-slot)) - (write-wordindexed des index (pop-stack))) + ((< index sb!vm:code-trace-table-offset-slot)) + (write-wordindexed des index (pop-stack))) (let* ((start (+ (descriptor-byte-offset des) - (ash header-n-words sb!vm:word-shift))) - (end (+ start code-size))) - (read-bigvec-as-sequence-or-die (descriptor-bytes des) - *fasl-input-stream* - :start start - :end end) - #!+sb-show - (when *show-pre-fixup-code-p* - (format *trace-output* - "~&/raw code from code-fop ~W ~W:~%" - nconst - code-size) - (do ((i start (+ i sb!vm:n-word-bytes))) - ((>= i end)) - (format *trace-output* - "/#X~8,'0x: #X~8,'0x~%" - (+ i (gspace-byte-address (descriptor-gspace des))) - (bvref-32 (descriptor-bytes des) i))))) + (ash header-n-words sb!vm:word-shift))) + (end (+ start code-size))) + (read-bigvec-as-sequence-or-die (descriptor-bytes des) + *fasl-input-stream* + :start start + :end end) + #!+sb-show + (when *show-pre-fixup-code-p* + (format *trace-output* + "~&/raw code from code-fop ~W ~W:~%" + nconst + code-size) + (do ((i start (+ i sb!vm:n-word-bytes))) + ((>= i end)) + (format *trace-output* + "/#X~8,'0x: #X~8,'0x~%" + (+ i (gspace-byte-address (descriptor-gspace des))) + (bvref-32 (descriptor-bytes des) i))))) des))) (define-cold-code-fop fop-code (read-word-arg) (read-word-arg)) @@ -2438,66 +2438,66 @@ core and return a descriptor to it." (define-cold-code-fop fop-small-code (read-byte-arg) (read-halfword-arg)) (clone-cold-fop (fop-alter-code :pushp nil) - (fop-byte-alter-code) + (fop-byte-alter-code) (let ((slot (clone-arg)) - (value (pop-stack)) - (code (pop-stack))) + (value (pop-stack)) + (code (pop-stack))) (write-wordindexed code slot value))) (define-cold-fop (fop-fun-entry) (let* ((type (pop-stack)) - (arglist (pop-stack)) - (name (pop-stack)) - (code-object (pop-stack)) - (offset (calc-offset code-object (read-word-arg))) - (fn (descriptor-beyond code-object - offset - sb!vm:fun-pointer-lowtag)) - (next (read-wordindexed code-object sb!vm:code-entry-points-slot))) + (arglist (pop-stack)) + (name (pop-stack)) + (code-object (pop-stack)) + (offset (calc-offset code-object (read-word-arg))) + (fn (descriptor-beyond code-object + offset + sb!vm:fun-pointer-lowtag)) + (next (read-wordindexed code-object sb!vm:code-entry-points-slot))) (unless (zerop (logand offset sb!vm:lowtag-mask)) (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 - (ash offset (- sb!vm:word-shift)) - sb!vm:simple-fun-header-widetag)) + (make-other-immediate-descriptor + (ash offset (- sb!vm:word-shift)) + sb!vm:simple-fun-header-widetag)) (write-wordindexed fn - sb!vm:simple-fun-self-slot - ;; KLUDGE: Wiring decisions like this in at - ;; this level ("if it's an x86") instead of a - ;; higher level of abstraction ("if it has such - ;; and such relocation peculiarities (which - ;; happen to be confined to the x86)") is bad. - ;; It would be nice if the code were instead - ;; conditional on some more descriptive - ;; feature, :STICKY-CODE or - ;; :LOAD-GC-INTERACTION or something. - ;; - ;; FIXME: The X86 definition of the function - ;; self slot breaks everything object.tex says - ;; about it. (As far as I can tell, the X86 - ;; definition makes it a pointer to the actual - ;; 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. - #!-(or x86 x86-64) - ;; a pointer back to the function object, as - ;; described in CMU CL - ;; src/docs/internals/object.tex - fn - #!+(or x86 x86-64) - ;; KLUDGE: a pointer to the actual code of the - ;; object, as described nowhere that I can find - ;; -- WHN 19990907 - (make-random-descriptor - (+ (descriptor-bits fn) - (- (ash sb!vm:simple-fun-code-offset - sb!vm:word-shift) - ;; FIXME: We should mask out the type - ;; bits, not assume we know what they - ;; are and subtract them out this way. - sb!vm:fun-pointer-lowtag)))) + sb!vm:simple-fun-self-slot + ;; KLUDGE: Wiring decisions like this in at + ;; this level ("if it's an x86") instead of a + ;; higher level of abstraction ("if it has such + ;; and such relocation peculiarities (which + ;; happen to be confined to the x86)") is bad. + ;; It would be nice if the code were instead + ;; conditional on some more descriptive + ;; feature, :STICKY-CODE or + ;; :LOAD-GC-INTERACTION or something. + ;; + ;; FIXME: The X86 definition of the function + ;; self slot breaks everything object.tex says + ;; about it. (As far as I can tell, the X86 + ;; definition makes it a pointer to the actual + ;; 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. + #!-(or x86 x86-64) + ;; a pointer back to the function object, as + ;; described in CMU CL + ;; src/docs/internals/object.tex + fn + #!+(or x86 x86-64) + ;; KLUDGE: a pointer to the actual code of the + ;; object, as described nowhere that I can find + ;; -- WHN 19990907 + (make-random-descriptor + (+ (descriptor-bits fn) + (- (ash sb!vm:simple-fun-code-offset + sb!vm:word-shift) + ;; FIXME: We should mask out the type + ;; bits, not assume we know what they + ;; are and subtract them out this way. + sb!vm:fun-pointer-lowtag)))) (write-wordindexed fn sb!vm:simple-fun-next-slot next) (write-wordindexed fn sb!vm:simple-fun-name-slot name) (write-wordindexed fn sb!vm:simple-fun-arglist-slot arglist) @@ -2506,21 +2506,21 @@ core and return a descriptor to it." (define-cold-fop (fop-foreign-fixup) (let* ((kind (pop-stack)) - (code-object (pop-stack)) - (len (read-byte-arg)) - (sym (make-string len))) + (code-object (pop-stack)) + (len (read-byte-arg)) + (sym (make-string len))) (read-string-as-bytes *fasl-input-stream* sym) (let ((offset (read-word-arg)) - (value (cold-foreign-symbol-address sym))) + (value (cold-foreign-symbol-address sym))) (do-cold-fixup code-object offset value kind)) code-object)) #!+linkage-table (define-cold-fop (fop-foreign-dataref-fixup) (let* ((kind (pop-stack)) - (code-object (pop-stack)) - (len (read-byte-arg)) - (sym (make-string len))) + (code-object (pop-stack)) + (len (read-byte-arg)) + (sym (make-string len))) (read-string-as-bytes *fasl-input-stream* sym) (maphash (lambda (k v) (format *error-output* "~&~S = #X~8X~%" k v)) @@ -2529,39 +2529,39 @@ core and return a descriptor to it." (define-cold-fop (fop-assembler-code) (let* ((length (read-word-arg)) - (header-n-words - ;; Note: we round the number of constants up to ensure that - ;; the code vector will be properly aligned. - (round-up sb!vm:code-constants-offset 2)) - (des (allocate-cold-descriptor *read-only* - (+ (ash header-n-words - sb!vm:word-shift) - length) - sb!vm:other-pointer-lowtag))) + (header-n-words + ;; Note: we round the number of constants up to ensure that + ;; the code vector will be properly aligned. + (round-up sb!vm:code-constants-offset 2)) + (des (allocate-cold-descriptor *read-only* + (+ (ash header-n-words + sb!vm:word-shift) + length) + sb!vm:other-pointer-lowtag))) (write-memory des - (make-other-immediate-descriptor - header-n-words sb!vm:code-header-widetag)) + (make-other-immediate-descriptor + header-n-words sb!vm:code-header-widetag)) (write-wordindexed des - sb!vm:code-code-size-slot - (make-fixnum-descriptor - (ash (+ length (1- (ash 1 sb!vm:word-shift))) - (- sb!vm:word-shift)))) + sb!vm:code-code-size-slot + (make-fixnum-descriptor + (ash (+ length (1- (ash 1 sb!vm:word-shift))) + (- sb!vm:word-shift)))) (write-wordindexed des sb!vm:code-entry-points-slot *nil-descriptor*) (write-wordindexed des sb!vm:code-debug-info-slot *nil-descriptor*) (let* ((start (+ (descriptor-byte-offset des) - (ash header-n-words sb!vm:word-shift))) - (end (+ start length))) + (ash header-n-words sb!vm:word-shift))) + (end (+ start length))) (read-bigvec-as-sequence-or-die (descriptor-bytes des) - *fasl-input-stream* - :start start - :end end)) + *fasl-input-stream* + :start start + :end end)) des)) (define-cold-fop (fop-assembler-routine) (let* ((routine (pop-stack)) - (des (pop-stack)) - (offset (calc-offset des (read-word-arg)))) + (des (pop-stack)) + (offset (calc-offset des (read-word-arg)))) (record-cold-assembler-routine routine (+ (logandc2 (descriptor-bits des) sb!vm:lowtag-mask) offset)) @@ -2569,17 +2569,17 @@ core and return a descriptor to it." (define-cold-fop (fop-assembler-fixup) (let* ((routine (pop-stack)) - (kind (pop-stack)) - (code-object (pop-stack)) - (offset (read-word-arg))) + (kind (pop-stack)) + (code-object (pop-stack)) + (offset (read-word-arg))) (record-cold-assembler-fixup routine code-object offset kind) code-object)) (define-cold-fop (fop-code-object-fixup) (let* ((kind (pop-stack)) - (code-object (pop-stack)) - (offset (read-word-arg)) - (value (descriptor-bits code-object))) + (code-object (pop-stack)) + (offset (read-word-arg)) + (value (descriptor-bits code-object))) (do-cold-fixup code-object offset value kind) code-object)) @@ -2592,33 +2592,33 @@ core and return a descriptor to it." (defun write-boilerplate () (format t "/*~%") (dolist (line - '("This is a machine-generated file. Please do not edit it by hand." + '("This is a machine-generated file. Please do not edit it by hand." "(As of sbcl-0.8.14, it came from WRITE-CONFIG-H in genesis.lisp.)" - "" - "This file contains low-level information about the" - "internals of a particular version and configuration" - "of SBCL. It is used by the C compiler to create a runtime" - "support environment, an executable program in the host" - "operating system's native format, which can then be used to" - "load and run 'core' files, which are basically programs" - "in SBCL's own format.")) + "" + "This file contains low-level information about the" + "internals of a particular version and configuration" + "of SBCL. It is used by the C compiler to create a runtime" + "support environment, an executable program in the host" + "operating system's native format, which can then be used to" + "load and run 'core' files, which are basically programs" + "in SBCL's own format.")) (format t " * ~A~%" line)) (format t " */~%")) (defun write-config-h () ;; propagating *SHEBANG-FEATURES* into C-level #define's (dolist (shebang-feature-name (sort (mapcar #'symbol-name - sb-cold:*shebang-features*) - #'string<)) + sb-cold:*shebang-features*) + #'string<)) (format t - "#define LISP_FEATURE_~A~%" - (substitute #\_ #\- shebang-feature-name))) + "#define LISP_FEATURE_~A~%" + (substitute #\_ #\- shebang-feature-name))) (terpri) ;; and miscellaneous constants (format t "#define SBCL_CORE_VERSION_INTEGER ~D~%" sbcl-core-version-integer) (format t - "#define SBCL_VERSION_STRING ~S~%" - (sb!xc:lisp-implementation-version)) + "#define SBCL_VERSION_STRING ~S~%" + (sb!xc:lisp-implementation-version)) (format t "#define CORE_MAGIC 0x~X~%" core-magic) (format t "#ifndef LANGUAGE_ASSEMBLY~2%") (format t "#define LISPOBJ(x) ((lispobj)x)~2%") @@ -2628,16 +2628,16 @@ core and return a descriptor to it." (terpri)) (defun write-constants-h () - ;; writing entire families of named constants + ;; writing entire families of named constants (let ((constants nil)) (dolist (package-name '(;; Even in CMU CL, constants from VM - ;; were automatically propagated - ;; into the runtime. - "SB!VM" - ;; In SBCL, we also propagate various - ;; magic numbers related to file format, - ;; which live here instead of SB!VM. - "SB!FASL")) + ;; were automatically propagated + ;; into the runtime. + "SB!VM" + ;; In SBCL, we also propagate various + ;; magic numbers related to file format, + ;; which live here instead of SB!VM. + "SB!FASL")) (do-external-symbols (symbol (find-package package-name)) (when (constantp symbol) (let ((name (symbol-name symbol))) @@ -2674,7 +2674,7 @@ core and return a descriptor to it." (tailwise-equal name suffix)) suffixes) (record-with-translated-name priority)))) - + (maybe-record-with-translated-name '("-LOWTAG") 0) (maybe-record-with-translated-name '("-WIDETAG") 1) (maybe-record-with-munged-name "-FLAG" "flag_" 2) @@ -2701,45 +2701,45 @@ core and return a descriptor to it." constants)) (setf constants - (sort constants - (lambda (const1 const2) - (if (= (second const1) (second const2)) - (< (third const1) (third const2)) - (< (second const1) (second const2)))))) + (sort constants + (lambda (const1 const2) + (if (= (second const1) (second const2)) + (< (third const1) (third const2)) + (< (second const1) (second const2)))))) (let ((prev-priority (second (car constants)))) (dolist (const constants) - (destructuring-bind (name priority value doc) const - (unless (= prev-priority priority) - (terpri) - (setf prev-priority priority)) - (format t "#define ~A " name) - (format t - ;; KLUDGE: As of sbcl-0.6.7.14, we're dumping two - ;; different kinds of values here, (1) small codes - ;; and (2) machine addresses. The small codes can be - ;; dumped as bare integer values. The large machine - ;; addresses might cause problems if they're large - ;; and represented as (signed) C integers, so we - ;; want to force them to be unsigned. We do that by - ;; wrapping them in the LISPOBJ macro. (We could do - ;; it with a bare "(unsigned)" cast, except that - ;; this header file is used not only in C files, but - ;; also in assembly files, which don't understand - ;; the cast syntax. The LISPOBJ macro goes away in - ;; assembly files, but that shouldn't matter because - ;; we don't do arithmetic on address constants in - ;; assembly files. See? It really is a kludge..) -- - ;; WHN 2000-10-18 - (let (;; cutoff for treatment as a small code - (cutoff (expt 2 16))) - (cond ((minusp value) - (error "stub: negative values unsupported")) - ((< value cutoff) - "~D") - (t - "LISPOBJ(~D)"))) - value) - (format t " /* 0x~X */~@[ /* ~A */~]~%" value doc)))) + (destructuring-bind (name priority value doc) const + (unless (= prev-priority priority) + (terpri) + (setf prev-priority priority)) + (format t "#define ~A " name) + (format t + ;; KLUDGE: As of sbcl-0.6.7.14, we're dumping two + ;; different kinds of values here, (1) small codes + ;; and (2) machine addresses. The small codes can be + ;; dumped as bare integer values. The large machine + ;; addresses might cause problems if they're large + ;; and represented as (signed) C integers, so we + ;; want to force them to be unsigned. We do that by + ;; wrapping them in the LISPOBJ macro. (We could do + ;; it with a bare "(unsigned)" cast, except that + ;; this header file is used not only in C files, but + ;; also in assembly files, which don't understand + ;; the cast syntax. The LISPOBJ macro goes away in + ;; assembly files, but that shouldn't matter because + ;; we don't do arithmetic on address constants in + ;; assembly files. See? It really is a kludge..) -- + ;; WHN 2000-10-18 + (let (;; cutoff for treatment as a small code + (cutoff (expt 2 16))) + (cond ((minusp value) + (error "stub: negative values unsupported")) + ((< value cutoff) + "~D") + (t + "LISPOBJ(~D)"))) + value) + (format t " /* 0x~X */~@[ /* ~A */~]~%" value doc)))) (terpri)) ;; writing information about internal errors @@ -2762,64 +2762,64 @@ core and return a descriptor to it." #!+sparc (when (boundp 'sb!vm::pseudo-atomic-trap) (format t - "#define PSEUDO_ATOMIC_TRAP ~D /* 0x~:*~X */~%" - sb!vm::pseudo-atomic-trap) + "#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]) (dolist (symbol '(sb!vm::float-traps-byte - sb!vm::float-exceptions-byte - sb!vm::float-sticky-bits - sb!vm::float-rounding-mode)) + sb!vm::float-exceptions-byte + sb!vm::float-sticky-bits + sb!vm::float-rounding-mode)) (format t "#define ~A_POSITION ~A /* ~:*0x~X */~%" - (substitute #\_ #\- (symbol-name symbol)) - (sb!xc:byte-position (symbol-value symbol))) + (substitute #\_ #\- (symbol-name symbol)) + (sb!xc:byte-position (symbol-value symbol))) (format t "#define ~A_MASK 0x~X /* ~:*~A */~%" - (substitute #\_ #\- (symbol-name symbol)) - (sb!xc:mask-field (symbol-value symbol) -1)))) + (substitute #\_ #\- (symbol-name symbol)) + (sb!xc:mask-field (symbol-value symbol) -1)))) -(defun write-primitive-object (obj) +(defun write-primitive-object (obj) ;; writing primitive object layouts (format t "#ifndef LANGUAGE_ASSEMBLY~2%") (format t - "struct ~A {~%" - (substitute #\_ #\- - (string-downcase (string (sb!vm:primitive-object-name obj))))) + "struct ~A {~%" + (substitute #\_ #\- + (string-downcase (string (sb!vm:primitive-object-name obj))))) (when (sb!vm:primitive-object-widetag obj) - (format t " lispobj header;~%")) + (format t " lispobj header;~%")) (dolist (slot (sb!vm:primitive-object-slots obj)) - (format t " ~A ~A~@[[1]~];~%" - (getf (sb!vm:slot-options slot) :c-type "lispobj") - (substitute #\_ #\- - (string-downcase (string (sb!vm:slot-name slot)))) - (sb!vm:slot-rest-p slot))) + (format t " ~A ~A~@[[1]~];~%" + (getf (sb!vm:slot-options slot) :c-type "lispobj") + (substitute #\_ #\- + (string-downcase (string (sb!vm:slot-name slot)))) + (sb!vm:slot-rest-p slot))) (format t "};~2%") (format t "#else /* LANGUAGE_ASSEMBLY */~2%") (let ((name (sb!vm:primitive-object-name obj)) (lowtag (eval (sb!vm:primitive-object-lowtag obj)))) - (when lowtag - (dolist (slot (sb!vm:primitive-object-slots obj)) - (format t "#define ~A_~A_OFFSET ~D~%" - (substitute #\_ #\- (string name)) - (substitute #\_ #\- (string (sb!vm:slot-name slot))) - (- (* (sb!vm:slot-offset slot) sb!vm:n-word-bytes) lowtag))) + (when lowtag + (dolist (slot (sb!vm:primitive-object-slots obj)) + (format t "#define ~A_~A_OFFSET ~D~%" + (substitute #\_ #\- (string name)) + (substitute #\_ #\- (string (sb!vm:slot-name slot))) + (- (* (sb!vm:slot-offset slot) sb!vm:n-word-bytes) lowtag))) (terpri))) (format t "#endif /* LANGUAGE_ASSEMBLY */~2%")) (defun write-structure-object (dd) (flet ((cstring (designator) - (substitute #\_ #\- (string-downcase (string designator))))) + (substitute #\_ #\- (string-downcase (string designator))))) (format t "#ifndef LANGUAGE_ASSEMBLY~2%") (format t "struct ~A {~%" (cstring (dd-name dd))) (format t " lispobj header;~%") (format t " lispobj layout;~%") (dolist (slot (dd-slots dd)) (when (eq t (dsd-raw-type slot)) - (format t " lispobj ~A;~%" (cstring (dsd-name slot))))) + (format t " lispobj ~A;~%" (cstring (dsd-name slot))))) (unless (oddp (+ (dd-length dd) (dd-raw-length dd))) (format t " long raw_slot_padding;~%")) (dotimes (n (dd-raw-length dd)) @@ -2832,18 +2832,18 @@ core and return a descriptor to it." ;; FIXME: It would be nice to use longer names than NIL and ;; (particularly) T in #define statements. (format t "#define ~A LISPOBJ(0x~X)~%" - (substitute #\_ #\- - (remove-if (lambda (char) - (member char '(#\% #\* #\. #\!))) - (symbol-name symbol))) - (if *static* ; if we ran GENESIS - ;; We actually ran GENESIS, use the real value. - (descriptor-bits (cold-intern symbol)) - ;; We didn't run GENESIS, so guess at the address. - (+ sb!vm:static-space-start - sb!vm:n-word-bytes - sb!vm:other-pointer-lowtag - (if symbol (sb!vm:static-symbol-offset symbol) 0)))))) + (substitute #\_ #\- + (remove-if (lambda (char) + (member char '(#\% #\* #\. #\!))) + (symbol-name symbol))) + (if *static* ; if we ran GENESIS + ;; We actually ran GENESIS, use the real value. + (descriptor-bits (cold-intern symbol)) + ;; We didn't run GENESIS, so guess at the address. + (+ sb!vm:static-space-start + sb!vm:n-word-bytes + sb!vm:other-pointer-lowtag + (if symbol (sb!vm:static-symbol-offset symbol) 0)))))) ;;;; writing map file @@ -2854,29 +2854,29 @@ core and return a descriptor to it." ;;; stages of cold load. (defun write-map () (let ((*print-pretty* nil) - (*print-case* :upcase)) + (*print-case* :upcase)) (format t "assembler routines defined in core image:~2%") (dolist (routine (sort (copy-list *cold-assembler-routines*) #'< - :key #'cdr)) + :key #'cdr)) (format t "#X~8,'0X: ~S~%" (cdr routine) (car routine))) (let ((funs nil) - (undefs 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))))) - *cold-fdefn-objects*) + (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)) (dolist (info funs) - (format t "0x~8,'0X: ~S #X~8,'0X~%" (cdr info) (car info) - (- (cdr info) #x17))) + (format t "0x~8,'0X: ~S #X~8,'0X~%" (cdr info) (car info) + (- (cdr info) #x17))) (format t "~%~| (a note about initially undefined function references: These functions @@ -2935,30 +2935,30 @@ initially undefined function references:~2%") (write-byte (ldb (byte 8 (* i 8)) num) *core-file*))) (:big-endian (dotimes (i sb!vm:n-word-bytes) - (write-byte (ldb (byte 8 (* (- (1- sb!vm:n-word-bytes) i) 8)) num) - *core-file*)))) + (write-byte (ldb (byte 8 (* (- (1- sb!vm:n-word-bytes) i) 8)) num) + *core-file*)))) num) (defun advance-to-page () (force-output *core-file*) (file-position *core-file* - (round-up (file-position *core-file*) - sb!c:*backend-page-size*))) + (round-up (file-position *core-file*) + sb!c:*backend-page-size*))) (defun output-gspace (gspace) (force-output *core-file*) (let* ((posn (file-position *core-file*)) - (bytes (* (gspace-free-word-index gspace) sb!vm:n-word-bytes)) - (pages (ceiling bytes sb!c:*backend-page-size*)) - (total-bytes (* pages sb!c:*backend-page-size*))) + (bytes (* (gspace-free-word-index gspace) sb!vm:n-word-bytes)) + (pages (ceiling bytes sb!c:*backend-page-size*)) + (total-bytes (* pages sb!c:*backend-page-size*))) (file-position *core-file* - (* sb!c:*backend-page-size* (1+ *data-page*))) + (* sb!c:*backend-page-size* (1+ *data-page*))) (format t - "writing ~S byte~:P [~S page~:P] from ~S~%" - total-bytes - pages - gspace) + "writing ~S byte~:P [~S page~:P] from ~S~%" + total-bytes + pages + gspace) (force-output) ;; Note: It is assumed that the GSPACE allocation routines always @@ -2968,8 +2968,8 @@ initially undefined function references:~2%") ;; where the page size is equal. (RT is 4K, PMAX is 4K, Sun 3 is ;; 8K). (write-bigvec-as-sequence (gspace-bytes gspace) - *core-file* - :end total-bytes) + *core-file* + :end total-bytes) (force-output *core-file*) (file-position *core-file* posn) @@ -2983,7 +2983,7 @@ initially undefined function references:~2%") (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*) + (floor (gspace-byte-address gspace) sb!c:*backend-page-size*) (aver (zerop rem)) (write-word floor)) (write-word pages) @@ -2998,17 +2998,17 @@ initially undefined function references:~2%") (defun write-initial-core-file (filename) (let ((filenamestring (namestring filename)) - (*data-page* 0)) + (*data-page* 0)) (format t - "[building initial core file in ~S: ~%" - filenamestring) + "[building initial core file in ~S: ~%" + filenamestring) (force-output) (with-open-file (*core-file* filenamestring - :direction :output - :element-type '(unsigned-byte 8) - :if-exists :rename-and-delete) + :direction :output + :element-type '(unsigned-byte 8) + :if-exists :rename-and-delete) ;; Write the magic number. (write-word core-magic) @@ -3021,18 +3021,18 @@ initially undefined function references:~2%") ;; Write the build ID. (write-word build-id-core-entry-type-code) (let ((build-id (with-open-file (s "output/build-id.tmp" - :direction :input) - (read s)))) - (declare (type simple-string build-id)) - (/show build-id (length build-id)) - ;; Write length of build ID record: BUILD-ID-CORE-ENTRY-TYPE-CODE - ;; word, this length word, and one word for each char of BUILD-ID. - (write-word (+ 2 (length build-id))) - (dovector (char build-id) - ;; (We write each character as a word in order to avoid - ;; having to think about word alignment issues in the - ;; sbcl-0.7.8 version of coreparse.c.) - (write-word (sb!xc:char-code char)))) + :direction :input) + (read s)))) + (declare (type simple-string build-id)) + (/show build-id (length build-id)) + ;; Write length of build ID record: BUILD-ID-CORE-ENTRY-TYPE-CODE + ;; word, this length word, and one word for each char of BUILD-ID. + (write-word (+ 2 (length build-id))) + (dovector (char build-id) + ;; (We write each character as a word in order to avoid + ;; having to think about word alignment issues in the + ;; sbcl-0.7.8 version of coreparse.c.) + (write-word (sb!xc:char-code char)))) ;; Write the New Directory entry header. (write-word new-directory-core-entry-type-code) @@ -3046,13 +3046,13 @@ initially undefined function references:~2%") (write-word initial-fun-core-entry-type-code) (write-word 3) (let* ((cold-name (cold-intern '!cold-init)) - (cold-fdefn (cold-fdefinition-object cold-name)) - (initial-fun (read-wordindexed cold-fdefn - sb!vm:fdefn-fun-slot))) - (format t - "~&/(DESCRIPTOR-BITS INITIAL-FUN)=#X~X~%" - (descriptor-bits initial-fun)) - (write-word (descriptor-bits initial-fun))) + (cold-fdefn (cold-fdefinition-object cold-name)) + (initial-fun (read-wordindexed cold-fdefn + sb!vm:fdefn-fun-slot))) + (format t + "~&/(DESCRIPTOR-BITS INITIAL-FUN)=#X~X~%" + (descriptor-bits initial-fun)) + (write-word (descriptor-bits initial-fun))) ;; Write the End entry. (write-word end-core-entry-type-code) @@ -3087,36 +3087,36 @@ initially undefined function references:~2%") ;;; 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 - object-file-names - symbol-table-file-name - core-file-name - map-file-name - c-header-dir-name) + object-file-names + symbol-table-file-name + core-file-name + map-file-name + c-header-dir-name) (format t - "~&beginning GENESIS, ~A~%" - (if core-file-name - ;; Note: This output summarizing what we're doing is - ;; somewhat telegraphic in style, not meant to imply that - ;; we're not e.g. also creating a header file when we - ;; create a core. - (format nil "creating core ~S" core-file-name) - (format nil "creating headers in ~S" c-header-dir-name))) - + "~&beginning GENESIS, ~A~%" + (if core-file-name + ;; Note: This output summarizing what we're doing is + ;; somewhat telegraphic in style, not meant to imply that + ;; we're not e.g. also creating a header file when we + ;; create a core. + (format nil "creating core ~S" core-file-name) + (format nil "creating headers in ~S" c-header-dir-name))) + (let ((*cold-foreign-symbol-table* (make-hash-table :test 'equal))) (when core-file-name (if symbol-table-file-name - (load-cold-foreign-symbol-table symbol-table-file-name) - (error "can't output a core file without symbol table file input"))) + (load-cold-foreign-symbol-table symbol-table-file-name) + (error "can't output a core file without symbol table file input"))) ;; Now that we've successfully read our only input file (by ;; loading the symbol table, if any), it's a good time to ensure ;; that there'll be someplace for our output files to go when ;; we're done. (flet ((frob (filename) - (when filename - (ensure-directories-exist filename :verbose t)))) + (when filename + (ensure-directories-exist filename :verbose t)))) (frob core-file-name) (frob map-file-name)) @@ -3128,28 +3128,28 @@ initially undefined function references:~2%") (remprop sym 'cold-intern-info)) (let* ((*foreign-symbol-placeholder-value* (if core-file-name nil 0)) - (*load-time-value-counter* 0) - (*cold-fdefn-objects* (make-hash-table :test 'equal)) - (*cold-symbols* (make-hash-table :test 'equal)) - (*cold-package-symbols* nil) - (*read-only* (make-gspace :read-only - read-only-core-space-id - sb!vm:read-only-space-start)) - (*static* (make-gspace :static - static-core-space-id - sb!vm:static-space-start)) - (*dynamic* (make-gspace :dynamic - dynamic-core-space-id - #!+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 - 0 - sb!vm:unbound-marker-widetag)) - *cold-assembler-fixups* - *cold-assembler-routines* - #!+(or x86 x86-64) *load-time-code-fixups*) + (*load-time-value-counter* 0) + (*cold-fdefn-objects* (make-hash-table :test 'equal)) + (*cold-symbols* (make-hash-table :test 'equal)) + (*cold-package-symbols* nil) + (*read-only* (make-gspace :read-only + read-only-core-space-id + sb!vm:read-only-space-start)) + (*static* (make-gspace :static + static-core-space-id + sb!vm:static-space-start)) + (*dynamic* (make-gspace :dynamic + dynamic-core-space-id + #!+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 + 0 + sb!vm:unbound-marker-widetag)) + *cold-assembler-fixups* + *cold-assembler-routines* + #!+(or x86 x86-64) *load-time-code-fixups*) ;; Prepare for cold load. (initialize-non-nil-symbols) @@ -3181,39 +3181,39 @@ initially undefined function references:~2%") ;; to make &KEY arguments work right and in order to make ;; BACKTRACEs into target Lisp system code be legible.) (dolist (exported-name - (sb-cold:read-from-file "common-lisp-exports.lisp-expr")) - (cold-intern (intern exported-name *cl-package*))) + (sb-cold:read-from-file "common-lisp-exports.lisp-expr")) + (cold-intern (intern exported-name *cl-package*))) (dolist (pd (sb-cold:read-from-file "package-data-list.lisp-expr")) - (declare (type sb-cold:package-data pd)) - (let ((package (find-package (sb-cold:package-data-name pd)))) - (labels (;; Call FN on every node of the TREE. - (mapc-on-tree (fn tree) + (declare (type sb-cold:package-data pd)) + (let ((package (find-package (sb-cold:package-data-name pd)))) + (labels (;; Call FN on every node of the TREE. + (mapc-on-tree (fn tree) (declare (type function fn)) - (typecase tree - (cons (mapc-on-tree fn (car tree)) - (mapc-on-tree fn (cdr tree))) - (t (funcall fn tree) - (values)))) - ;; Make sure that information about the association - ;; between PACKAGE and the symbol named NAME gets - ;; recorded in the cold-intern system or (as a - ;; convenience when dealing with the tree structure - ;; allowed in the PACKAGE-DATA-EXPORTS slot) do - ;; nothing if NAME is NIL. - (chill (name) - (when name - (cold-intern (intern name package) package)))) - (mapc-on-tree #'chill (sb-cold:package-data-export pd)) - (mapc #'chill (sb-cold:package-data-reexport pd)) - (dolist (sublist (sb-cold:package-data-import-from pd)) - (destructuring-bind (package-name &rest symbol-names) sublist - (declare (ignore package-name)) - (mapc #'chill symbol-names)))))) + (typecase tree + (cons (mapc-on-tree fn (car tree)) + (mapc-on-tree fn (cdr tree))) + (t (funcall fn tree) + (values)))) + ;; Make sure that information about the association + ;; between PACKAGE and the symbol named NAME gets + ;; recorded in the cold-intern system or (as a + ;; convenience when dealing with the tree structure + ;; allowed in the PACKAGE-DATA-EXPORTS slot) do + ;; nothing if NAME is NIL. + (chill (name) + (when name + (cold-intern (intern name package) package)))) + (mapc-on-tree #'chill (sb-cold:package-data-export pd)) + (mapc #'chill (sb-cold:package-data-reexport pd)) + (dolist (sublist (sb-cold:package-data-import-from pd)) + (destructuring-bind (package-name &rest symbol-names) sublist + (declare (ignore package-name)) + (mapc #'chill symbol-names)))))) ;; Cold load. (dolist (file-name object-file-names) - (write-line (namestring file-name)) - (cold-load file-name)) + (write-line (namestring file-name)) + (cold-load file-name)) ;; Tidy up loose ends left by cold loading. ("Postpare from cold load?") (resolve-assembler-fixups) @@ -3225,17 +3225,17 @@ initially undefined function references:~2%") ;; Tell the target Lisp how much stuff we've allocated. (cold-set 'sb!vm:*read-only-space-free-pointer* - (allocate-cold-descriptor *read-only* - 0 - sb!vm:even-fixnum-lowtag)) + (allocate-cold-descriptor *read-only* + 0 + sb!vm:even-fixnum-lowtag)) (cold-set 'sb!vm:*static-space-free-pointer* - (allocate-cold-descriptor *static* - 0 - sb!vm:even-fixnum-lowtag)) + (allocate-cold-descriptor *static* + 0 + sb!vm:even-fixnum-lowtag)) (cold-set 'sb!vm:*initial-dynamic-space-free-pointer* - (allocate-cold-descriptor *dynamic* - 0 - sb!vm:even-fixnum-lowtag)) + (allocate-cold-descriptor *dynamic* + 0 + sb!vm:even-fixnum-lowtag)) (/show "done setting free pointers") ;; Write results to files. @@ -3246,46 +3246,46 @@ initially undefined function references:~2%") ;; *STANDARD-OUTPUT*) not be parallel to WRITE-INITIAL-CORE-FILE ;; (to a stream explicitly passed as an argument). (macrolet ((out-to (name &body body) - `(let ((fn (format nil "~A/~A.h" c-header-dir-name ,name))) - (ensure-directories-exist fn) - (with-open-file (*standard-output* fn - :if-exists :supersede :direction :output) - (write-boilerplate) - (let ((n (substitute #\_ #\- (string-upcase ,name)))) - (format - t - "#ifndef SBCL_GENESIS_~A~%#define SBCL_GENESIS_~A 1~%" - n n)) - ,@body - (format t - "#endif /* SBCL_GENESIS_~A */~%" - (string-upcase ,name)))))) + `(let ((fn (format nil "~A/~A.h" c-header-dir-name ,name))) + (ensure-directories-exist fn) + (with-open-file (*standard-output* fn + :if-exists :supersede :direction :output) + (write-boilerplate) + (let ((n (substitute #\_ #\- (string-upcase ,name)))) + (format + t + "#ifndef SBCL_GENESIS_~A~%#define SBCL_GENESIS_~A 1~%" + n n)) + ,@body + (format t + "#endif /* SBCL_GENESIS_~A */~%" + (string-upcase ,name)))))) (when map-file-name - (with-open-file (*standard-output* map-file-name - :direction :output - :if-exists :supersede) - (write-map))) - (out-to "config" (write-config-h)) - (out-to "constants" (write-constants-h)) - (let ((structs (sort (copy-list sb!vm:*primitive-objects*) #'string< - :key (lambda (obj) - (symbol-name - (sb!vm:primitive-object-name obj)))))) - (dolist (obj structs) - (out-to - (string-downcase (string (sb!vm:primitive-object-name obj))) - (write-primitive-object obj))) - (out-to "primitive-objects" - (dolist (obj structs) - (format t "~&#include \"~A.h\"~%" - (string-downcase - (string (sb!vm:primitive-object-name obj))))))) - (dolist (class '(hash-table layout)) - (out-to - (string-downcase (string class)) - (write-structure-object - (sb!kernel:layout-info (sb!kernel:find-layout class))))) - (out-to "static-symbols" (write-static-symbols)) - + (with-open-file (*standard-output* map-file-name + :direction :output + :if-exists :supersede) + (write-map))) + (out-to "config" (write-config-h)) + (out-to "constants" (write-constants-h)) + (let ((structs (sort (copy-list sb!vm:*primitive-objects*) #'string< + :key (lambda (obj) + (symbol-name + (sb!vm:primitive-object-name obj)))))) + (dolist (obj structs) + (out-to + (string-downcase (string (sb!vm:primitive-object-name obj))) + (write-primitive-object obj))) + (out-to "primitive-objects" + (dolist (obj structs) + (format t "~&#include \"~A.h\"~%" + (string-downcase + (string (sb!vm:primitive-object-name obj))))))) + (dolist (class '(hash-table layout)) + (out-to + (string-downcase (string class)) + (write-structure-object + (sb!kernel:layout-info (sb!kernel:find-layout class))))) + (out-to "static-symbols" (write-static-symbols)) + (when core-file-name - (write-initial-core-file core-file-name)))))) + (write-initial-core-file core-file-name)))))) diff --git a/src/compiler/generic/interr.lisp b/src/compiler/generic/interr.lisp index 8fde951..fd992ab 100644 --- a/src/compiler/generic/interr.lisp +++ b/src/compiler/generic/interr.lisp @@ -24,14 +24,14 @@ ;;; functions as closures instead of DEFUNs? (eval-when (:compile-toplevel :execute) (def!macro define-internal-errors (&rest errors) - (let ((info (mapcar (lambda (x) - (cons (symbolicate (first x) "-ERROR") - (second x))) - errors))) - `(progn - (setf sb!c:*backend-internal-errors* - ',(coerce info 'vector)) - nil)))) + (let ((info (mapcar (lambda (x) + (cons (symbolicate (first x) "-ERROR") + (second x))) + errors))) + `(progn + (setf sb!c:*backend-internal-errors* + ',(coerce info 'vector)) + nil)))) (define-internal-errors (unknown @@ -147,11 +147,11 @@ "Object is not a complex (non-SIMPLE-ARRAY) vector.") . #.(map 'list - (lambda (saetp) - (list - (symbolicate "OBJECT-NOT-" (sb!vm:saetp-primitive-type-name saetp)) - (format nil "Object is not of type ~A." - (specifier-type - `(simple-array ,(sb!vm:saetp-specifier saetp) (*)))))) - sb!vm:*specialized-array-element-type-properties*)) + (lambda (saetp) + (list + (symbolicate "OBJECT-NOT-" (sb!vm:saetp-primitive-type-name saetp)) + (format nil "Object is not of type ~A." + (specifier-type + `(simple-array ,(sb!vm:saetp-specifier saetp) (*)))))) + sb!vm:*specialized-array-element-type-properties*)) diff --git a/src/compiler/generic/late-nlx.lisp b/src/compiler/generic/late-nlx.lisp index 4f6b31a..d2d5855 100644 --- a/src/compiler/generic/late-nlx.lisp +++ b/src/compiler/generic/late-nlx.lisp @@ -15,12 +15,12 @@ ;;; state for use with the SAVE- and RESTORE-DYNAMIC-ENVIRONMENT VOPs. (!def-vm-support-routine make-dynamic-state-tns () (make-n-tns #.(let ((nsave - (sb!c::vop-info-num-results - (template-or-lose 'save-dynamic-state))) - (nrestore - (sb!c::vop-info-num-args - (template-or-lose 'restore-dynamic-state)))) - (aver (= nsave nrestore)) - nsave) - *backend-t-primitive-type*)) + (sb!c::vop-info-num-results + (template-or-lose 'save-dynamic-state))) + (nrestore + (sb!c::vop-info-num-args + (template-or-lose 'restore-dynamic-state)))) + (aver (= nsave nrestore)) + nsave) + *backend-t-primitive-type*)) diff --git a/src/compiler/generic/late-type-vops.lisp b/src/compiler/generic/late-type-vops.lisp index c9a9602..74ff6ed 100644 --- a/src/compiler/generic/late-type-vops.lisp +++ b/src/compiler/generic/late-type-vops.lisp @@ -37,7 +37,7 @@ (!define-type-vops complexp check-complex complex object-not-complex-error (complex-widetag complex-single-float-widetag complex-double-float-widetag - #!+long-float complex-long-float-widetag)) + #!+long-float complex-long-float-widetag)) (!define-type-vops complex-rational-p check-complex-rational nil object-not-complex-rational-error @@ -46,7 +46,7 @@ (!define-type-vops complex-float-p check-complex-float nil object-not-complex-float-error (complex-single-float-widetag complex-double-float-widetag - #!+long-float complex-long-float-widetag)) + #!+long-float complex-long-float-widetag)) (!define-type-vops complex-single-float-p check-complex-single-float complex-single-float object-not-complex-single-float-error @@ -71,17 +71,17 @@ (macrolet ((define-simple-array-type-vops () - `(progn - ,@(map 'list - (lambda (saetp) - (let ((primtype (saetp-primitive-type-name saetp))) - `(!define-type-vops - ,(symbolicate primtype "-P") - ,(symbolicate "CHECK-" primtype) - ,primtype - ,(symbolicate "OBJECT-NOT-" primtype "-ERROR") - (,(saetp-typecode saetp))))) - *specialized-array-element-type-properties*)))) + `(progn + ,@(map 'list + (lambda (saetp) + (let ((primtype (saetp-primitive-type-name saetp))) + `(!define-type-vops + ,(symbolicate primtype "-P") + ,(symbolicate "CHECK-" primtype) + ,primtype + ,(symbolicate "OBJECT-NOT-" primtype "-ERROR") + (,(saetp-typecode saetp))))) + *specialized-array-element-type-properties*)))) (define-simple-array-type-vops)) (!define-type-vops characterp check-character character @@ -141,12 +141,12 @@ (complex-vector-widetag . #.(append (map 'list - #'saetp-typecode - *specialized-array-element-type-properties*) + #'saetp-typecode + *specialized-array-element-type-properties*) (mapcan (lambda (saetp) - (when (saetp-complex-typecode saetp) - (list (saetp-complex-typecode saetp)))) - (coerce *specialized-array-element-type-properties* 'list))))) + (when (saetp-complex-typecode saetp) + (list (saetp-complex-typecode saetp)))) + (coerce *specialized-array-element-type-properties* 'list))))) ;;; Note that this "type VOP" is sort of an oddball; it doesn't so ;;; much test for a Lisp-level type as just expose a low-level type @@ -166,8 +166,8 @@ object-not-simple-array-error (simple-array-widetag . #.(map 'list - #'saetp-typecode - *specialized-array-element-type-properties*))) + #'saetp-typecode + *specialized-array-element-type-properties*))) (!define-type-vops arrayp check-array nil object-not-array-error (simple-array-widetag @@ -175,12 +175,12 @@ complex-vector-widetag . #.(append (map 'list - #'saetp-typecode - *specialized-array-element-type-properties*) + #'saetp-typecode + *specialized-array-element-type-properties*) (mapcan (lambda (saetp) - (when (saetp-complex-typecode saetp) - (list (saetp-complex-typecode saetp)))) - (coerce *specialized-array-element-type-properties* 'list))))) + (when (saetp-complex-typecode saetp) + (list (saetp-complex-typecode saetp)))) + (coerce *specialized-array-element-type-properties* 'list))))) (!define-type-vops numberp check-number nil object-not-number-error (even-fixnum-lowtag diff --git a/src/compiler/generic/objdef.lisp b/src/compiler/generic/objdef.lisp index 716589e..7bfbb4c 100644 --- a/src/compiler/generic/objdef.lisp +++ b/src/compiler/generic/objdef.lisp @@ -39,129 +39,129 @@ ;;;; the primitive objects themselves (define-primitive-object (cons :lowtag list-pointer-lowtag - :alloc-trans cons) + :alloc-trans cons) (car :ref-trans car :set-trans sb!c::%rplaca :init :arg) (cdr :ref-trans cdr :set-trans sb!c::%rplacd :init :arg)) (define-primitive-object (instance :lowtag instance-pointer-lowtag - :widetag instance-header-widetag - :alloc-trans %make-instance) + :widetag instance-header-widetag + :alloc-trans %make-instance) (slots :rest-p t)) (define-primitive-object (bignum :lowtag other-pointer-lowtag - :widetag bignum-widetag - :alloc-trans sb!bignum::%allocate-bignum) + :widetag bignum-widetag + :alloc-trans sb!bignum::%allocate-bignum) (digits :rest-p t :c-type #!-alpha "long" #!+alpha "u32")) (define-primitive-object (ratio :type ratio - :lowtag other-pointer-lowtag - :widetag ratio-widetag - :alloc-trans %make-ratio) + :lowtag other-pointer-lowtag + :widetag ratio-widetag + :alloc-trans %make-ratio) (numerator :type integer - :ref-known (flushable movable) - :ref-trans %numerator - :init :arg) + :ref-known (flushable movable) + :ref-trans %numerator + :init :arg) (denominator :type integer - :ref-known (flushable movable) - :ref-trans %denominator - :init :arg)) + :ref-known (flushable movable) + :ref-trans %denominator + :init :arg)) #!+#.(cl:if (cl:= sb!vm:n-word-bits 32) '(and) '(or)) (define-primitive-object (single-float :lowtag other-pointer-lowtag - :widetag single-float-widetag) + :widetag single-float-widetag) (value :c-type "float")) (define-primitive-object (double-float :lowtag other-pointer-lowtag - :widetag double-float-widetag) + :widetag double-float-widetag) #!-x86-64 (filler) (value :c-type "double" :length #!-x86-64 2 #!+x86-64 1)) #!+long-float (define-primitive-object (long-float :lowtag other-pointer-lowtag - :widetag long-float-widetag) + :widetag long-float-widetag) #!+sparc (filler) (value :c-type "long double" :length #!+x86 3 #!+sparc 4)) (define-primitive-object (complex :type complex - :lowtag other-pointer-lowtag - :widetag complex-widetag - :alloc-trans %make-complex) + :lowtag other-pointer-lowtag + :widetag complex-widetag + :alloc-trans %make-complex) (real :type real - :ref-known (flushable movable) - :ref-trans %realpart - :init :arg) + :ref-known (flushable movable) + :ref-trans %realpart + :init :arg) (imag :type real - :ref-known (flushable movable) - :ref-trans %imagpart - :init :arg)) + :ref-known (flushable movable) + :ref-trans %imagpart + :init :arg)) (define-primitive-object (array :lowtag other-pointer-lowtag - :widetag t) + :widetag t) ;; FILL-POINTER of an ARRAY is in the same place as LENGTH of a ;; VECTOR -- see SHRINK-VECTOR. (fill-pointer :type index - :ref-trans %array-fill-pointer - :ref-known (flushable foldable) - :set-trans (setf %array-fill-pointer) - :set-known (unsafe)) + :ref-trans %array-fill-pointer + :ref-known (flushable foldable) + :set-trans (setf %array-fill-pointer) + :set-known (unsafe)) (fill-pointer-p :type (member t nil) - :ref-trans %array-fill-pointer-p - :ref-known (flushable foldable) - :set-trans (setf %array-fill-pointer-p) - :set-known (unsafe)) + :ref-trans %array-fill-pointer-p + :ref-known (flushable foldable) + :set-trans (setf %array-fill-pointer-p) + :set-known (unsafe)) (elements :type index - :ref-trans %array-available-elements - :ref-known (flushable foldable) - :set-trans (setf %array-available-elements) - :set-known (unsafe)) + :ref-trans %array-available-elements + :ref-known (flushable foldable) + :set-trans (setf %array-available-elements) + :set-known (unsafe)) (data :type array - :ref-trans %array-data-vector - :ref-known (flushable foldable) - :set-trans (setf %array-data-vector) - :set-known (unsafe)) + :ref-trans %array-data-vector + :ref-known (flushable foldable) + :set-trans (setf %array-data-vector) + :set-known (unsafe)) (displacement :type (or index null) - :ref-trans %array-displacement - :ref-known (flushable foldable) - :set-trans (setf %array-displacement) - :set-known (unsafe)) + :ref-trans %array-displacement + :ref-known (flushable foldable) + :set-trans (setf %array-displacement) + :set-known (unsafe)) (displaced-p :type (member t nil) - :ref-trans %array-displaced-p - :ref-known (flushable foldable) - :set-trans (setf %array-displaced-p) - :set-known (unsafe)) + :ref-trans %array-displaced-p + :ref-known (flushable foldable) + :set-trans (setf %array-displaced-p) + :set-known (unsafe)) (dimensions :rest-p t)) (define-primitive-object (vector :type vector - :lowtag other-pointer-lowtag - :widetag t) + :lowtag other-pointer-lowtag + :widetag t) ;; FILL-POINTER of an ARRAY is in the same place as LENGTH of a ;; VECTOR -- see SHRINK-VECTOR. (length :ref-trans sb!c::vector-length - :type index) + :type index) (data :rest-p t :c-type #!-alpha "unsigned long" #!+alpha "u32")) (define-primitive-object (code :type code-component - :lowtag other-pointer-lowtag - :widetag t) + :lowtag other-pointer-lowtag + :widetag t) (code-size :type index - :ref-known (flushable movable) - :ref-trans %code-code-size) + :ref-known (flushable movable) + :ref-trans %code-code-size) (entry-points :type (or function null) - :ref-known (flushable) - :ref-trans %code-entry-points - :set-known (unsafe) - :set-trans (setf %code-entry-points)) + :ref-known (flushable) + :ref-trans %code-entry-points + :set-known (unsafe) + :set-trans (setf %code-entry-points)) (debug-info :type t - :ref-known (flushable) - :ref-trans %code-debug-info - :set-known (unsafe) - :set-trans (setf %code-debug-info)) + :ref-known (flushable) + :ref-trans %code-debug-info + :set-known (unsafe) + :set-trans (setf %code-debug-info)) (trace-table-offset) (constants :rest-p t)) (define-primitive-object (fdefn :type fdefn - :lowtag other-pointer-lowtag - :widetag fdefn-widetag) + :lowtag other-pointer-lowtag + :widetag fdefn-widetag) (name :ref-trans fdefn-name) (fun :type (or function null) :ref-trans fdefn-fun) (raw-addr :c-type #!-alpha "char *" #!+alpha "u32")) @@ -169,44 +169,44 @@ ;;; a simple function (as opposed to hairier things like closures ;;; which are also subtypes of Common Lisp's FUNCTION type) (define-primitive-object (simple-fun :type function - :lowtag fun-pointer-lowtag - :widetag simple-fun-header-widetag) + :lowtag fun-pointer-lowtag + :widetag simple-fun-header-widetag) #!-(or x86 x86-64) (self :ref-trans %simple-fun-self - :set-trans (setf %simple-fun-self)) + :set-trans (setf %simple-fun-self)) #!+(or x86 x86-64) (self - ;; KLUDGE: There's no :SET-KNOWN, :SET-TRANS, :REF-KNOWN, or - ;; :REF-TRANS here in this case. Instead, there's separate - ;; DEFKNOWN/DEFINE-VOP/DEFTRANSFORM stuff in - ;; compiler/x86/system.lisp to define and declare them by - ;; hand. I don't know why this is, but that's (basically) - ;; the way it was done in CMU CL, and it works. (It's not - ;; exactly the same way it was done in CMU CL in that CMU - ;; CL's allows duplicate DEFKNOWNs, blithely overwriting any - ;; previous data associated with the previous DEFKNOWN, and - ;; that property was used to mask the definitions here. In - ;; SBCL as of 0.6.12.64 that's not allowed -- too confusing! - ;; -- so we have to explicitly suppress the DEFKNOWNish - ;; stuff here in order to allow this old hack to work in the - ;; new world. -- WHN 2001-08-82 - ) + ;; KLUDGE: There's no :SET-KNOWN, :SET-TRANS, :REF-KNOWN, or + ;; :REF-TRANS here in this case. Instead, there's separate + ;; DEFKNOWN/DEFINE-VOP/DEFTRANSFORM stuff in + ;; compiler/x86/system.lisp to define and declare them by + ;; hand. I don't know why this is, but that's (basically) + ;; the way it was done in CMU CL, and it works. (It's not + ;; exactly the same way it was done in CMU CL in that CMU + ;; CL's allows duplicate DEFKNOWNs, blithely overwriting any + ;; previous data associated with the previous DEFKNOWN, and + ;; that property was used to mask the definitions here. In + ;; SBCL as of 0.6.12.64 that's not allowed -- too confusing! + ;; -- so we have to explicitly suppress the DEFKNOWNish + ;; stuff here in order to allow this old hack to work in the + ;; new world. -- WHN 2001-08-82 + ) (next :type (or function null) - :ref-known (flushable) - :ref-trans %simple-fun-next - :set-known (unsafe) - :set-trans (setf %simple-fun-next)) + :ref-known (flushable) + :ref-trans %simple-fun-next + :set-known (unsafe) + :set-trans (setf %simple-fun-next)) (name :ref-known (flushable) - :ref-trans %simple-fun-name - :set-known (unsafe) - :set-trans (setf %simple-fun-name)) + :ref-trans %simple-fun-name + :set-known (unsafe) + :set-trans (setf %simple-fun-name)) (arglist :type list :ref-known (flushable) - :ref-trans %simple-fun-arglist - :set-known (unsafe) - :set-trans (setf %simple-fun-arglist)) + :ref-trans %simple-fun-arglist + :set-known (unsafe) + :set-trans (setf %simple-fun-arglist)) (type :ref-known (flushable) - :ref-trans %simple-fun-type - :set-known (unsafe) - :set-trans (setf %simple-fun-type)) + :ref-trans %simple-fun-type + :set-known (unsafe) + :set-trans (setf %simple-fun-type)) ;; the SB!C::DEBUG-FUN object corresponding to this object, or NIL for none #+nil ; FIXME: doesn't work (gotcha, lowly maintenoid!) See notes on bug 137. (debug-fun :ref-known (flushable) @@ -219,14 +219,14 @@ (return-point :c-type "unsigned char" :rest-p t)) (define-primitive-object (closure :lowtag fun-pointer-lowtag - :widetag closure-header-widetag) + :widetag closure-header-widetag) (fun :init :arg :ref-trans %closure-fun) (info :rest-p t)) (define-primitive-object (funcallable-instance - :lowtag fun-pointer-lowtag - :widetag funcallable-instance-header-widetag - :alloc-trans %make-funcallable-instance) + :lowtag fun-pointer-lowtag + :widetag funcallable-instance-header-widetag + :alloc-trans %make-funcallable-instance) #!-(or x86 x86-64) (fun :ref-known (flushable) :ref-trans %funcallable-instance-fun @@ -249,42 +249,42 @@ ;; translation without trying to fix it. -- WHN 2001-08-02 ) (lexenv :ref-known (flushable) :ref-trans %funcallable-instance-lexenv - :set-known (unsafe) :set-trans (setf %funcallable-instance-lexenv)) + :set-known (unsafe) :set-trans (setf %funcallable-instance-lexenv)) (layout :init :arg - :ref-known (flushable) :ref-trans %funcallable-instance-layout - :set-known (unsafe) :set-trans (setf %funcallable-instance-layout)) + :ref-known (flushable) :ref-trans %funcallable-instance-layout + :set-known (unsafe) :set-trans (setf %funcallable-instance-layout)) (info :rest-p t)) (define-primitive-object (value-cell :lowtag other-pointer-lowtag - :widetag value-cell-header-widetag - :alloc-trans make-value-cell) + :widetag value-cell-header-widetag + :alloc-trans make-value-cell) (value :set-trans value-cell-set - :set-known (unsafe) - :ref-trans value-cell-ref - :ref-known (flushable) - :init :arg)) + :set-known (unsafe) + :ref-trans value-cell-ref + :ref-known (flushable) + :init :arg)) #!+alpha (define-primitive-object (sap :lowtag other-pointer-lowtag - :widetag sap-widetag) + :widetag sap-widetag) (padding) (pointer :c-type "char *" :length 2)) #!-alpha (define-primitive-object (sap :lowtag other-pointer-lowtag - :widetag sap-widetag) + :widetag sap-widetag) (pointer :c-type "char *")) (define-primitive-object (weak-pointer :type weak-pointer - :lowtag other-pointer-lowtag - :widetag weak-pointer-widetag - :alloc-trans make-weak-pointer) + :lowtag other-pointer-lowtag + :widetag weak-pointer-widetag + :alloc-trans make-weak-pointer) (value :ref-trans sb!c::%weak-pointer-value :ref-known (flushable) - :init :arg) + :init :arg) (broken :type (member t nil) - :ref-trans sb!c::%weak-pointer-broken :ref-known (flushable) - :init :null) + :ref-trans sb!c::%weak-pointer-broken :ref-known (flushable) + :init :null) (next :c-type #!-alpha "struct weak_pointer *" #!+alpha "u32")) ;;;; other non-heap data blocks @@ -315,11 +315,11 @@ ;;;; symbols (define-primitive-object (symbol :lowtag other-pointer-lowtag - :widetag symbol-header-widetag - :alloc-trans make-symbol) + :widetag symbol-header-widetag + :alloc-trans make-symbol) ;; Beware when changing this definition. NIL-the-symbol is defined - ;; using this layout, and NIL-the-end-of-list-marker is the cons + ;; using this layout, and NIL-the-end-of-list-marker is the cons ;; ( NIL . NIL ), living in the first two slots of NIL-the-symbol ;; (conses have no header). Careful selection of lowtags ensures ;; that the same pointer can be used for both purposes: @@ -334,24 +334,24 @@ (hash :set-trans %set-symbol-hash) (plist :ref-trans symbol-plist - :set-trans %set-symbol-plist - :init :null) + :set-trans %set-symbol-plist + :init :null) (name :ref-trans symbol-name :init :arg) (package :ref-trans symbol-package - :set-trans %set-symbol-package - :init :null) + :set-trans %set-symbol-package + :init :null) #!+sb-thread (tls-index :ref-known (flushable) :ref-trans symbol-tls-index)) (define-primitive-object (complex-single-float - :lowtag other-pointer-lowtag - :widetag complex-single-float-widetag) + :lowtag other-pointer-lowtag + :widetag complex-single-float-widetag) (real :c-type "float") (imag :c-type "float")) (define-primitive-object (complex-double-float - :lowtag other-pointer-lowtag - :widetag complex-double-float-widetag) - #!-x86-64 (filler) + :lowtag other-pointer-lowtag + :widetag complex-double-float-widetag) + #!-x86-64 (filler) (real :c-type "double" :length #!-x86-64 2 #!+x86-64 1) (imag :c-type "double" :length #!-x86-64 2 #!+x86-64 1)) @@ -359,12 +359,12 @@ ;;; in c-land. However, we need sight of so many parts of it from Lisp that ;;; it makes sense to define it here anyway, so that the GENESIS machinery ;;; can take care of maintaining Lisp and C versions. -;;; Hence the even-fixnum lowtag just so we don't get odd(sic) numbers +;;; Hence the even-fixnum lowtag just so we don't get odd(sic) numbers ;;; added to the slot offsets (define-primitive-object (thread :lowtag even-fixnum-lowtag) - ;; unbound_marker is borrowed very briefly at thread startup to - ;; pass the address of initial-function into new_thread_trampoline - (unbound-marker :init :unbound) ; tls[0] = UNBOUND_MARKER_WIDETAG + ;; unbound_marker is borrowed very briefly at thread startup to + ;; pass the address of initial-function into new_thread_trampoline + (unbound-marker :init :unbound) ; tls[0] = UNBOUND_MARKER_WIDETAG (os-thread :c-type "os_thread_t") (binding-stack-start :c-type "lispobj *" :length #!+alpha 2 #!-alpha 1) (binding-stack-pointer :c-type "lispobj *" :length #!+alpha 2 #!-alpha 1) @@ -373,7 +373,7 @@ (alien-stack-start :c-type "lispobj *" :length #!+alpha 2 #!-alpha 1) (alien-stack-pointer :c-type "lispobj *" :length #!+alpha 2 #!-alpha 1) #!+gencgc (alloc-region :c-type "struct alloc_region" :length 5) - (tls-cookie) ; on x86, the LDT index + (tls-cookie) ; on x86, the LDT index (this :c-type "struct thread *" :length #!+alpha 2 #!-alpha 1) (prev :c-type "struct thread *" :length #!+alpha 2 #!-alpha 1) (next :c-type "struct thread *" :length #!+alpha 2 #!-alpha 1) @@ -383,6 +383,6 @@ #!+(or x86 x86-64) (pseudo-atomic-interrupted) (interrupt-fun) (interrupt-fun-lock) - (interrupt-data :c-type "struct interrupt_data *" - :length #!+alpha 2 #!-alpha 1) + (interrupt-data :c-type "struct interrupt_data *" + :length #!+alpha 2 #!-alpha 1) (interrupt-contexts :c-type "os_context_t *" :rest-p t)) diff --git a/src/compiler/generic/primtype.lisp b/src/compiler/generic/primtype.lisp index 836a5bd..1492378 100644 --- a/src/compiler/generic/primtype.lisp +++ b/src/compiler/generic/primtype.lisp @@ -100,14 +100,14 @@ ;;; primitive other-pointer array types (/show0 "primtype.lisp 96") (macrolet ((define-simple-array-primitive-types () - `(progn - ,@(map 'list - (lambda (saetp) - `(!def-primitive-type - ,(saetp-primitive-type-name saetp) - (descriptor-reg) - :type (simple-array ,(saetp-specifier saetp) (*)))) - *specialized-array-element-type-properties*)))) + `(progn + ,@(map 'list + (lambda (saetp) + `(!def-primitive-type + ,(saetp-primitive-type-name saetp) + (descriptor-reg) + :type (simple-array ,(saetp-specifier saetp) (*)))) + *specialized-array-element-type-properties*)))) (define-simple-array-primitive-types)) ;;; Note: The complex array types are not included, 'cause it is ;;; pointless to restrict VOPs to them. @@ -126,10 +126,10 @@ (!def-vm-support-routine primitive-type-of (object) (let ((type (ctype-of object))) (cond ((not (member-type-p type)) (primitive-type type)) - ((equal (member-type-members type) '(nil)) - (primitive-type-or-lose 'list)) - (t - *backend-t-primitive-type*)))) + ((equal (member-type-members type) '(nil)) + (primitive-type-or-lose 'list)) + (t + *backend-t-primitive-type*)))) ;;; Return the primitive type corresponding to a type descriptor ;;; structure. The second value is true when the primitive type is @@ -145,172 +145,172 @@ (primitive-type-aux type)) (/show0 "primtype.lisp 191") (defun-cached (primitive-type-aux - :hash-function (lambda (x) - (logand (type-hash-value x) #x1FF)) - :hash-bits 9 - :values 2 - :default (values nil :empty)) - ((type eq)) + :hash-function (lambda (x) + (logand (type-hash-value x) #x1FF)) + :hash-bits 9 + :values 2 + :default (values nil :empty)) + ((type eq)) (declare (type ctype type)) (macrolet ((any () '(values *backend-t-primitive-type* nil)) - (exactly (type) - `(values (primitive-type-or-lose ',type) t)) - (part-of (type) - `(values (primitive-type-or-lose ',type) nil))) + (exactly (type) + `(values (primitive-type-or-lose ',type) t)) + (part-of (type) + `(values (primitive-type-or-lose ',type) nil))) (flet ((maybe-numeric-type-union (t1 t2) - (let ((t1-name (primitive-type-name t1)) - (t2-name (primitive-type-name t2))) - (case t1-name - (positive-fixnum - (if (or (eq t2-name 'fixnum) - (eq t2-name - (ecase sb!vm::n-machine-word-bits - (32 'signed-byte-32) - (64 'signed-byte-64))) - (eq t2-name - (ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-31) - (64 'unsigned-byte-63))) - (eq t2-name - (ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-32) - (64 'unsigned-byte-64)))) - t2)) - (fixnum - (case t2-name - (#.(ecase sb!vm::n-machine-word-bits - (32 'signed-byte-32) - (64 'signed-byte-64)) - t2) - (#.(ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-31) - (64 'unsigned-byte-63)) - (primitive-type-or-lose - (ecase sb!vm::n-machine-word-bits - (32 'signed-byte-32) - (64 'signed-byte-64)))))) - (#.(ecase sb!vm::n-machine-word-bits - (32 'signed-byte-32) - (64 'signed-byte-64)) - (if (eq t2-name - (ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-31) - (64 'unsigned-byte-63))) - t1)) - (#.(ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-31) - (64 'unsigned-byte-63)) - (if (eq t2-name - (ecase sb!vm::n-machine-word-bits - (32 'unsigned-byte-32) - (64 'unsigned-byte-64))) - t2)))))) + (let ((t1-name (primitive-type-name t1)) + (t2-name (primitive-type-name t2))) + (case t1-name + (positive-fixnum + (if (or (eq t2-name 'fixnum) + (eq t2-name + (ecase sb!vm::n-machine-word-bits + (32 'signed-byte-32) + (64 'signed-byte-64))) + (eq t2-name + (ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-31) + (64 'unsigned-byte-63))) + (eq t2-name + (ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-32) + (64 'unsigned-byte-64)))) + t2)) + (fixnum + (case t2-name + (#.(ecase sb!vm::n-machine-word-bits + (32 'signed-byte-32) + (64 'signed-byte-64)) + t2) + (#.(ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-31) + (64 'unsigned-byte-63)) + (primitive-type-or-lose + (ecase sb!vm::n-machine-word-bits + (32 'signed-byte-32) + (64 'signed-byte-64)))))) + (#.(ecase sb!vm::n-machine-word-bits + (32 'signed-byte-32) + (64 'signed-byte-64)) + (if (eq t2-name + (ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-31) + (64 'unsigned-byte-63))) + t1)) + (#.(ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-31) + (64 'unsigned-byte-63)) + (if (eq t2-name + (ecase sb!vm::n-machine-word-bits + (32 'unsigned-byte-32) + (64 'unsigned-byte-64))) + t2)))))) (etypecase type - (numeric-type - (let ((lo (numeric-type-low type)) - (hi (numeric-type-high type))) - (case (numeric-type-complexp type) - (:real - (case (numeric-type-class type) - (integer - (cond ((and hi lo) - (dolist (spec - `((positive-fixnum 0 ,sb!xc:most-positive-fixnum) - ,@(ecase sb!vm::n-machine-word-bits - (32 - `((unsigned-byte-31 - 0 ,(1- (ash 1 31))) - (unsigned-byte-32 - 0 ,(1- (ash 1 32))))) - (64 - `((unsigned-byte-63 - 0 ,(1- (ash 1 63))) - (unsigned-byte-64 - 0 ,(1- (ash 1 64)))))) - (fixnum ,sb!xc:most-negative-fixnum - ,sb!xc:most-positive-fixnum) - ,(ecase sb!vm::n-machine-word-bits - (32 - `(signed-byte-32 ,(ash -1 31) - ,(1- (ash 1 31)))) - (64 - `(signed-byte-64 ,(ash -1 63) - ,(1- (ash 1 63)))))) - (if (or (< hi sb!xc:most-negative-fixnum) - (> lo sb!xc:most-positive-fixnum)) - (part-of bignum) - (any))) - (let ((type (car spec)) - (min (cadr spec)) - (max (caddr spec))) - (when (<= min lo hi max) - (return (values - (primitive-type-or-lose type) - (and (= lo min) (= hi max)))))))) - ((or (and hi (< hi sb!xc:most-negative-fixnum)) - (and lo (> lo sb!xc:most-positive-fixnum))) - (part-of bignum)) - (t - (any)))) - (float - (let ((exact (and (null lo) (null hi)))) - (case (numeric-type-format type) - ((short-float single-float) - (values (primitive-type-or-lose 'single-float) - exact)) - ((double-float) - (values (primitive-type-or-lose 'double-float) - exact)) - (t - (any))))) - (t - (any)))) - (:complex - (if (eq (numeric-type-class type) 'float) - (let ((exact (and (null lo) (null hi)))) - (case (numeric-type-format type) - ((short-float single-float) - (values (primitive-type-or-lose 'complex-single-float) - exact)) - ((double-float long-float) - (values (primitive-type-or-lose 'complex-double-float) - exact)) - (t - (part-of complex)))) - (part-of complex))) - (t - (any))))) - (array-type - (if (array-type-complexp type) - (any) - (let* ((dims (array-type-dimensions type)) - (etype (array-type-specialized-element-type type)) - (type-spec (type-specifier etype)) - ;; FIXME: We're _WHAT_? Testing for type equality - ;; with a specifier and #'EQUAL? *BOGGLE*. -- - ;; CSR, 2003-06-24 - (ptype (cdr (assoc type-spec *simple-array-primitive-types* - :test #'equal)))) - (if (and (consp dims) (null (rest dims)) ptype) - (values (primitive-type-or-lose ptype) - (eq (first dims) '*)) - (any))))) - (union-type - (if (type= type (specifier-type 'list)) - (exactly list) - (let ((types (union-type-types type))) - (multiple-value-bind (res exact) (primitive-type (first types)) - (dolist (type (rest types) (values res exact)) - (multiple-value-bind (ptype ptype-exact) - (primitive-type type) - (unless ptype-exact (setq exact nil)) - (unless (eq ptype res) - (let ((new-ptype + (numeric-type + (let ((lo (numeric-type-low type)) + (hi (numeric-type-high type))) + (case (numeric-type-complexp type) + (:real + (case (numeric-type-class type) + (integer + (cond ((and hi lo) + (dolist (spec + `((positive-fixnum 0 ,sb!xc:most-positive-fixnum) + ,@(ecase sb!vm::n-machine-word-bits + (32 + `((unsigned-byte-31 + 0 ,(1- (ash 1 31))) + (unsigned-byte-32 + 0 ,(1- (ash 1 32))))) + (64 + `((unsigned-byte-63 + 0 ,(1- (ash 1 63))) + (unsigned-byte-64 + 0 ,(1- (ash 1 64)))))) + (fixnum ,sb!xc:most-negative-fixnum + ,sb!xc:most-positive-fixnum) + ,(ecase sb!vm::n-machine-word-bits + (32 + `(signed-byte-32 ,(ash -1 31) + ,(1- (ash 1 31)))) + (64 + `(signed-byte-64 ,(ash -1 63) + ,(1- (ash 1 63)))))) + (if (or (< hi sb!xc:most-negative-fixnum) + (> lo sb!xc:most-positive-fixnum)) + (part-of bignum) + (any))) + (let ((type (car spec)) + (min (cadr spec)) + (max (caddr spec))) + (when (<= min lo hi max) + (return (values + (primitive-type-or-lose type) + (and (= lo min) (= hi max)))))))) + ((or (and hi (< hi sb!xc:most-negative-fixnum)) + (and lo (> lo sb!xc:most-positive-fixnum))) + (part-of bignum)) + (t + (any)))) + (float + (let ((exact (and (null lo) (null hi)))) + (case (numeric-type-format type) + ((short-float single-float) + (values (primitive-type-or-lose 'single-float) + exact)) + ((double-float) + (values (primitive-type-or-lose 'double-float) + exact)) + (t + (any))))) + (t + (any)))) + (:complex + (if (eq (numeric-type-class type) 'float) + (let ((exact (and (null lo) (null hi)))) + (case (numeric-type-format type) + ((short-float single-float) + (values (primitive-type-or-lose 'complex-single-float) + exact)) + ((double-float long-float) + (values (primitive-type-or-lose 'complex-double-float) + exact)) + (t + (part-of complex)))) + (part-of complex))) + (t + (any))))) + (array-type + (if (array-type-complexp type) + (any) + (let* ((dims (array-type-dimensions type)) + (etype (array-type-specialized-element-type type)) + (type-spec (type-specifier etype)) + ;; FIXME: We're _WHAT_? Testing for type equality + ;; with a specifier and #'EQUAL? *BOGGLE*. -- + ;; CSR, 2003-06-24 + (ptype (cdr (assoc type-spec *simple-array-primitive-types* + :test #'equal)))) + (if (and (consp dims) (null (rest dims)) ptype) + (values (primitive-type-or-lose ptype) + (eq (first dims) '*)) + (any))))) + (union-type + (if (type= type (specifier-type 'list)) + (exactly list) + (let ((types (union-type-types type))) + (multiple-value-bind (res exact) (primitive-type (first types)) + (dolist (type (rest types) (values res exact)) + (multiple-value-bind (ptype ptype-exact) + (primitive-type type) + (unless ptype-exact (setq exact nil)) + (unless (eq ptype res) + (let ((new-ptype (or (maybe-numeric-type-union res ptype) - (maybe-numeric-type-union ptype res)))) - (if new-ptype - (setq res new-ptype) - (return (any))))))))))) + (maybe-numeric-type-union ptype res)))) + (if new-ptype + (setq res new-ptype) + (return (any))))))))))) (intersection-type (let ((types (intersection-type-types type)) (res (any)) @@ -334,21 +334,21 @@ ;; (any). Takes care of undecidable types in ;; intersections with decidable ones. (setq res ptype)))))) - (member-type - (let* ((members (member-type-members type)) - (res (primitive-type-of (first members)))) - (dolist (mem (rest members) (values res nil)) - (let ((ptype (primitive-type-of mem))) - (unless (eq ptype res) - (let ((new-ptype (or (maybe-numeric-type-union res ptype) - (maybe-numeric-type-union ptype res)))) - (if new-ptype - (setq res new-ptype) - (return (any))))))))) - (named-type - (ecase (named-type-name type) - ((t *) (values *backend-t-primitive-type* t)) - ((nil) (any)))) + (member-type + (let* ((members (member-type-members type)) + (res (primitive-type-of (first members)))) + (dolist (mem (rest members) (values res nil)) + (let ((ptype (primitive-type-of mem))) + (unless (eq ptype res) + (let ((new-ptype (or (maybe-numeric-type-union res ptype) + (maybe-numeric-type-union ptype res)))) + (if new-ptype + (setq res new-ptype) + (return (any))))))))) + (named-type + (ecase (named-type-name type) + ((t *) (values *backend-t-primitive-type* t)) + ((nil) (any)))) (character-set-type (let ((pairs (character-set-type-pairs type))) (if (and (= (length pairs) 1) diff --git a/src/compiler/generic/target-core.lisp b/src/compiler/generic/target-core.lisp index 5023124..6b76b18 100644 --- a/src/compiler/generic/target-core.lisp +++ b/src/compiler/generic/target-core.lisp @@ -37,44 +37,44 @@ ;;; vector and node info. (defun make-core-component (component segment length trace-table fixup-notes object) (declare (type component component) - (type sb!assem:segment segment) - (type index length) - (list trace-table fixup-notes) - (type core-object object)) + (type sb!assem:segment segment) + (type index length) + (list trace-table fixup-notes) + (type core-object object)) (without-gcing (let* ((2comp (component-info component)) - (constants (ir2-component-constants 2comp)) - (trace-table (pack-trace-table trace-table)) - (trace-table-len (length trace-table)) - (trace-table-bits (* trace-table-len tt-bits-per-entry)) - (total-length (+ length - (ceiling trace-table-bits sb!vm:n-byte-bits))) - (box-num (- (length constants) sb!vm:code-trace-table-offset-slot)) - (code-obj - (%primitive allocate-code-object box-num total-length)) - (fill-ptr (code-instructions code-obj))) + (constants (ir2-component-constants 2comp)) + (trace-table (pack-trace-table trace-table)) + (trace-table-len (length trace-table)) + (trace-table-bits (* trace-table-len tt-bits-per-entry)) + (total-length (+ length + (ceiling trace-table-bits sb!vm:n-byte-bits))) + (box-num (- (length constants) sb!vm:code-trace-table-offset-slot)) + (code-obj + (%primitive allocate-code-object box-num total-length)) + (fill-ptr (code-instructions code-obj))) (declare (type index box-num total-length)) (sb!assem:on-segment-contents-vectorly segment (lambda (v) - (declare (type (simple-array sb!assem:assembly-unit 1) v)) - (copy-byte-vector-to-system-area v fill-ptr) - (setf fill-ptr (sap+ fill-ptr (length v))))) + (declare (type (simple-array sb!assem:assembly-unit 1) v)) + (copy-byte-vector-to-system-area v fill-ptr) + (setf fill-ptr (sap+ fill-ptr (length v))))) (do-core-fixups code-obj fixup-notes) (dolist (entry (ir2-component-entries 2comp)) - (make-fun-entry entry code-obj object)) + (make-fun-entry entry code-obj object)) (sb!vm:sanctify-for-execution code-obj) (let ((info (debug-info-for-component component))) - (push info (core-object-debug-info object)) - (setf (%code-debug-info code-obj) info)) + (push info (core-object-debug-info object)) + (setf (%code-debug-info code-obj) info)) (setf (code-header-ref code-obj sb!vm:code-trace-table-offset-slot) - length) + length) ;; KLUDGE: the "old" COPY-TO-SYSTEM-AREA automagically worked if ;; somebody changed the number of bytes in a trace table entry. ;; This version is a bit more fragile; if only there were some way @@ -88,18 +88,18 @@ (copy-ub16-to-system-area trace-table 0 fill-ptr 0 trace-table-len) (do ((index sb!vm:code-constants-offset (1+ index))) - ((>= index (length constants))) - (let ((const (aref constants index))) - (etypecase const - (null) - (constant - (setf (code-header-ref code-obj index) - (constant-value const))) - (list - (ecase (car const) - (:entry - (reference-core-fun code-obj index (cdr const) object)) - (:fdefinition - (setf (code-header-ref code-obj index) - (fdefinition-object (cdr const) t)))))))))) + ((>= index (length constants))) + (let ((const (aref constants index))) + (etypecase const + (null) + (constant + (setf (code-header-ref code-obj index) + (constant-value const))) + (list + (ecase (car const) + (:entry + (reference-core-fun code-obj index (cdr const) object)) + (:fdefinition + (setf (code-header-ref code-obj index) + (fdefinition-object (cdr const) t)))))))))) (values)) diff --git a/src/compiler/generic/utils.lisp b/src/compiler/generic/utils.lisp index bbe98d2..7095f61 100644 --- a/src/compiler/generic/utils.lisp +++ b/src/compiler/generic/utils.lisp @@ -28,11 +28,11 @@ (defun static-symbol-offset (symbol) (if symbol (let ((posn (position symbol *static-symbols*))) - (unless posn (error "~S is not a static symbol." symbol)) - (+ (* posn (pad-data-block symbol-size)) - (pad-data-block (1- symbol-size)) - other-pointer-lowtag - (- list-pointer-lowtag))) + (unless posn (error "~S is not a static symbol." symbol)) + (+ (* posn (pad-data-block symbol-size)) + (pad-data-block (1- symbol-size)) + other-pointer-lowtag + (- list-pointer-lowtag))) 0)) ;;; Given a byte offset, OFFSET, return the appropriate static symbol. @@ -40,18 +40,18 @@ (if (zerop offset) nil (multiple-value-bind (n rem) - (truncate (+ offset list-pointer-lowtag (- other-pointer-lowtag) - (- (pad-data-block (1- symbol-size)))) - (pad-data-block symbol-size)) - (unless (and (zerop rem) (<= 0 n (1- (length *static-symbols*)))) - (error "The byte offset ~W is not valid." offset)) - (elt *static-symbols* n)))) + (truncate (+ offset list-pointer-lowtag (- other-pointer-lowtag) + (- (pad-data-block (1- symbol-size)))) + (pad-data-block symbol-size)) + (unless (and (zerop rem) (<= 0 n (1- (length *static-symbols*)))) + (error "The byte offset ~W is not valid." offset)) + (elt *static-symbols* n)))) ;;; Return the (byte) offset from NIL to the start of the fdefn object ;;; for the static function NAME. (defun static-fun-offset (name) (let ((static-syms (length *static-symbols*)) - (static-fun-index (position name *static-funs*))) + (static-fun-index (position name *static-funs*))) (unless static-fun-index (error "~S isn't a static function." name)) (+ (* static-syms (pad-data-block symbol-size)) diff --git a/src/compiler/generic/vm-array.lisp b/src/compiler/generic/vm-array.lisp index d09673d..ba48b3d 100644 --- a/src/compiler/generic/vm-array.lisp +++ b/src/compiler/generic/vm-array.lisp @@ -14,17 +14,17 @@ (in-package "SB!VM") (defstruct (specialized-array-element-type-properties - (:conc-name saetp-) - (:constructor - !make-saetp - (specifier - initial-element-default - n-bits - primitive-type-name - &key (n-pad-elements 0) complex-typecode (importance 0) - &aux (typecode - (symbol-value (symbolicate primitive-type-name "-WIDETAG"))))) - (:copier nil)) + (:conc-name saetp-) + (:constructor + !make-saetp + (specifier + initial-element-default + n-bits + primitive-type-name + &key (n-pad-elements 0) complex-typecode (importance 0) + &aux (typecode + (symbol-value (symbolicate primitive-type-name "-WIDETAG"))))) + (:copier nil)) ;; the element specifier, e.g. BASE-CHAR or (UNSIGNED-BYTE 4) (specifier (missing-arg) :type type-specifier :read-only t) ;; the element type, e.g. # or @@ -58,68 +58,68 @@ (defparameter *specialized-array-element-type-properties* (map 'simple-vector (lambda (args) - (apply #'!make-saetp args)) + (apply #'!make-saetp args)) `(;; Erm. Yeah. There aren't a lot of things that make sense - ;; for an initial element for (ARRAY NIL). -- CSR, 2002-03-07 - (nil #:mu 0 simple-array-nil - :complex-typecode #.sb!vm:complex-vector-nil-widetag - :importance 0) + ;; for an initial element for (ARRAY NIL). -- CSR, 2002-03-07 + (nil #:mu 0 simple-array-nil + :complex-typecode #.sb!vm:complex-vector-nil-widetag + :importance 0) #!-sb-unicode - (character ,(code-char 0) 8 simple-base-string - ;; (SIMPLE-BASE-STRINGs are stored with an extra - ;; trailing #\NULL for convenience in calling out - ;; to C.) - :n-pad-elements 1 - :complex-typecode #.sb!vm:complex-base-string-widetag - :importance 17) + (character ,(code-char 0) 8 simple-base-string + ;; (SIMPLE-BASE-STRINGs are stored with an extra + ;; trailing #\NULL for convenience in calling out + ;; to C.) + :n-pad-elements 1 + :complex-typecode #.sb!vm:complex-base-string-widetag + :importance 17) #!+sb-unicode - (base-char ,(code-char 0) 8 simple-base-string - ;; (SIMPLE-BASE-STRINGs are stored with an extra - ;; trailing #\NULL for convenience in calling out - ;; to C.) - :n-pad-elements 1 - :complex-typecode #.sb!vm:complex-base-string-widetag - :importance 17) + (base-char ,(code-char 0) 8 simple-base-string + ;; (SIMPLE-BASE-STRINGs are stored with an extra + ;; trailing #\NULL for convenience in calling out + ;; to C.) + :n-pad-elements 1 + :complex-typecode #.sb!vm:complex-base-string-widetag + :importance 17) #!+sb-unicode - (character ,(code-char 0) 32 simple-character-string - :n-pad-elements 1 - :complex-typecode #.sb!vm:complex-character-string-widetag - :importance 17) - (single-float 0.0f0 32 simple-array-single-float - :importance 6) - (double-float 0.0d0 64 simple-array-double-float - :importance 5) - (bit 0 1 simple-bit-vector - :complex-typecode #.sb!vm:complex-bit-vector-widetag - :importance 16) - ;; KLUDGE: The fact that these UNSIGNED-BYTE entries come - ;; before their SIGNED-BYTE partners is significant in the - ;; implementation of the compiler; some of the cross-compiler - ;; code (see e.g. COERCE-TO-SMALLEST-ELTYPE in - ;; src/compiler/debug-dump.lisp) attempts to create an array - ;; specialized on (UNSIGNED-BYTE FOO), where FOO could be 7; - ;; (UNSIGNED-BYTE 7) is SUBTYPEP (SIGNED-BYTE 8), so if we're - ;; not careful we could get the wrong specialized array when - ;; we try to FIND-IF, below. -- CSR, 2002-07-08 - ((unsigned-byte 2) 0 2 simple-array-unsigned-byte-2 - :importance 15) - ((unsigned-byte 4) 0 4 simple-array-unsigned-byte-4 - :importance 14) - ((unsigned-byte 7) 0 8 simple-array-unsigned-byte-7 - :importance 13) - ((unsigned-byte 8) 0 8 simple-array-unsigned-byte-8 - :importance 13) - ((unsigned-byte 15) 0 16 simple-array-unsigned-byte-15 - :importance 12) - ((unsigned-byte 16) 0 16 simple-array-unsigned-byte-16 - :importance 12) + (character ,(code-char 0) 32 simple-character-string + :n-pad-elements 1 + :complex-typecode #.sb!vm:complex-character-string-widetag + :importance 17) + (single-float 0.0f0 32 simple-array-single-float + :importance 6) + (double-float 0.0d0 64 simple-array-double-float + :importance 5) + (bit 0 1 simple-bit-vector + :complex-typecode #.sb!vm:complex-bit-vector-widetag + :importance 16) + ;; KLUDGE: The fact that these UNSIGNED-BYTE entries come + ;; before their SIGNED-BYTE partners is significant in the + ;; implementation of the compiler; some of the cross-compiler + ;; code (see e.g. COERCE-TO-SMALLEST-ELTYPE in + ;; src/compiler/debug-dump.lisp) attempts to create an array + ;; specialized on (UNSIGNED-BYTE FOO), where FOO could be 7; + ;; (UNSIGNED-BYTE 7) is SUBTYPEP (SIGNED-BYTE 8), so if we're + ;; not careful we could get the wrong specialized array when + ;; we try to FIND-IF, below. -- CSR, 2002-07-08 + ((unsigned-byte 2) 0 2 simple-array-unsigned-byte-2 + :importance 15) + ((unsigned-byte 4) 0 4 simple-array-unsigned-byte-4 + :importance 14) + ((unsigned-byte 7) 0 8 simple-array-unsigned-byte-7 + :importance 13) + ((unsigned-byte 8) 0 8 simple-array-unsigned-byte-8 + :importance 13) + ((unsigned-byte 15) 0 16 simple-array-unsigned-byte-15 + :importance 12) + ((unsigned-byte 16) 0 16 simple-array-unsigned-byte-16 + :importance 12) #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) - ((unsigned-byte 29) 0 32 simple-array-unsigned-byte-29 - :importance 8) - ((unsigned-byte 31) 0 32 simple-array-unsigned-byte-31 - :importance 11) - ((unsigned-byte 32) 0 32 simple-array-unsigned-byte-32 - :importance 11) + ((unsigned-byte 29) 0 32 simple-array-unsigned-byte-29 + :importance 8) + ((unsigned-byte 31) 0 32 simple-array-unsigned-byte-31 + :importance 11) + ((unsigned-byte 32) 0 32 simple-array-unsigned-byte-32 + :importance 11) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) ((unsigned-byte 60) 0 64 simple-array-unsigned-byte-60 :importance 8) @@ -129,18 +129,18 @@ #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) ((unsigned-byte 64) 0 64 simple-array-unsigned-byte-64 :importance 9) - ((signed-byte 8) 0 8 simple-array-signed-byte-8 - :importance 10) - ((signed-byte 16) 0 16 simple-array-signed-byte-16 - :importance 9) - ;; KLUDGE: See the comment in PRIMITIVE-TYPE-AUX, - ;; compiler/generic/primtype.lisp, for why this is FIXNUM and - ;; not (SIGNED-BYTE 30) + ((signed-byte 8) 0 8 simple-array-signed-byte-8 + :importance 10) + ((signed-byte 16) 0 16 simple-array-signed-byte-16 + :importance 9) + ;; KLUDGE: See the comment in PRIMITIVE-TYPE-AUX, + ;; compiler/generic/primtype.lisp, for why this is FIXNUM and + ;; not (SIGNED-BYTE 30) #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) - (fixnum 0 32 simple-array-signed-byte-30 - :importance 8) - ((signed-byte 32) 0 32 simple-array-signed-byte-32 - :importance 7) + (fixnum 0 32 simple-array-signed-byte-30 + :importance 8) + ((signed-byte 32) 0 32 simple-array-signed-byte-32 + :importance 7) ;; KLUDGE: see above KLUDGE for the 32-bit case #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (fixnum 0 64 simple-array-signed-byte-61 @@ -148,17 +148,17 @@ #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) ((signed-byte 64) 0 64 simple-array-signed-byte-64 :importance 7) - ((complex single-float) #C(0.0f0 0.0f0) 64 - simple-array-complex-single-float - :importance 3) - ((complex double-float) #C(0.0d0 0.0d0) 128 - simple-array-complex-double-float - :importance 2) - #!+long-float - ((complex long-float) #C(0.0l0 0.0l0) #!+x86 192 #!+sparc 256 - simple-array-complex-long-float - :importance 1) - (t 0 #.sb!vm:n-word-bits simple-vector :importance 18)))) + ((complex single-float) #C(0.0f0 0.0f0) 64 + simple-array-complex-single-float + :importance 3) + ((complex double-float) #C(0.0d0 0.0d0) 128 + simple-array-complex-double-float + :importance 2) + #!+long-float + ((complex long-float) #C(0.0l0 0.0l0) #!+x86 192 #!+sparc 256 + simple-array-complex-long-float + :importance 1) + (t 0 #.sb!vm:n-word-bits simple-vector :importance 18)))) (defvar sb!kernel::*specialized-array-element-types* (map 'list @@ -168,13 +168,13 @@ #-sb-xc-host (defun !vm-type-cold-init () (setf sb!kernel::*specialized-array-element-types* - '#.sb!kernel::*specialized-array-element-types*)) + '#.sb!kernel::*specialized-array-element-types*)) (defvar *simple-array-primitive-types* (map 'list (lambda (saetp) - (cons (saetp-specifier saetp) - (saetp-primitive-type-name saetp))) + (cons (saetp-specifier saetp) + (saetp-primitive-type-name saetp))) *specialized-array-element-type-properties*) #!+sb-doc "An alist for mapping simple array element types to their diff --git a/src/compiler/generic/vm-fndb.lisp b/src/compiler/generic/vm-fndb.lisp index e8848a2..93c5677 100644 --- a/src/compiler/generic/vm-fndb.lisp +++ b/src/compiler/generic/vm-fndb.lisp @@ -16,44 +16,44 @@ ;;; Simple TYPEP uses that don't have any standard predicate are ;;; translated into non-standard unary predicates. (defknown (fixnump bignump ratiop - short-float-p single-float-p double-float-p long-float-p - complex-rational-p complex-float-p complex-single-float-p - complex-double-float-p #!+long-float complex-long-float-p - complex-vector-p - base-char-p %standard-char-p %instancep - base-string-p simple-base-string-p + short-float-p single-float-p double-float-p long-float-p + complex-rational-p complex-float-p complex-single-float-p + complex-double-float-p #!+long-float complex-long-float-p + complex-vector-p + base-char-p %standard-char-p %instancep + base-string-p simple-base-string-p #!+sb-unicode character-string-p #!+sb-unicode simple-character-string-p - array-header-p - simple-array-p simple-array-nil-p vector-nil-p - simple-array-unsigned-byte-2-p - simple-array-unsigned-byte-4-p simple-array-unsigned-byte-7-p - simple-array-unsigned-byte-8-p simple-array-unsigned-byte-15-p - simple-array-unsigned-byte-16-p + array-header-p + simple-array-p simple-array-nil-p vector-nil-p + simple-array-unsigned-byte-2-p + simple-array-unsigned-byte-4-p simple-array-unsigned-byte-7-p + simple-array-unsigned-byte-8-p simple-array-unsigned-byte-15-p + simple-array-unsigned-byte-16-p #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) simple-array-unsigned-byte-29-p - simple-array-unsigned-byte-31-p - simple-array-unsigned-byte-32-p + simple-array-unsigned-byte-31-p + simple-array-unsigned-byte-32-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) simple-array-unsigned-byte-60-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) simple-array-unsigned-byte-63-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) simple-array-unsigned-byte-64-p - simple-array-signed-byte-8-p simple-array-signed-byte-16-p + simple-array-signed-byte-8-p simple-array-signed-byte-16-p #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) - simple-array-signed-byte-30-p + simple-array-signed-byte-30-p simple-array-signed-byte-32-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) simple-array-signed-byte-61-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) simple-array-signed-byte-64-p - simple-array-single-float-p simple-array-double-float-p - #!+long-float simple-array-long-float-p - simple-array-complex-single-float-p - simple-array-complex-double-float-p - #!+long-float simple-array-complex-long-float-p - system-area-pointer-p realp + simple-array-single-float-p simple-array-double-float-p + #!+long-float simple-array-long-float-p + simple-array-complex-single-float-p + simple-array-complex-double-float-p + #!+long-float simple-array-complex-long-float-p + system-area-pointer-p realp ;; #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) unsigned-byte-32-p ;; #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) @@ -62,8 +62,8 @@ unsigned-byte-64-p #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) signed-byte-64-p - vector-t-p weak-pointer-p code-component-p lra-p - funcallable-instance-p) + vector-t-p weak-pointer-p code-component-p lra-p + funcallable-instance-p) (t) boolean (movable foldable flushable)) ;;;; miscellaneous "sub-primitives" @@ -217,7 +217,7 @@ (flushable movable)) (defknown (dynamic-space-free-pointer binding-stack-pointer-sap - control-stack-pointer-sap) () + control-stack-pointer-sap) () system-area-pointer (flushable)) @@ -243,11 +243,11 @@ (foldable flushable movable)) (defknown (word-logical-and word-logical-nand - word-logical-or word-logical-nor - word-logical-xor word-logical-eqv - word-logical-andc1 word-logical-andc2 - word-logical-orc1 word-logical-orc2) - (sb!vm:word sb!vm:word) sb!vm:word + word-logical-or word-logical-nor + word-logical-xor word-logical-eqv + word-logical-andc1 word-logical-andc2 + word-logical-orc1 word-logical-orc2) + (sb!vm:word sb!vm:word) sb!vm:word (foldable flushable movable)) (defknown (shift-towards-start shift-towards-end) (sb!vm:word fixnum) @@ -276,13 +276,13 @@ (foldable flushable movable)) (defknown (%add-with-carry %subtract-with-borrow) - (bignum-element-type bignum-element-type (mod 2)) + (bignum-element-type bignum-element-type (mod 2)) (values bignum-element-type (mod 2)) (foldable flushable movable)) (defknown %multiply-and-add - (bignum-element-type bignum-element-type bignum-element-type - &optional bignum-element-type) + (bignum-element-type bignum-element-type bignum-element-type + &optional bignum-element-type) (values bignum-element-type bignum-element-type) (foldable flushable movable)) @@ -309,7 +309,7 @@ (foldable flushable movable)) (defknown (%ashl %ashr %digit-logical-shift-right) - (bignum-element-type (mod #.sb!vm:n-word-bits)) bignum-element-type + (bignum-element-type (mod #.sb!vm:n-word-bits)) bignum-element-type (foldable flushable movable)) ;;;; bit-bashing routines @@ -360,7 +360,7 @@ (defknown fun-subtype (function) (unsigned-byte #.sb!vm:n-widetag-bits) (flushable)) (defknown ((setf fun-subtype)) - ((unsigned-byte #.sb!vm:n-widetag-bits) function) + ((unsigned-byte #.sb!vm:n-widetag-bits) function) (unsigned-byte #.sb!vm:n-widetag-bits) ()) @@ -394,4 +394,4 @@ (defknown %data-vector-and-index (array index) (values (simple-array * (*)) index) - (foldable flushable)) + (foldable flushable)) diff --git a/src/compiler/generic/vm-ir2tran.lisp b/src/compiler/generic/vm-ir2tran.lisp index 09d6a82..1ca4e97 100644 --- a/src/compiler/generic/vm-ir2tran.lisp +++ b/src/compiler/generic/vm-ir2tran.lisp @@ -11,17 +11,17 @@ (defoptimizer ir2-convert-reffer ((object) node block name offset lowtag) (let* ((lvar (node-lvar node)) - (locs (lvar-result-tns lvar - (list *backend-t-primitive-type*))) - (res (first locs))) + (locs (lvar-result-tns lvar + (list *backend-t-primitive-type*))) + (res (first locs))) (vop slot node block (lvar-tn node block object) - name offset lowtag res) + name offset lowtag res) (move-lvar-result node block locs lvar))) (defoptimizer ir2-convert-setter ((object value) node block name offset lowtag) (let ((value-tn (lvar-tn node block value))) (vop set-slot node block (lvar-tn node block object) value-tn - name offset lowtag) + name offset lowtag) (move-lvar-result node block (list value-tn) (node-lvar node)))) ;;; FIXME: Isn't there a name for this which looks less like a typo? @@ -29,56 +29,56 @@ (defoptimizer ir2-convert-setfer ((value object) node block name offset lowtag) (let ((value-tn (lvar-tn node block value))) (vop set-slot node block (lvar-tn node block object) value-tn - name offset lowtag) + name offset lowtag) (move-lvar-result node block (list value-tn) (node-lvar node)))) (defun do-inits (node block name result lowtag inits args) (let ((unbound-marker-tn nil)) (dolist (init inits) (let ((kind (car init)) - (slot (cdr init))) - (vop set-slot node block result - (ecase kind - (:arg - (aver args) - (lvar-tn node block (pop args))) - (:unbound - (or unbound-marker-tn - (setf unbound-marker-tn - (let ((tn (make-restricted-tn - nil - (sc-number-or-lose 'sb!vm::any-reg)))) - (vop make-unbound-marker node block tn) - tn)))) - (:null - (emit-constant nil))) - name slot lowtag)))) + (slot (cdr init))) + (vop set-slot node block result + (ecase kind + (:arg + (aver args) + (lvar-tn node block (pop args))) + (:unbound + (or unbound-marker-tn + (setf unbound-marker-tn + (let ((tn (make-restricted-tn + nil + (sc-number-or-lose 'sb!vm::any-reg)))) + (vop make-unbound-marker node block tn) + tn)))) + (:null + (emit-constant nil))) + name slot lowtag)))) (aver (null args))) (defun do-fixed-alloc (node block name words type lowtag result) (vop fixed-alloc node block name words type lowtag result)) (defoptimizer ir2-convert-fixed-allocation - ((&rest args) node block name words type lowtag inits) + ((&rest args) node block name words type lowtag inits) (let* ((lvar (node-lvar node)) - (locs (lvar-result-tns lvar - (list *backend-t-primitive-type*))) - (result (first locs))) + (locs (lvar-result-tns lvar + (list *backend-t-primitive-type*))) + (result (first locs))) (do-fixed-alloc node block name words type lowtag result) (do-inits node block name result lowtag inits args) (move-lvar-result node block locs lvar))) (defoptimizer ir2-convert-variable-allocation - ((extra &rest args) node block name words type lowtag inits) + ((extra &rest args) node block name words type lowtag inits) (let* ((lvar (node-lvar node)) - (locs (lvar-result-tns lvar - (list *backend-t-primitive-type*))) - (result (first locs))) + (locs (lvar-result-tns lvar + (list *backend-t-primitive-type*))) + (result (first locs))) (if (constant-lvar-p extra) - (let ((words (+ (lvar-value extra) words))) - (do-fixed-alloc node block name words type lowtag result)) - (vop var-alloc node block (lvar-tn node block extra) name words - type lowtag result)) + (let ((words (+ (lvar-value extra) words))) + (do-fixed-alloc node block name words type lowtag result)) + (vop var-alloc node block (lvar-tn node block extra) name words + type lowtag result)) (do-inits node block name result lowtag inits args) (move-lvar-result node block locs lvar))) @@ -89,11 +89,11 @@ ;;; by hand. -- CSR, 2003-05-08 (let ((fun-info (fun-info-or-lose '%set-symbol-value))) (setf (fun-info-ir2-convert fun-info) - (lambda (node block) - (let ((args (basic-combination-args node))) - (destructuring-bind (symbol value) args - (let ((value-tn (lvar-tn node block value))) - (vop set node block - (lvar-tn node block symbol) value-tn) - (move-lvar-result - node block (list value-tn) (node-lvar node)))))))) + (lambda (node block) + (let ((args (basic-combination-args node))) + (destructuring-bind (symbol value) args + (let ((value-tn (lvar-tn node block value))) + (vop set node block + (lvar-tn node block symbol) value-tn) + (move-lvar-result + node block (list value-tn) (node-lvar node)))))))) diff --git a/src/compiler/generic/vm-macs.lisp b/src/compiler/generic/vm-macs.lisp index ae21559..b6bc5a9 100644 --- a/src/compiler/generic/vm-macs.lisp +++ b/src/compiler/generic/vm-macs.lisp @@ -26,16 +26,16 @@ (defun remove-keywords (options keywords) (cond ((null options) nil) - ((member (car options) keywords) - (remove-keywords (cddr options) keywords)) - (t - (list* (car options) (cadr options) - (remove-keywords (cddr options) keywords))))) + ((member (car options) keywords) + (remove-keywords (cddr options) keywords)) + (t + (list* (car options) (cadr options) + (remove-keywords (cddr options) keywords))))) (def!struct (prim-object-slot - (:constructor make-slot (name docs rest-p offset options)) - (:make-load-form-fun just-dump-it-normally) - (:conc-name slot-)) + (:constructor make-slot (name docs rest-p offset options)) + (:make-load-form-fun just-dump-it-normally) + (:conc-name slot-)) (name nil :type symbol) (docs nil :type (or null simple-string)) (rest-p nil :type (member t nil)) @@ -56,72 +56,72 @@ (defun %define-primitive-object (primobj) (let ((name (primitive-object-name primobj))) (setf *primitive-objects* - (cons primobj - (remove name *primitive-objects* - :key #'primitive-object-name :test #'eq))) + (cons primobj + (remove name *primitive-objects* + :key #'primitive-object-name :test #'eq))) name)) (defmacro define-primitive-object - ((name &key lowtag widetag alloc-trans (type t)) - &rest slot-specs) + ((name &key lowtag widetag alloc-trans (type t)) + &rest slot-specs) (collect ((slots) (exports) (constants) (forms) (inits)) (let ((offset (if widetag 1 0)) - (variable-length-p nil)) + (variable-length-p nil)) (dolist (spec slot-specs) - (when variable-length-p - (error "No more slots can follow a :rest-p slot.")) - (destructuring-bind - (slot-name &rest options - &key docs rest-p (length (if rest-p 0 1)) - ((:type slot-type) t) init - (ref-known nil ref-known-p) ref-trans - (set-known nil set-known-p) set-trans - &allow-other-keys) - (if (atom spec) (list spec) spec) - (slots (make-slot slot-name docs rest-p offset - (remove-keywords options - '(:docs :rest-p :length)))) - (let ((offset-sym (symbolicate name "-" slot-name - (if rest-p "-OFFSET" "-SLOT")))) - (constants `(def!constant ,offset-sym ,offset - ,@(when docs (list docs)))) - (exports offset-sym)) - (when ref-trans - (when ref-known-p - (forms `(defknown ,ref-trans (,type) ,slot-type ,ref-known))) - (forms `(def-reffer ,ref-trans ,offset ,lowtag))) - (when set-trans - (when set-known-p - (forms `(defknown ,set-trans - ,(if (listp set-trans) - (list slot-type type) - (list type slot-type)) - ,slot-type - ,set-known))) - (forms `(def-setter ,set-trans ,offset ,lowtag))) - (when init - (inits (cons init offset))) - (when rest-p - (setf variable-length-p t)) - (incf offset length))) + (when variable-length-p + (error "No more slots can follow a :rest-p slot.")) + (destructuring-bind + (slot-name &rest options + &key docs rest-p (length (if rest-p 0 1)) + ((:type slot-type) t) init + (ref-known nil ref-known-p) ref-trans + (set-known nil set-known-p) set-trans + &allow-other-keys) + (if (atom spec) (list spec) spec) + (slots (make-slot slot-name docs rest-p offset + (remove-keywords options + '(:docs :rest-p :length)))) + (let ((offset-sym (symbolicate name "-" slot-name + (if rest-p "-OFFSET" "-SLOT")))) + (constants `(def!constant ,offset-sym ,offset + ,@(when docs (list docs)))) + (exports offset-sym)) + (when ref-trans + (when ref-known-p + (forms `(defknown ,ref-trans (,type) ,slot-type ,ref-known))) + (forms `(def-reffer ,ref-trans ,offset ,lowtag))) + (when set-trans + (when set-known-p + (forms `(defknown ,set-trans + ,(if (listp set-trans) + (list slot-type type) + (list type slot-type)) + ,slot-type + ,set-known))) + (forms `(def-setter ,set-trans ,offset ,lowtag))) + (when init + (inits (cons init offset))) + (when rest-p + (setf variable-length-p t)) + (incf offset length))) (unless variable-length-p - (let ((size (symbolicate name "-SIZE"))) - (constants `(def!constant ,size ,offset)) - (exports size))) + (let ((size (symbolicate name "-SIZE"))) + (constants `(def!constant ,size ,offset)) + (exports size))) (when alloc-trans - (forms `(def-alloc ,alloc-trans ,offset ,variable-length-p ,widetag - ,lowtag ',(inits)))) + (forms `(def-alloc ,alloc-trans ,offset ,variable-length-p ,widetag + ,lowtag ',(inits)))) `(progn - (eval-when (:compile-toplevel :load-toplevel :execute) - (%define-primitive-object - ',(make-primitive-object :name name - :widetag widetag - :lowtag lowtag - :slots (slots) - :size offset - :variable-length-p variable-length-p)) - ,@(constants)) - ,@(forms))))) + (eval-when (:compile-toplevel :load-toplevel :execute) + (%define-primitive-object + ',(make-primitive-object :name name + :widetag widetag + :lowtag lowtag + :slots (slots) + :size offset + :variable-length-p variable-length-p)) + ,@(constants)) + ,@(forms))))) ;;;; stuff for defining reffers and setters diff --git a/src/compiler/generic/vm-tran.lisp b/src/compiler/generic/vm-tran.lisp index 36d4227..06009ee 100644 --- a/src/compiler/generic/vm-tran.lisp +++ b/src/compiler/generic/vm-tran.lisp @@ -45,18 +45,18 @@ (deftransform hairy-data-vector-ref ((string index) (simple-string t)) (let ((ctype (lvar-type string))) (if (array-type-p ctype) - ;; the other transform will kick in, so that's OK - (give-up-ir1-transform) - `(etypecase string - ((simple-array character (*)) (data-vector-ref string index)) + ;; the other transform will kick in, so that's OK + (give-up-ir1-transform) + `(etypecase string + ((simple-array character (*)) (data-vector-ref string index)) #!+sb-unicode - ((simple-array base-char (*)) (data-vector-ref string index)) - ((simple-array nil (*)) (data-vector-ref string index)))))) + ((simple-array base-char (*)) (data-vector-ref string index)) + ((simple-array nil (*)) (data-vector-ref string index)))))) (deftransform hairy-data-vector-ref ((array index) (array t) *) "avoid runtime dispatch on array element type" (let ((element-ctype (extract-upgraded-element-type array)) - (declared-element-ctype (extract-declared-element-type array))) + (declared-element-ctype (extract-declared-element-type array))) (declare (type ctype element-ctype)) (when (eq *wild-type* element-ctype) (give-up-ir1-transform @@ -67,13 +67,13 @@ ;; to hand-expand it ourselves.) (let ((element-type-specifier (type-specifier element-ctype))) `(multiple-value-bind (array index) - (%data-vector-and-index array index) - (declare (type (simple-array ,element-type-specifier 1) array)) - ,(let ((bare-form '(data-vector-ref array index))) - (if (type= element-ctype declared-element-ctype) - bare-form - `(the ,(type-specifier declared-element-ctype) - ,bare-form))))))) + (%data-vector-and-index array index) + (declare (type (simple-array ,element-type-specifier 1) array)) + ,(let ((bare-form '(data-vector-ref array index))) + (if (type= element-ctype declared-element-ctype) + bare-form + `(the ,(type-specifier declared-element-ctype) + ,bare-form))))))) (deftransform data-vector-ref ((array index) (simple-array t)) @@ -93,41 +93,41 @@ index))))) (deftransform hairy-data-vector-set ((string index new-value) - (simple-string t t)) + (simple-string t t)) (let ((ctype (lvar-type string))) (if (array-type-p ctype) - ;; the other transform will kick in, so that's OK - (give-up-ir1-transform) - `(etypecase string - ((simple-array character (*)) - (data-vector-set string index new-value)) + ;; the other transform will kick in, so that's OK + (give-up-ir1-transform) + `(etypecase string + ((simple-array character (*)) + (data-vector-set string index new-value)) #!+sb-unicode - ((simple-array base-char (*)) - (data-vector-set string index new-value)) - ((simple-array nil (*)) - (data-vector-set string index new-value)))))) + ((simple-array base-char (*)) + (data-vector-set string index new-value)) + ((simple-array nil (*)) + (data-vector-set string index new-value)))))) (deftransform hairy-data-vector-set ((array index new-value) - (array t t) - *) + (array t t) + *) "avoid runtime dispatch on array element type" (let ((element-ctype (extract-upgraded-element-type array)) - (declared-element-ctype (extract-declared-element-type array))) + (declared-element-ctype (extract-declared-element-type array))) (declare (type ctype element-ctype)) (when (eq *wild-type* element-ctype) (give-up-ir1-transform "Upgraded element type of array is not known at compile time.")) (let ((element-type-specifier (type-specifier element-ctype))) `(multiple-value-bind (array index) - (%data-vector-and-index array index) - (declare (type (simple-array ,element-type-specifier 1) array) - (type ,element-type-specifier new-value)) - ,(if (type= element-ctype declared-element-ctype) - '(data-vector-set array index new-value) - `(truly-the ,(type-specifier declared-element-ctype) - (data-vector-set array index - (the ,(type-specifier declared-element-ctype) - new-value)))))))) + (%data-vector-and-index array index) + (declare (type (simple-array ,element-type-specifier 1) array) + (type ,element-type-specifier new-value)) + ,(if (type= element-ctype declared-element-ctype) + '(data-vector-set array index new-value) + `(truly-the ,(type-specifier declared-element-ctype) + (data-vector-set array index + (the ,(type-specifier declared-element-ctype) + new-value)))))))) (deftransform data-vector-set ((array index new-value) (simple-array t t)) @@ -157,8 +157,8 @@ index))))) (deftransform %data-vector-and-index ((%array %index) - (simple-array t) - *) + (simple-array t) + *) ;; KLUDGE: why the percent signs? Well, ARRAY and INDEX are ;; respectively exported from the CL and SB!INT packages, which ;; means that they're visible to all sorts of things. If the @@ -189,27 +189,27 @@ (macrolet ((frob (type bits) (let ((elements-per-word (truncate sb!vm:n-word-bits bits))) - `(progn - (deftransform data-vector-ref ((vector index) - (,type *)) - `(multiple-value-bind (word bit) - (floor index ,',elements-per-word) - (ldb ,(ecase sb!vm:target-byte-order - (:little-endian '(byte ,bits (* bit ,bits))) - (:big-endian '(byte ,bits (- sb!vm:n-word-bits - (* (1+ bit) ,bits))))) - (%raw-bits vector (+ word sb!vm:vector-data-offset))))) - (deftransform data-vector-set ((vector index new-value) - (,type * *)) - `(multiple-value-bind (word bit) - (floor index ,',elements-per-word) - (setf (ldb ,(ecase sb!vm:target-byte-order - (:little-endian '(byte ,bits (* bit ,bits))) - (:big-endian - '(byte ,bits (- sb!vm:n-word-bits - (* (1+ bit) ,bits))))) - (%raw-bits vector (+ word sb!vm:vector-data-offset))) - new-value))))))) + `(progn + (deftransform data-vector-ref ((vector index) + (,type *)) + `(multiple-value-bind (word bit) + (floor index ,',elements-per-word) + (ldb ,(ecase sb!vm:target-byte-order + (:little-endian '(byte ,bits (* bit ,bits))) + (:big-endian '(byte ,bits (- sb!vm:n-word-bits + (* (1+ bit) ,bits))))) + (%raw-bits vector (+ word sb!vm:vector-data-offset))))) + (deftransform data-vector-set ((vector index new-value) + (,type * *)) + `(multiple-value-bind (word bit) + (floor index ,',elements-per-word) + (setf (ldb ,(ecase sb!vm:target-byte-order + (:little-endian '(byte ,bits (* bit ,bits))) + (:big-endian + '(byte ,bits (- sb!vm:n-word-bits + (* (1+ bit) ,bits))))) + (%raw-bits vector (+ word sb!vm:vector-data-offset))) + new-value))))))) (frob simple-bit-vector 1) (frob (simple-array (unsigned-byte 2) (*)) 2) (frob (simple-array (unsigned-byte 4) (*)) 4)) @@ -224,46 +224,46 @@ (macrolet ((def (bitfun wordfun) `(deftransform ,bitfun ((bit-array-1 bit-array-2 result-bit-array) (simple-bit-vector - simple-bit-vector - simple-bit-vector) - * + simple-bit-vector + simple-bit-vector) + * :node node :policy (>= speed space)) `(progn ,@(unless (policy node (zerop safety)) '((unless (= (length bit-array-1) - (length bit-array-2) + (length bit-array-2) (length result-bit-array)) (error "Argument and/or result bit arrays are not the same length:~ ~% ~S~% ~S ~% ~S" bit-array-1 - bit-array-2 - result-bit-array)))) - (let ((length (length result-bit-array))) - (if (= length 0) - ;; We avoid doing anything to 0-length - ;; bit-vectors, or rather, the memory that - ;; follows them. Other divisible-by-32 cases - ;; are handled by the (1- length), below. - ;; CSR, 2002-04-24 - result-bit-array - (do ((index sb!vm:vector-data-offset (1+ index)) - (end-1 (+ sb!vm:vector-data-offset - ;; bit-vectors of length 1-32 - ;; need precisely one (SETF - ;; %RAW-BITS), done here in the - ;; epilogue. - CSR, 2002-04-24 - (truncate (truly-the index (1- length)) - sb!vm:n-word-bits)))) - ((= index end-1) - (setf (%raw-bits result-bit-array index) - (,',wordfun (%raw-bits bit-array-1 index) - (%raw-bits bit-array-2 index))) - result-bit-array) - (declare (optimize (speed 3) (safety 0)) - (type index index end-1)) - (setf (%raw-bits result-bit-array index) - (,',wordfun (%raw-bits bit-array-1 index) - (%raw-bits bit-array-2 index)))))))))) + bit-array-2 + result-bit-array)))) + (let ((length (length result-bit-array))) + (if (= length 0) + ;; We avoid doing anything to 0-length + ;; bit-vectors, or rather, the memory that + ;; follows them. Other divisible-by-32 cases + ;; are handled by the (1- length), below. + ;; CSR, 2002-04-24 + result-bit-array + (do ((index sb!vm:vector-data-offset (1+ index)) + (end-1 (+ sb!vm:vector-data-offset + ;; bit-vectors of length 1-32 + ;; need precisely one (SETF + ;; %RAW-BITS), done here in the + ;; epilogue. - CSR, 2002-04-24 + (truncate (truly-the index (1- length)) + sb!vm:n-word-bits)))) + ((= index end-1) + (setf (%raw-bits result-bit-array index) + (,',wordfun (%raw-bits bit-array-1 index) + (%raw-bits bit-array-2 index))) + result-bit-array) + (declare (optimize (speed 3) (safety 0)) + (type index index end-1)) + (setf (%raw-bits result-bit-array index) + (,',wordfun (%raw-bits bit-array-1 index) + (%raw-bits bit-array-2 index)))))))))) (def bit-and word-logical-and) (def bit-ior word-logical-or) (def bit-xor word-logical-xor) @@ -276,75 +276,75 @@ (def bit-orc2 word-logical-orc2)) (deftransform bit-not - ((bit-array result-bit-array) - (simple-bit-vector simple-bit-vector) * - :node node :policy (>= speed space)) + ((bit-array result-bit-array) + (simple-bit-vector simple-bit-vector) * + :node node :policy (>= speed space)) `(progn ,@(unless (policy node (zerop safety)) - '((unless (= (length bit-array) - (length result-bit-array)) - (error "Argument and result bit arrays are not the same length:~ + '((unless (= (length bit-array) + (length result-bit-array)) + (error "Argument and result bit arrays are not the same length:~ ~% ~S~% ~S" - bit-array result-bit-array)))) + bit-array result-bit-array)))) (let ((length (length result-bit-array))) (if (= length 0) - ;; We avoid doing anything to 0-length bit-vectors, or rather, - ;; the memory that follows them. Other divisible-by - ;; n-word-bits cases are handled by the (1- length), below. - ;; CSR, 2002-04-24 - result-bit-array - (do ((index sb!vm:vector-data-offset (1+ index)) - (end-1 (+ sb!vm:vector-data-offset - ;; bit-vectors of length 1 to n-word-bits need - ;; precisely one (SETF %RAW-BITS), done here in - ;; the epilogue. - CSR, 2002-04-24 - (truncate (truly-the index (1- length)) - sb!vm:n-word-bits)))) - ((= index end-1) - (setf (%raw-bits result-bit-array index) - (word-logical-not (%raw-bits bit-array index))) - result-bit-array) - (declare (optimize (speed 3) (safety 0)) - (type index index end-1)) - (setf (%raw-bits result-bit-array index) - (word-logical-not (%raw-bits bit-array index)))))))) + ;; We avoid doing anything to 0-length bit-vectors, or rather, + ;; the memory that follows them. Other divisible-by + ;; n-word-bits cases are handled by the (1- length), below. + ;; CSR, 2002-04-24 + result-bit-array + (do ((index sb!vm:vector-data-offset (1+ index)) + (end-1 (+ sb!vm:vector-data-offset + ;; bit-vectors of length 1 to n-word-bits need + ;; precisely one (SETF %RAW-BITS), done here in + ;; the epilogue. - CSR, 2002-04-24 + (truncate (truly-the index (1- length)) + sb!vm:n-word-bits)))) + ((= index end-1) + (setf (%raw-bits result-bit-array index) + (word-logical-not (%raw-bits bit-array index))) + result-bit-array) + (declare (optimize (speed 3) (safety 0)) + (type index index end-1)) + (setf (%raw-bits result-bit-array index) + (word-logical-not (%raw-bits bit-array index)))))))) (deftransform bit-vector-= ((x y) (simple-bit-vector simple-bit-vector)) `(and (= (length x) (length y)) (let ((length (length x))) - (or (= length 0) - (do* ((i sb!vm:vector-data-offset (+ i 1)) - (end-1 (+ sb!vm:vector-data-offset - (floor (1- length) sb!vm:n-word-bits)))) - ((= i end-1) - (let* ((extra (1+ (mod (1- length) sb!vm:n-word-bits))) - (mask (ash #.(1- (ash 1 sb!vm:n-word-bits)) - (- extra sb!vm:n-word-bits))) - (numx - (logand - (ash mask - ,(ecase sb!c:*backend-byte-order* - (:little-endian 0) - (:big-endian - '(- sb!vm:n-word-bits extra)))) - (%raw-bits x i))) - (numy - (logand - (ash mask - ,(ecase sb!c:*backend-byte-order* - (:little-endian 0) - (:big-endian - '(- sb!vm:n-word-bits extra)))) - (%raw-bits y i)))) - (declare (type (integer 1 #.sb!vm:n-word-bits) extra) - (type sb!vm:word mask numx numy)) - (= numx numy))) - (declare (type index i end-1)) - (let ((numx (%raw-bits x i)) - (numy (%raw-bits y i))) - (declare (type sb!vm:word numx numy)) - (unless (= numx numy) - (return nil)))))))) + (or (= length 0) + (do* ((i sb!vm:vector-data-offset (+ i 1)) + (end-1 (+ sb!vm:vector-data-offset + (floor (1- length) sb!vm:n-word-bits)))) + ((= i end-1) + (let* ((extra (1+ (mod (1- length) sb!vm:n-word-bits))) + (mask (ash #.(1- (ash 1 sb!vm:n-word-bits)) + (- extra sb!vm:n-word-bits))) + (numx + (logand + (ash mask + ,(ecase sb!c:*backend-byte-order* + (:little-endian 0) + (:big-endian + '(- sb!vm:n-word-bits extra)))) + (%raw-bits x i))) + (numy + (logand + (ash mask + ,(ecase sb!c:*backend-byte-order* + (:little-endian 0) + (:big-endian + '(- sb!vm:n-word-bits extra)))) + (%raw-bits y i)))) + (declare (type (integer 1 #.sb!vm:n-word-bits) extra) + (type sb!vm:word mask numx numy)) + (= numx numy))) + (declare (type index i end-1)) + (let ((numx (%raw-bits x i)) + (numy (%raw-bits y i))) + (declare (type sb!vm:word numx numy)) + (unless (= numx numy) + (return nil)))))))) (deftransform count ((item sequence) (bit simple-bit-vector) * :policy (>= speed space)) @@ -358,14 +358,14 @@ sb!vm:n-word-bits)))) ((= index end-1) (let* ((extra (1+ (mod (1- length) sb!vm:n-word-bits))) - (mask (ash #.(1- (ash 1 sb!vm:n-word-bits)) - (- extra sb!vm:n-word-bits))) - (bits (logand (ash mask - ,(ecase sb!c:*backend-byte-order* - (:little-endian 0) - (:big-endian - '(- sb!vm:n-word-bits extra)))) - (%raw-bits sequence index)))) + (mask (ash #.(1- (ash 1 sb!vm:n-word-bits)) + (- extra sb!vm:n-word-bits))) + (bits (logand (ash mask + ,(ecase sb!c:*backend-byte-order* + (:little-endian 0) + (:big-endian + '(- sb!vm:n-word-bits extra)))) + (%raw-bits sequence index)))) (declare (type (integer 1 #.sb!vm:n-word-bits) extra)) (declare (type sb!vm:word mask bits)) ;; could consider LOGNOT for the zero case instead of @@ -378,7 +378,7 @@ (- extra (logcount bits)) (logcount bits)))))) (declare (type index index count end-1) - (optimize (speed 3) (safety 0))) + (optimize (speed 3) (safety 0))) (incf count ,(if (constant-lvar-p item) (if (zerop (lvar-value item)) '(- sb!vm:n-word-bits (logcount (%raw-bits sequence index))) @@ -388,56 +388,56 @@ (logcount (%raw-bits sequence index))))))))) (deftransform fill ((sequence item) (simple-bit-vector bit) * - :policy (>= speed space)) + :policy (>= speed space)) (let ((value (if (constant-lvar-p item) - (if (= (lvar-value item) 0) - 0 - #.(1- (ash 1 sb!vm:n-word-bits))) - `(if (= item 0) 0 #.(1- (ash 1 sb!vm:n-word-bits)))))) + (if (= (lvar-value item) 0) + 0 + #.(1- (ash 1 sb!vm:n-word-bits))) + `(if (= item 0) 0 #.(1- (ash 1 sb!vm:n-word-bits)))))) `(let ((length (length sequence)) - (value ,value)) + (value ,value)) (if (= length 0) - sequence - (do ((index sb!vm:vector-data-offset (1+ index)) - (end-1 (+ sb!vm:vector-data-offset - ;; bit-vectors of length 1 to n-word-bits need - ;; precisely one (SETF %RAW-BITS), done here + sequence + (do ((index sb!vm:vector-data-offset (1+ index)) + (end-1 (+ sb!vm:vector-data-offset + ;; bit-vectors of length 1 to n-word-bits need + ;; precisely one (SETF %RAW-BITS), done here ;; in the epilogue. - CSR, 2002-04-24 - (truncate (truly-the index (1- length)) - sb!vm:n-word-bits)))) - ((= index end-1) - (setf (%raw-bits sequence index) value) - sequence) - (declare (optimize (speed 3) (safety 0)) - (type index index end-1)) - (setf (%raw-bits sequence index) value)))))) + (truncate (truly-the index (1- length)) + sb!vm:n-word-bits)))) + ((= index end-1) + (setf (%raw-bits sequence index) value) + sequence) + (declare (optimize (speed 3) (safety 0)) + (type index index end-1)) + (setf (%raw-bits sequence index) value)))))) (deftransform fill ((sequence item) (simple-base-string base-char) * - :policy (>= speed space)) + :policy (>= speed space)) (let ((value (if (constant-lvar-p item) - (let* ((char (lvar-value item)) - (code (sb!xc:char-code char)) + (let* ((char (lvar-value item)) + (code (sb!xc:char-code char)) (accum 0)) (dotimes (i sb!vm:n-word-bytes accum) (setf accum (logior accum (ash code (* 8 i)))))) - `(let ((code (sb!xc:char-code item))) + `(let ((code (sb!xc:char-code item))) (logior ,@(loop for i from 0 below sb!vm:n-word-bytes collect `(ash code ,(* 8 i)))))))) `(let ((length (length sequence)) - (value ,value)) + (value ,value)) (multiple-value-bind (times rem) - (truncate length sb!vm:n-word-bytes) - (do ((index sb!vm:vector-data-offset (1+ index)) - (end (+ times sb!vm:vector-data-offset))) - ((= index end) - (let ((place (* times sb!vm:n-word-bytes))) - (declare (fixnum place)) - (dotimes (j rem sequence) - (declare (index j)) - (setf (schar sequence (the index (+ place j))) item)))) - (declare (optimize (speed 3) (safety 0)) - (type index index)) - (setf (%raw-bits sequence index) value)))))) + (truncate length sb!vm:n-word-bytes) + (do ((index sb!vm:vector-data-offset (1+ index)) + (end (+ times sb!vm:vector-data-offset))) + ((= index end) + (let ((place (* times sb!vm:n-word-bytes))) + (declare (fixnum place)) + (dotimes (j rem sequence) + (declare (index j)) + (setf (schar sequence (the index (+ place j))) item)))) + (declare (optimize (speed 3) (safety 0)) + (type index index)) + (setf (%raw-bits sequence index) value)))))) ;;;; %BYTE-BLT @@ -449,11 +449,11 @@ ;;; SB!KERNEL and SB!SYS (e.g. i/o code). It's not clear that it's the ;;; ideal interface, though, and it probably deserves some thought. (deftransform %byte-blt ((src src-start dst dst-start dst-end) - ((or (simple-unboxed-array (*)) system-area-pointer) - index - (or (simple-unboxed-array (*)) system-area-pointer) - index - index)) + ((or (simple-unboxed-array (*)) system-area-pointer) + index + (or (simple-unboxed-array (*)) system-area-pointer) + index + index)) ;; FIXME: CMU CL had a hairier implementation of this (back when it ;; was still called (%PRIMITIVE BYTE-BLT). It had the small problem ;; that it didn't work for large (>16M) values of SRC-START or @@ -463,19 +463,19 @@ ;; acceptable for SQRT and COS, it's acceptable here, but this ;; should probably be checked. -- WHN '(flet ((sapify (thing) - (etypecase thing - (system-area-pointer thing) - ;; FIXME: The code here rather relies on the simple - ;; unboxed array here having byte-sized entries. That - ;; should be asserted explicitly, I just haven't found - ;; a concise way of doing it. (It would be nice to - ;; declare it in the DEFKNOWN too.) - ((simple-unboxed-array (*)) (vector-sap thing))))) + (etypecase thing + (system-area-pointer thing) + ;; FIXME: The code here rather relies on the simple + ;; unboxed array here having byte-sized entries. That + ;; should be asserted explicitly, I just haven't found + ;; a concise way of doing it. (It would be nice to + ;; declare it in the DEFKNOWN too.) + ((simple-unboxed-array (*)) (vector-sap thing))))) (declare (inline sapify)) (without-gcing (memmove (sap+ (sapify dst) dst-start) - (sap+ (sapify src) src-start) - (- dst-end dst-start))) + (sap+ (sapify src) src-start) + (- dst-end dst-start))) (values))) ;;;; transforms for EQL of floating point values @@ -485,7 +485,7 @@ (deftransform eql ((x y) (double-float double-float)) '(and (= (double-float-low-bits x) (double-float-low-bits y)) - (= (double-float-high-bits x) (double-float-high-bits y)))) + (= (double-float-high-bits x) (double-float-high-bits y)))) ;;;; modular functions @@ -498,17 +498,17 @@ (let ((type (ecase class (:unsigned 'unsigned-byte) (:signed 'signed-byte)))) - `(progn - (defknown ,name (integer (integer 0)) (,type ,width) - (foldable flushable movable)) - (define-modular-fun-optimizer ash ((integer count) ,class :width width) - (when (and (<= width ,width) - (or (and (constant-lvar-p count) - (plusp (lvar-value count))) - (csubtypep (lvar-type count) - (specifier-type '(and unsigned-byte fixnum))))) - (cut-to-width integer ,class width) - ',name)) + `(progn + (defknown ,name (integer (integer 0)) (,type ,width) + (foldable flushable movable)) + (define-modular-fun-optimizer ash ((integer count) ,class :width width) + (when (and (<= width ,width) + (or (and (constant-lvar-p count) + (plusp (lvar-value count))) + (csubtypep (lvar-type count) + (specifier-type '(and unsigned-byte fixnum))))) + (cut-to-width integer ,class width) + ',name)) (setf (gethash ',name (modular-class-versions (find-modular-class ',class))) `(ash ,',width)))))) ;; This should really be dependent on SB!VM:N-WORD-BITS, but since we @@ -574,38 +574,38 @@ (defun ub32-strength-reduce-constant-multiply (arg num) (declare (type (unsigned-byte 32) num)) (let ((adds 0) (shifts 0) - (result nil) first-one) + (result nil) first-one) (labels ((add (next-factor) - (setf result - (if result + (setf result + (if result (progn (incf adds) `(+ ,result ,next-factor)) next-factor)))) (declare (inline add)) (dotimes (bitpos 32) - (if first-one - (when (not (logbitp bitpos num)) - (add (if (= (1+ first-one) bitpos) - ;; There is only a single bit in the string. - (progn (incf shifts) `(ash ,arg ,first-one)) - ;; There are at least two. - (progn - (incf adds) - (incf shifts 2) - `(- (ash ,arg ,bitpos) - (ash ,arg ,first-one))))) - (setf first-one nil)) - (when (logbitp bitpos num) - (setf first-one bitpos)))) + (if first-one + (when (not (logbitp bitpos num)) + (add (if (= (1+ first-one) bitpos) + ;; There is only a single bit in the string. + (progn (incf shifts) `(ash ,arg ,first-one)) + ;; There are at least two. + (progn + (incf adds) + (incf shifts 2) + `(- (ash ,arg ,bitpos) + (ash ,arg ,first-one))))) + (setf first-one nil)) + (when (logbitp bitpos num) + (setf first-one bitpos)))) (when first-one - (cond ((= first-one 31)) - ((= first-one 30) (incf shifts) (add `(ash ,arg 30))) - (t - (incf shifts 2) - (incf adds) - (add `(- (ash ,arg 31) - (ash ,arg ,first-one))))) - (incf shifts) - (add `(ash ,arg 31)))) + (cond ((= first-one 31)) + ((= first-one 30) (incf shifts) (add `(ash ,arg 30))) + (t + (incf shifts 2) + (incf adds) + (add `(- (ash ,arg 31) + (ash ,arg ,first-one))))) + (incf shifts) + (add `(ash ,arg 31)))) (values (if (plusp adds) `(logand ,result #.(1- (ash 1 32))) ; using modular arithmetic result) diff --git a/src/compiler/generic/vm-type.lisp b/src/compiler/generic/vm-type.lisp index 85c1b0b..f8494cf 100644 --- a/src/compiler/generic/vm-type.lisp +++ b/src/compiler/generic/vm-type.lisp @@ -84,14 +84,14 @@ (collect ((types (list 'or))) (dolist (type *specialized-array-element-types*) (when (subtypep type '(or integer character float (complex float))) - (types `(array ,type ,dims)))) + (types `(array ,type ,dims)))) (types))) (sb!xc:deftype simple-unboxed-array (&optional dims) (collect ((types (list 'or))) (dolist (type *specialized-array-element-types*) (when (subtypep type '(or integer character float (complex float))) - (types `(simple-array ,type ,dims)))) + (types `(simple-array ,type ,dims)))) (types))) ;;; Return the symbol that describes the format of FLOAT. @@ -110,24 +110,24 @@ (defun specialize-array-type (type) (let ((eltype (array-type-element-type type))) (setf (array-type-specialized-element-type type) - (if (or (eq eltype *wild-type*) - ;; This is slightly dubious, but not as dubious as - ;; assuming that the upgraded-element-type should be - ;; equal to T, given the way that the AREF - ;; DERIVE-TYPE optimizer works. -- CSR, 2002-08-19 - (unknown-type-p eltype)) - *wild-type* - (dolist (stype-name *specialized-array-element-types* - *universal-type*) - ;; FIXME: Mightn't it be better to have - ;; *SPECIALIZED-ARRAY-ELEMENT-TYPES* be stored as precalculated - ;; SPECIFIER-TYPE results, instead of having to calculate - ;; them on the fly this way? (Call the new array - ;; *SPECIALIZED-ARRAY-ELEMENT-SPECIFIER-TYPES* or something..) - (let ((stype (specifier-type stype-name))) - (aver (not (unknown-type-p stype))) - (when (csubtypep eltype stype) - (return stype)))))) + (if (or (eq eltype *wild-type*) + ;; This is slightly dubious, but not as dubious as + ;; assuming that the upgraded-element-type should be + ;; equal to T, given the way that the AREF + ;; DERIVE-TYPE optimizer works. -- CSR, 2002-08-19 + (unknown-type-p eltype)) + *wild-type* + (dolist (stype-name *specialized-array-element-types* + *universal-type*) + ;; FIXME: Mightn't it be better to have + ;; *SPECIALIZED-ARRAY-ELEMENT-TYPES* be stored as precalculated + ;; SPECIFIER-TYPE results, instead of having to calculate + ;; them on the fly this way? (Call the new array + ;; *SPECIALIZED-ARRAY-ELEMENT-SPECIFIER-TYPES* or something..) + (let ((stype (specifier-type stype-name))) + (aver (not (unknown-type-p stype))) + (when (csubtypep eltype stype) + (return stype)))))) type)) (defun sb!xc:upgraded-array-element-type (spec &optional environment) @@ -138,7 +138,7 @@ (if (unknown-type-p (specifier-type spec)) (error "undefined type: ~S" spec) (type-specifier (array-type-specialized-element-type - (specifier-type `(array ,spec)))))) + (specifier-type `(array ,spec)))))) (defun sb!xc:upgraded-complex-part-type (spec &optional environment) #!+sb-doc @@ -168,10 +168,10 @@ ;;; includes the given type. (defun containing-integer-type (subtype) (dolist (type '(fixnum - (signed-byte 32) - (unsigned-byte 32) - integer) - (error "~S isn't an integer type?" subtype)) + (signed-byte 32) + (unsigned-byte 32) + integer) + (error "~S isn't an integer type?" subtype)) (when (csubtypep subtype (specifier-type type)) (return type)))) @@ -182,20 +182,20 @@ (typecase type (cons-type (if (type= type (specifier-type 'cons)) - 'sb!c:check-cons - nil)) + 'sb!c:check-cons + nil)) (built-in-classoid (if (type= type (specifier-type 'symbol)) - 'sb!c:check-symbol - nil)) + 'sb!c:check-symbol + nil)) (numeric-type (cond ((type= type (specifier-type 'fixnum)) - 'sb!c:check-fixnum) - ((type= type (specifier-type '(signed-byte 32))) - 'sb!c:check-signed-byte-32) - ((type= type (specifier-type '(unsigned-byte 32))) - 'sb!c:check-unsigned-byte-32) - (t nil))) + 'sb!c:check-fixnum) + ((type= type (specifier-type '(signed-byte 32))) + 'sb!c:check-signed-byte-32) + ((type= type (specifier-type '(unsigned-byte 32))) + 'sb!c:check-unsigned-byte-32) + (t nil))) (fun-type 'sb!c:check-fun) (t diff --git a/src/compiler/generic/vm-typetran.lisp b/src/compiler/generic/vm-typetran.lisp index 2595ed0..8446c0e 100644 --- a/src/compiler/generic/vm-typetran.lisp +++ b/src/compiler/generic/vm-typetran.lisp @@ -36,62 +36,62 @@ (define-type-predicate simple-array-p simple-array) (define-type-predicate simple-array-nil-p (simple-array nil (*))) (define-type-predicate simple-array-unsigned-byte-2-p - (simple-array (unsigned-byte 2) (*))) + (simple-array (unsigned-byte 2) (*))) (define-type-predicate simple-array-unsigned-byte-4-p - (simple-array (unsigned-byte 4) (*))) + (simple-array (unsigned-byte 4) (*))) (define-type-predicate simple-array-unsigned-byte-7-p (simple-array (unsigned-byte 7) (*))) (define-type-predicate simple-array-unsigned-byte-8-p - (simple-array (unsigned-byte 8) (*))) + (simple-array (unsigned-byte 8) (*))) (define-type-predicate simple-array-unsigned-byte-15-p (simple-array (unsigned-byte 15) (*))) (define-type-predicate simple-array-unsigned-byte-16-p - (simple-array (unsigned-byte 16) (*))) + (simple-array (unsigned-byte 16) (*))) #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-unsigned-byte-29-p (simple-array (unsigned-byte 29) (*))) (define-type-predicate simple-array-unsigned-byte-31-p (simple-array (unsigned-byte 31) (*))) (define-type-predicate simple-array-unsigned-byte-32-p - (simple-array (unsigned-byte 32) (*))) + (simple-array (unsigned-byte 32) (*))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-unsigned-byte-60-p - (simple-array (unsigned-byte 60) (*))) + (simple-array (unsigned-byte 60) (*))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-unsigned-byte-63-p - (simple-array (unsigned-byte 63) (*))) + (simple-array (unsigned-byte 63) (*))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-unsigned-byte-64-p - (simple-array (unsigned-byte 64) (*))) + (simple-array (unsigned-byte 64) (*))) (define-type-predicate simple-array-signed-byte-8-p - (simple-array (signed-byte 8) (*))) + (simple-array (signed-byte 8) (*))) (define-type-predicate simple-array-signed-byte-16-p - (simple-array (signed-byte 16) (*))) + (simple-array (signed-byte 16) (*))) #!+#.(cl:if (cl:= 32 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-signed-byte-30-p - (simple-array (signed-byte 30) (*))) + (simple-array (signed-byte 30) (*))) (define-type-predicate simple-array-signed-byte-32-p - (simple-array (signed-byte 32) (*))) + (simple-array (signed-byte 32) (*))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-signed-byte-61-p - (simple-array (signed-byte 61) (*))) + (simple-array (signed-byte 61) (*))) #!+#.(cl:if (cl:= 64 sb!vm:n-word-bits) '(and) '(or)) (define-type-predicate simple-array-signed-byte-64-p - (simple-array (signed-byte 64) (*))) + (simple-array (signed-byte 64) (*))) (define-type-predicate simple-array-single-float-p - (simple-array single-float (*))) + (simple-array single-float (*))) (define-type-predicate simple-array-double-float-p - (simple-array double-float (*))) + (simple-array double-float (*))) #!+long-float (define-type-predicate simple-array-long-float-p - (simple-array long-float (*))) + (simple-array long-float (*))) (define-type-predicate simple-array-complex-single-float-p - (simple-array (complex single-float) (*))) + (simple-array (complex single-float) (*))) (define-type-predicate simple-array-complex-double-float-p - (simple-array (complex double-float) (*))) + (simple-array (complex double-float) (*))) #!+long-float (define-type-predicate simple-array-complex-long-float-p - (simple-array (complex long-float) (*))) + (simple-array (complex long-float) (*))) (define-type-predicate simple-base-string-p simple-base-string) #!+sb-unicode (define-type-predicate simple-character-string-p (simple-array character (*))) diff --git a/version.lisp-expr b/version.lisp-expr index 6b494da..ee75044 100644 --- a/version.lisp-expr +++ b/version.lisp-expr @@ -17,4 +17,4 @@ ;;; checkins which aren't released. (And occasionally for internal ;;; versions, especially for internal versions off the main CVS ;;; branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".) -"0.9.2.43" +"0.9.2.44"