1 ;;;; miscellaneous VM definition noise for the x86-64
3 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
14 ;;; the size of an INTEGER representation of a SYSTEM-AREA-POINTER, i.e.
15 ;;; size of a native memory address
16 (deftype sap-int () '(unsigned-byte 64))
20 (eval-when (:compile-toplevel :load-toplevel :execute)
21 (defvar *byte-register-names* (make-array 32 :initial-element nil))
22 (defvar *word-register-names* (make-array 16 :initial-element nil))
23 (defvar *dword-register-names* (make-array 16 :initial-element nil))
24 (defvar *qword-register-names* (make-array 32 :initial-element nil))
25 (defvar *float-register-names* (make-array 16 :initial-element nil)))
27 (macrolet ((defreg (name offset size)
28 (let ((offset-sym (symbolicate name "-OFFSET"))
29 (names-vector (symbolicate "*" size "-REGISTER-NAMES*")))
31 (eval-when (:compile-toplevel :load-toplevel :execute)
32 ;; EVAL-WHEN is necessary because stuff like #.EAX-OFFSET
33 ;; (in the same file) depends on compile-time evaluation
34 ;; of the DEFCONSTANT. -- AL 20010224
35 (def!constant ,offset-sym ,offset))
36 (setf (svref ,names-vector ,offset-sym)
37 ,(symbol-name name)))))
38 ;; FIXME: It looks to me as though DEFREGSET should also
39 ;; define the related *FOO-REGISTER-NAMES* variable.
40 (defregset (name &rest regs)
41 `(eval-when (:compile-toplevel :load-toplevel :execute)
43 (list ,@(mapcar (lambda (name)
44 (symbolicate name "-OFFSET"))
49 ;; Note: the encoding here is different than that used by the chip.
50 ;; We use this encoding so that the compiler thinks that AX (and
51 ;; EAX) overlap AL and AH instead of AL and CL.
53 ;; High-byte are registers disabled on AMD64, since they can't be
54 ;; encoded for an op that has a REX-prefix and we don't want to
55 ;; add special cases into the code generation. The overlap doesn't
56 ;; therefore exist anymore, but the numbering hasn't been changed
66 (defreg r10b 20 :byte)
67 (defreg r11b 22 :byte)
68 (defreg r12b 24 :byte)
69 (defreg r13b 26 :byte)
70 (defreg r14b 28 :byte)
71 (defreg r15b 30 :byte)
72 (defregset *byte-regs*
73 al cl dl bl sil dil r8b r9b r10b
74 #+nil r11b #+nil r12b r13b r14b r15b)
85 (defregset *word-regs* ax cx dx bx si di)
87 ;; double word registers
93 (defreg ebp 10 :dword)
94 (defreg esi 12 :dword)
95 (defreg edi 14 :dword)
96 (defregset *dword-regs* eax ecx edx ebx esi edi)
100 (defreg rcx 2 :qword)
101 (defreg rdx 4 :qword)
102 (defreg rbx 6 :qword)
103 (defreg rsp 8 :qword)
104 (defreg rbp 10 :qword)
105 (defreg rsi 12 :qword)
106 (defreg rdi 14 :qword)
107 (defreg r8 16 :qword)
108 (defreg r9 18 :qword)
109 (defreg r10 20 :qword)
110 (defreg r11 22 :qword)
111 (defreg r12 24 :qword)
112 (defreg r13 26 :qword)
113 (defreg r14 28 :qword)
114 (defreg r15 30 :qword)
115 ;; for no good reason at the time, r12 and r13 were missed from the
116 ;; list of qword registers. However
117 ;; <jsnell> r13 is already used as temporary [#lisp irc 2005/01/30]
118 ;; and we're now going to use r12 for the struct thread*
120 ;; Except that now we use r11 instead of r13 as the temporary,
121 ;; since it's got a more compact encoding than r13, and experimentally
122 ;; the temporary gets used more than the other registers that are never
123 ;; wired. -- JES, 2005-11-02
124 (defregset *qword-regs* rax rcx rdx rbx rsi rdi
125 r8 r9 r10 #+nil r11 #+nil r12 r13 r14 r15)
127 ;; floating point registers
128 (defreg float0 0 :float)
129 (defreg float1 1 :float)
130 (defreg float2 2 :float)
131 (defreg float3 3 :float)
132 (defreg float4 4 :float)
133 (defreg float5 5 :float)
134 (defreg float6 6 :float)
135 (defreg float7 7 :float)
136 (defreg float8 8 :float)
137 (defreg float9 9 :float)
138 (defreg float10 10 :float)
139 (defreg float11 11 :float)
140 (defreg float12 12 :float)
141 (defreg float13 13 :float)
142 (defreg float14 14 :float)
143 (defreg float15 15 :float)
144 (defregset *float-regs* float0 float1 float2 float3 float4 float5 float6 float7
145 float8 float9 float10 float11 float12 float13 float14 float15)
147 ;; registers used to pass arguments
149 ;; the number of arguments/return values passed in registers
150 (def!constant register-arg-count 3)
151 ;; names and offsets for registers used to pass arguments
152 (eval-when (:compile-toplevel :load-toplevel :execute)
153 (defparameter *register-arg-names* '(rdx rdi rsi)))
154 (defregset *register-arg-offsets* rdx rdi rsi)
155 (defregset *c-call-register-arg-offsets* rdi rsi rdx rcx r8 r9))
159 ;;; There are 16 registers really, but we consider them 32 in order to
160 ;;; describe the overlap of byte registers. The only thing we need to
161 ;;; represent is what registers overlap. Therefore, we consider bytes
162 ;;; to take one unit, and [dq]?words to take two. We don't need to
163 ;;; tell the difference between [dq]?words, because you can't put two
164 ;;; words in a dword register.
165 (define-storage-base registers :finite :size 32)
167 (define-storage-base float-registers :finite :size 16)
169 (define-storage-base stack :unbounded :size 8)
170 (define-storage-base constant :non-packed)
171 (define-storage-base immediate-constant :non-packed)
172 (define-storage-base noise :unbounded :size 2)
176 ;;; a handy macro so we don't have to keep changing all the numbers whenever
177 ;;; we insert a new storage class
179 (defmacro !define-storage-classes (&rest classes)
182 (dolist (class classes)
183 (let* ((sc-name (car class))
184 (constant-name (symbolicate sc-name "-SC-NUMBER")))
185 (forms `(define-storage-class ,sc-name ,index
187 (forms `(def!constant ,constant-name ,index))
192 ;;; The DEFINE-STORAGE-CLASS call for CATCH-BLOCK refers to the size
193 ;;; of CATCH-BLOCK. The size of CATCH-BLOCK isn't calculated until
194 ;;; later in the build process, and the calculation is entangled with
195 ;;; code which has lots of predependencies, including dependencies on
196 ;;; the prior call of DEFINE-STORAGE-CLASS. The proper way to
197 ;;; unscramble this would be to untangle the code, so that the code
198 ;;; which calculates the size of CATCH-BLOCK can be separated from the
199 ;;; other lots-of-dependencies code, so that the code which calculates
200 ;;; the size of CATCH-BLOCK can be executed early, so that this value
201 ;;; is known properly at this point in compilation. However, that
202 ;;; would be a lot of editing of code that I (WHN 19990131) can't test
203 ;;; until the project is complete. So instead, I set the correct value
204 ;;; by hand here (a sort of nondeterministic guess of the right
205 ;;; answer:-) and add an assertion later, after the value is
206 ;;; calculated, that the original guess was correct.
208 ;;; (What a KLUDGE! Anyone who wants to come in and clean up this mess
209 ;;; has my gratitude.) (FIXME: Maybe this should be me..)
210 (eval-when (:compile-toplevel :load-toplevel :execute)
211 (def!constant kludge-nondeterministic-catch-block-size 6))
213 (!define-storage-classes
215 ;; non-immediate constants in the constant pool
218 (fp-single-zero immediate-constant)
219 (fp-double-zero immediate-constant)
221 (immediate immediate-constant)
228 (control-stack stack) ; may be pointers, scanned by GC
230 ;; the non-descriptor stacks
231 ;; XXX alpha backend has :element-size 2 :alignment 2 in these entries
232 (signed-stack stack) ; (signed-byte 32)
233 (unsigned-stack stack) ; (unsigned-byte 32)
234 (character-stack stack) ; non-descriptor characters.
235 (sap-stack stack) ; System area pointers.
236 (single-stack stack) ; single-floats
238 (complex-single-stack stack :element-size 2) ; complex-single-floats
239 (complex-double-stack stack :element-size 2) ; complex-double-floats
249 ;; things that can go in the integer registers
252 ;; On the X86, we don't have to distinguish between descriptor and
253 ;; non-descriptor registers, because of the conservative GC.
254 ;; Therefore, we use different scs only to distinguish between
255 ;; descriptor and non-descriptor values and to specify size.
257 ;; immediate descriptor objects. Don't have to be seen by GC, but nothing
258 ;; bad will happen if they are. (fixnums, characters, header values, etc).
260 :locations #.*qword-regs*
261 :element-size 2 ; I think this is for the al/ah overlap thing
262 :constant-scs (immediate)
264 :alternate-scs (control-stack))
266 ;; pointer descriptor objects -- must be seen by GC
267 (descriptor-reg registers
268 :locations #.*qword-regs*
270 ; :reserve-locations (#.eax-offset)
271 :constant-scs (constant immediate)
273 :alternate-scs (control-stack))
275 ;; non-descriptor characters
276 (character-reg registers
277 :locations #!-sb-unicode #.*byte-regs*
278 #!+sb-unicode #.*qword-regs*
279 #!-sb-unicode #!-sb-unicode
280 :reserve-locations (#.al-offset)
281 :constant-scs (immediate)
283 :alternate-scs (character-stack))
285 ;; non-descriptor SAPs (arbitrary pointers into address space)
287 :locations #.*qword-regs*
289 ; :reserve-locations (#.eax-offset)
290 :constant-scs (immediate)
292 :alternate-scs (sap-stack))
294 ;; non-descriptor (signed or unsigned) numbers
295 (signed-reg registers
296 :locations #.*qword-regs*
298 :constant-scs (immediate)
300 :alternate-scs (signed-stack))
301 (unsigned-reg registers
302 :locations #.*qword-regs*
304 :constant-scs (immediate)
306 :alternate-scs (unsigned-stack))
308 ;; miscellaneous objects that must not be seen by GC. Used only as
311 :locations #.*word-regs*
315 :locations #.*dword-regs*
319 :locations #.*byte-regs*
322 ;; that can go in the floating point registers
324 ;; non-descriptor SINGLE-FLOATs
325 (single-reg float-registers
326 :locations #.(loop for i from 0 below 15 collect i)
327 :constant-scs (fp-single-zero)
329 :alternate-scs (single-stack))
331 ;; non-descriptor DOUBLE-FLOATs
332 (double-reg float-registers
333 :locations #.(loop for i from 0 below 15 collect i)
334 :constant-scs (fp-double-zero)
336 :alternate-scs (double-stack))
338 (complex-single-reg float-registers
339 :locations #.(loop for i from 0 to 14 by 2 collect i)
343 :alternate-scs (complex-single-stack))
345 (complex-double-reg float-registers
346 :locations #.(loop for i from 0 to 14 by 2 collect i)
350 :alternate-scs (complex-double-stack))
352 ;; a catch or unwind block
353 (catch-block stack :element-size kludge-nondeterministic-catch-block-size))
355 (eval-when (:compile-toplevel :load-toplevel :execute)
356 (defparameter *byte-sc-names*
357 '(#!-sb-unicode character-reg byte-reg #!-sb-unicode character-stack))
358 (defparameter *word-sc-names* '(word-reg))
359 (defparameter *dword-sc-names* '(dword-reg))
360 (defparameter *qword-sc-names*
361 '(any-reg descriptor-reg sap-reg signed-reg unsigned-reg control-stack
362 signed-stack unsigned-stack sap-stack single-stack
363 #!+sb-unicode character-reg #!+sb-unicode character-stack constant))
364 ;;; added by jrd. I guess the right thing to do is to treat floats
365 ;;; as a separate size...
367 ;;; These are used to (at least) determine operand size.
368 (defparameter *float-sc-names* '(single-reg))
369 (defparameter *double-sc-names* '(double-reg double-stack))
372 ;;;; miscellaneous TNs for the various registers
374 (macrolet ((def-misc-reg-tns (sc-name &rest reg-names)
376 (dolist (reg-name reg-names)
377 (let ((tn-name (symbolicate reg-name "-TN"))
378 (offset-name (symbolicate reg-name "-OFFSET")))
379 ;; FIXME: It'd be good to have the special
380 ;; variables here be named with the *FOO*
382 (forms `(defparameter ,tn-name
383 (make-random-tn :kind :normal
384 :sc (sc-or-lose ',sc-name)
387 `(progn ,@(forms)))))
389 (def-misc-reg-tns unsigned-reg rax rbx rcx rdx rbp rsp rdi rsi
390 r8 r9 r10 r11 r12 r13 r14 r15)
391 (def-misc-reg-tns dword-reg eax ebx ecx edx ebp esp edi esi)
392 (def-misc-reg-tns word-reg ax bx cx dx bp sp di si)
393 (def-misc-reg-tns byte-reg al cl dl bl sil dil r8b r9b r10b
394 r11b r12b r13b r14b r15b)
395 (def-misc-reg-tns single-reg
396 float0 float1 float2 float3 float4 float5 float6 float7
397 float8 float9 float10 float11 float12 float13 float14 float15))
399 ;; A register that's never used by the code generator, and can therefore
400 ;; be used as an assembly temporary in cases where a VOP :TEMPORARY can't
402 (defparameter temp-reg-tn r11-tn)
404 ;;; TNs for registers used to pass arguments
405 (defparameter *register-arg-tns*
406 (mapcar (lambda (register-arg-name)
407 (symbol-value (symbolicate register-arg-name "-TN")))
408 *register-arg-names*))
410 (defparameter thread-base-tn
411 (make-random-tn :kind :normal :sc (sc-or-lose 'unsigned-reg )
414 (defparameter fp-single-zero-tn
415 (make-random-tn :kind :normal
416 :sc (sc-or-lose 'single-reg)
419 (defparameter fp-double-zero-tn
420 (make-random-tn :kind :normal
421 :sc (sc-or-lose 'double-reg)
424 ;;; If value can be represented as an immediate constant, then return
425 ;;; the appropriate SC number, otherwise return NIL.
426 (!def-vm-support-routine immediate-constant-sc (value)
428 ((or (integer #.sb!xc:most-negative-fixnum #.sb!xc:most-positive-fixnum)
429 #-sb-xc-host system-area-pointer character)
430 (sc-number-or-lose 'immediate))
432 (when (static-symbol-p value)
433 (sc-number-or-lose 'immediate)))
436 (sc-number-or-lose 'fp-single-zero )
440 (sc-number-or-lose 'fp-double-zero )
444 ;;;; miscellaneous function call parameters
446 ;;; offsets of special stack frame locations
447 (def!constant ocfp-save-offset 0)
448 (def!constant return-pc-save-offset 1)
449 (def!constant code-save-offset 2)
451 (def!constant lra-save-offset return-pc-save-offset) ; ?
453 ;;; This is used by the debugger.
454 (def!constant single-value-return-byte-offset 3)
456 ;;; This function is called by debug output routines that want a pretty name
457 ;;; for a TN's location. It returns a thing that can be printed with PRINC.
458 (!def-vm-support-routine location-print-name (tn)
459 (declare (type tn tn))
460 (let* ((sc (tn-sc tn))
461 (sb (sb-name (sc-sb sc)))
462 (offset (tn-offset tn)))
465 (let* ((sc-name (sc-name sc))
466 (name-vec (cond ((member sc-name *byte-sc-names*)
467 *byte-register-names*)
468 ((member sc-name *word-sc-names*)
469 *word-register-names*)
470 ((member sc-name *dword-sc-names*)
471 *dword-register-names*)
472 ((member sc-name *qword-sc-names*)
473 *qword-register-names*))))
475 (< -1 offset (length name-vec))
476 (svref name-vec offset))
477 ;; FIXME: Shouldn't this be an ERROR?
478 (format nil "<unknown reg: off=~W, sc=~A>" offset sc-name))))
479 (float-registers (format nil "FLOAT~D" offset))
480 (stack (format nil "S~D" offset))
481 (constant (format nil "Const~D" offset))
482 (immediate-constant "Immed")
483 (noise (symbol-name (sc-name sc))))))
484 ;;; FIXME: Could this, and everything that uses it, be made #!+SB-SHOW?
486 (defun dwords-for-quad (value)
487 (let* ((lo (logand value (1- (ash 1 32))))
488 (hi (ash value -32)))
491 (defun words-for-dword (value)
492 (let* ((lo (logand value (1- (ash 1 16))))
493 (hi (ash value -16)))
496 (def!constant cfp-offset rbp-offset) ; pfw - needed by stuff in /code
498 (!def-vm-support-routine combination-implementation-style (node)
499 (declare (type sb!c::combination node) (ignore node))
500 (values :default nil))