f0c102e2c0549ee9bf6956ba2cfb250fe8e73806
[sbcl.git] / src / compiler / x86 / vm.lisp
1 ;;;; miscellaneous VM definition noise for the x86
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
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.
11
12 (in-package "SB!VM")
13
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 32))
17 \f
18 ;;;; register specs
19
20 (eval-when (:compile-toplevel :load-toplevel :execute)
21   (defvar *byte-register-names* (make-array 8 :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 *float-register-names* (make-array 8 :initial-element nil)))
25
26 (macrolet ((defreg (name offset size)
27              (let ((offset-sym (symbolicate name "-OFFSET"))
28                    (names-vector (symbolicate "*" size "-REGISTER-NAMES*")))
29                `(progn
30                   (eval-when (:compile-toplevel :load-toplevel :execute)
31                     ;; EVAL-WHEN is necessary because stuff like #.EAX-OFFSET
32                     ;; (in the same file) depends on compile-time evaluation
33                     ;; of the DEFCONSTANT. -- AL 20010224
34                     (def!constant ,offset-sym ,offset))
35                   (setf (svref ,names-vector ,offset-sym)
36                         ,(symbol-name name)))))
37            ;; FIXME: It looks to me as though DEFREGSET should also
38            ;; define the related *FOO-REGISTER-NAMES* variable.
39            (defregset (name &rest regs)
40              `(eval-when (:compile-toplevel :load-toplevel :execute)
41                 (defparameter ,name
42                   (list ,@(mapcar (lambda (name)
43                                     (symbolicate name "-OFFSET"))
44                                   regs))))))
45
46   ;; byte registers
47   ;;
48   ;; Note: the encoding here is different than that used by the chip.
49   ;; We use this encoding so that the compiler thinks that AX (and
50   ;; EAX) overlap AL and AH instead of AL and CL.
51   (defreg al 0 :byte)
52   (defreg ah 1 :byte)
53   (defreg cl 2 :byte)
54   (defreg ch 3 :byte)
55   (defreg dl 4 :byte)
56   (defreg dh 5 :byte)
57   (defreg bl 6 :byte)
58   (defreg bh 7 :byte)
59   (defregset *byte-regs* al ah cl ch dl dh bl bh)
60
61   ;; word registers
62   (defreg ax 0 :word)
63   (defreg cx 2 :word)
64   (defreg dx 4 :word)
65   (defreg bx 6 :word)
66   (defreg sp 8 :word)
67   (defreg bp 10 :word)
68   (defreg si 12 :word)
69   (defreg di 14 :word)
70   (defregset *word-regs* ax cx dx bx si di)
71
72   ;; double word registers
73   (defreg eax 0 :dword)
74   (defreg ecx 2 :dword)
75   (defreg edx 4 :dword)
76   (defreg ebx 6 :dword)
77   (defreg esp 8 :dword)
78   (defreg ebp 10 :dword)
79   (defreg esi 12 :dword)
80   (defreg edi 14 :dword)
81   (defregset *dword-regs* eax ecx edx ebx esi edi)
82
83   ;; floating point registers
84   (defreg fr0 0 :float)
85   (defreg fr1 1 :float)
86   (defreg fr2 2 :float)
87   (defreg fr3 3 :float)
88   (defreg fr4 4 :float)
89   (defreg fr5 5 :float)
90   (defreg fr6 6 :float)
91   (defreg fr7 7 :float)
92   (defregset *float-regs* fr0 fr1 fr2 fr3 fr4 fr5 fr6 fr7)
93
94   ;; registers used to pass arguments
95   ;;
96   ;; the number of arguments/return values passed in registers
97   (def!constant  register-arg-count 3)
98   ;; names and offsets for registers used to pass arguments
99   (eval-when (:compile-toplevel :load-toplevel :execute)
100     (defparameter *register-arg-names* '(edx edi esi)))
101   (defregset    *register-arg-offsets* edx edi esi))
102 \f
103 ;;;; SB definitions
104
105 ;;; Despite the fact that there are only 8 different registers, we consider
106 ;;; them 16 in order to describe the overlap of byte registers. The only
107 ;;; thing we need to represent is what registers overlap. Therefore, we
108 ;;; consider bytes to take one unit, and words or dwords to take two. We
109 ;;; don't need to tell the difference between words and dwords, because
110 ;;; you can't put two words in a dword register.
111 (define-storage-base registers :finite :size 16)
112
113 ;;; jrd changed this from size 1 to size 8. It doesn't seem to make much
114 ;;; sense to use the 387's idea of a stack; 8 separate registers is easier
115 ;;; to deal with.
116 ;;; the old way:
117 ;;;   (define-storage-base float-registers :finite :size 1)
118 ;;; the new way:
119 (define-storage-base float-registers :finite :size 8)
120
121 (define-storage-base stack :unbounded :size 8)
122 (define-storage-base constant :non-packed)
123 (define-storage-base immediate-constant :non-packed)
124 (define-storage-base noise :unbounded :size 2)
125 \f
126 ;;;; SC definitions
127
128 ;;; a handy macro so we don't have to keep changing all the numbers whenever
129 ;;; we insert a new storage class
130 ;;;
131 (defmacro !define-storage-classes (&rest classes)
132   (collect ((forms))
133     (let ((index 0))
134       (dolist (class classes)
135         (let* ((sc-name (car class))
136                (constant-name (symbolicate sc-name "-SC-NUMBER")))
137           (forms `(define-storage-class ,sc-name ,index
138                     ,@(cdr class)))
139           (forms `(def!constant ,constant-name ,index))
140           (incf index))))
141     `(progn
142        ,@(forms))))
143
144 ;;; The DEFINE-STORAGE-CLASS call for CATCH-BLOCK refers to the size
145 ;;; of CATCH-BLOCK. The size of CATCH-BLOCK isn't calculated until
146 ;;; later in the build process, and the calculation is entangled with
147 ;;; code which has lots of predependencies, including dependencies on
148 ;;; the prior call of DEFINE-STORAGE-CLASS. The proper way to
149 ;;; unscramble this would be to untangle the code, so that the code
150 ;;; which calculates the size of CATCH-BLOCK can be separated from the
151 ;;; other lots-of-dependencies code, so that the code which calculates
152 ;;; the size of CATCH-BLOCK can be executed early, so that this value
153 ;;; is known properly at this point in compilation. However, that
154 ;;; would be a lot of editing of code that I (WHN 19990131) can't test
155 ;;; until the project is complete. So instead, I set the correct value
156 ;;; by hand here (a sort of nondeterministic guess of the right
157 ;;; answer:-) and add an assertion later, after the value is
158 ;;; calculated, that the original guess was correct.
159 ;;;
160 ;;; (What a KLUDGE! Anyone who wants to come in and clean up this mess
161 ;;; has my gratitude.) (FIXME: Maybe this should be me..)
162 (eval-when (:compile-toplevel :load-toplevel :execute)
163   (def!constant kludge-nondeterministic-catch-block-size 6))
164
165 (!define-storage-classes
166
167   ;; non-immediate constants in the constant pool
168   (constant constant)
169
170   ;; some FP constants can be generated in the i387 silicon
171   (fp-constant immediate-constant)
172
173   (immediate immediate-constant)
174
175   ;;
176   ;; the stacks
177   ;;
178   
179   ;; the control stack
180   (control-stack stack)                 ; may be pointers, scanned by GC
181
182   ;; the non-descriptor stacks
183   (signed-stack stack)                  ; (signed-byte 32)
184   (unsigned-stack stack)                ; (unsigned-byte 32)
185   (base-char-stack stack)               ; non-descriptor characters.
186   (sap-stack stack)                     ; System area pointers.
187   (single-stack stack)                  ; single-floats
188   (double-stack stack :element-size 2)  ; double-floats.
189   #!+long-float
190   (long-stack stack :element-size 3)    ; long-floats.
191   (complex-single-stack stack :element-size 2)  ; complex-single-floats
192   (complex-double-stack stack :element-size 4)  ; complex-double-floats
193   #!+long-float
194   (complex-long-stack stack :element-size 6)    ; complex-long-floats
195
196   ;;
197   ;; magic SCs
198   ;;
199
200   (ignore-me noise)
201
202   ;;
203   ;; things that can go in the integer registers
204   ;;
205
206   ;; On the X86, we don't have to distinguish between descriptor and
207   ;; non-descriptor registers, because of the conservative GC.
208   ;; Therefore, we use different scs only to distinguish between
209   ;; descriptor and non-descriptor values and to specify size.
210
211   ;; immediate descriptor objects. Don't have to be seen by GC, but nothing
212   ;; bad will happen if they are. (fixnums, characters, header values, etc).
213   (any-reg registers
214            :locations #.*dword-regs*
215            :element-size 2
216 ;          :reserve-locations (#.eax-offset)
217            :constant-scs (immediate)
218            :save-p t
219            :alternate-scs (control-stack))
220
221   ;; pointer descriptor objects -- must be seen by GC
222   (descriptor-reg registers
223                   :locations #.*dword-regs*
224                   :element-size 2
225 ;                 :reserve-locations (#.eax-offset)
226                   :constant-scs (constant immediate)
227                   :save-p t
228                   :alternate-scs (control-stack))
229
230   ;; non-descriptor characters
231   (base-char-reg registers
232                  :locations #.*byte-regs*
233                  :reserve-locations (#.ah-offset #.al-offset)
234                  :constant-scs (immediate)
235                  :save-p t
236                  :alternate-scs (base-char-stack))
237
238   ;; non-descriptor SAPs (arbitrary pointers into address space)
239   (sap-reg registers
240            :locations #.*dword-regs*
241            :element-size 2
242 ;          :reserve-locations (#.eax-offset)
243            :constant-scs (immediate)
244            :save-p t
245            :alternate-scs (sap-stack))
246
247   ;; non-descriptor (signed or unsigned) numbers
248   (signed-reg registers
249               :locations #.*dword-regs*
250               :element-size 2
251 ;             :reserve-locations (#.eax-offset)
252               :constant-scs (immediate)
253               :save-p t
254               :alternate-scs (signed-stack))
255   (unsigned-reg registers
256                 :locations #.*dword-regs*
257                 :element-size 2
258 ;               :reserve-locations (#.eax-offset)
259                 :constant-scs (immediate)
260                 :save-p t
261                 :alternate-scs (unsigned-stack))
262
263   ;; miscellaneous objects that must not be seen by GC. Used only as
264   ;; temporaries.
265   (word-reg registers
266             :locations #.*word-regs*
267             :element-size 2
268 ;           :reserve-locations (#.ax-offset)
269             )
270   (byte-reg registers
271             :locations #.*byte-regs*
272 ;           :reserve-locations (#.al-offset #.ah-offset)
273             )
274
275   ;; that can go in the floating point registers
276
277   ;; non-descriptor SINGLE-FLOATs
278   (single-reg float-registers
279               :locations (0 1 2 3 4 5 6 7)
280               :constant-scs (fp-constant)
281               :save-p t
282               :alternate-scs (single-stack))
283
284   ;; non-descriptor DOUBLE-FLOATs
285   (double-reg float-registers
286               :locations (0 1 2 3 4 5 6 7)
287               :constant-scs (fp-constant)
288               :save-p t
289               :alternate-scs (double-stack))
290
291   ;; non-descriptor LONG-FLOATs
292   #!+long-float
293   (long-reg float-registers
294             :locations (0 1 2 3 4 5 6 7)
295             :constant-scs (fp-constant)
296             :save-p t
297             :alternate-scs (long-stack))
298
299   (complex-single-reg float-registers
300                       :locations (0 2 4 6)
301                       :element-size 2
302                       :constant-scs ()
303                       :save-p t
304                       :alternate-scs (complex-single-stack))
305
306   (complex-double-reg float-registers
307                       :locations (0 2 4 6)
308                       :element-size 2
309                       :constant-scs ()
310                       :save-p t
311                       :alternate-scs (complex-double-stack))
312
313   #!+long-float
314   (complex-long-reg float-registers
315                     :locations (0 2 4 6)
316                     :element-size 2
317                     :constant-scs ()
318                     :save-p t
319                     :alternate-scs (complex-long-stack))
320
321   ;; a catch or unwind block
322   (catch-block stack :element-size kludge-nondeterministic-catch-block-size))
323
324 (eval-when (:compile-toplevel :load-toplevel :execute)
325 (defparameter *byte-sc-names* '(base-char-reg byte-reg base-char-stack))
326 (defparameter *word-sc-names* '(word-reg))
327 (defparameter *dword-sc-names*
328   '(any-reg descriptor-reg sap-reg signed-reg unsigned-reg control-stack
329     signed-stack unsigned-stack sap-stack single-stack constant))
330 ;;; added by jrd. I guess the right thing to do is to treat floats
331 ;;; as a separate size...
332 ;;;
333 ;;; These are used to (at least) determine operand size.
334 (defparameter *float-sc-names* '(single-reg))
335 (defparameter *double-sc-names* '(double-reg double-stack))
336 ) ; EVAL-WHEN
337 \f
338 ;;;; miscellaneous TNs for the various registers
339
340 (macrolet ((def-misc-reg-tns (sc-name &rest reg-names)
341              (collect ((forms))
342                       (dolist (reg-name reg-names)
343                         (let ((tn-name (symbolicate reg-name "-TN"))
344                               (offset-name (symbolicate reg-name "-OFFSET")))
345                           ;; FIXME: It'd be good to have the special
346                           ;; variables here be named with the *FOO*
347                           ;; convention.
348                           (forms `(defparameter ,tn-name
349                                     (make-random-tn :kind :normal
350                                                     :sc (sc-or-lose ',sc-name)
351                                                     :offset
352                                                     ,offset-name)))))
353                       `(progn ,@(forms)))))
354
355   (def-misc-reg-tns unsigned-reg eax ebx ecx edx ebp esp edi esi)
356   (def-misc-reg-tns word-reg ax bx cx dx bp sp di si)
357   (def-misc-reg-tns byte-reg al ah bl bh cl ch dl dh)
358   (def-misc-reg-tns single-reg fr0 fr1 fr2 fr3 fr4 fr5 fr6 fr7))
359
360 ;;; TNs for registers used to pass arguments
361 (defparameter *register-arg-tns*
362   (mapcar (lambda (register-arg-name)
363             (symbol-value (symbolicate register-arg-name "-TN")))
364           *register-arg-names*))
365
366 ;;; FIXME: doesn't seem to be used in SBCL
367 #|
368 ;;; added by pw
369 (defparameter fp-constant-tn
370   (make-random-tn :kind :normal
371                   :sc (sc-or-lose 'fp-constant)
372                   :offset 31))          ; Offset doesn't get used.
373 |#
374 \f
375 ;;; If value can be represented as an immediate constant, then return
376 ;;; the appropriate SC number, otherwise return NIL.
377 (!def-vm-support-routine immediate-constant-sc (value)
378   (typecase value
379     ((or fixnum #-sb-xc-host system-area-pointer character)
380      (sc-number-or-lose 'immediate))
381     (symbol
382      (when (static-symbol-p value)
383        (sc-number-or-lose 'immediate)))
384     (single-float
385      (when (or (eql value 0f0) (eql value 1f0))
386        (sc-number-or-lose 'fp-constant)))
387     (double-float
388      (when (or (eql value 0d0) (eql value 1d0))
389        (sc-number-or-lose 'fp-constant)))
390     #!+long-float
391     (long-float
392      (when (or (eql value 0l0) (eql value 1l0)
393                (eql value pi)
394                (eql value (log 10l0 2l0))
395                (eql value (log 2.718281828459045235360287471352662L0 2l0))
396                (eql value (log 2l0 10l0))
397                (eql value (log 2l0 2.718281828459045235360287471352662L0)))
398        (sc-number-or-lose 'fp-constant)))))
399 \f
400 ;;;; miscellaneous function call parameters
401
402 ;;; offsets of special stack frame locations
403 (def!constant ocfp-save-offset 0)
404 (def!constant return-pc-save-offset 1)
405 (def!constant code-save-offset 2)
406
407 ;;; FIXME: This is a bad comment (changed since when?) and there are others
408 ;;; like it in this file. It'd be nice to clarify them. Failing that deleting
409 ;;; them or flagging them with KLUDGE might be better than nothing.
410 ;;;
411 ;;; names of these things seem to have changed. these aliases by jrd
412 (def!constant lra-save-offset return-pc-save-offset)
413
414 (def!constant cfp-offset ebp-offset)    ; pfw - needed by stuff in /code
415                                         ; related to signal context stuff
416
417 ;;; This is used by the debugger.
418 (def!constant single-value-return-byte-offset 2)
419 \f
420 ;;; This function is called by debug output routines that want a pretty name
421 ;;; for a TN's location. It returns a thing that can be printed with PRINC.
422 (!def-vm-support-routine location-print-name (tn)
423   (declare (type tn tn))
424   (let* ((sc (tn-sc tn))
425          (sb (sb-name (sc-sb sc)))
426          (offset (tn-offset tn)))
427     (ecase sb
428       (registers
429        (let* ((sc-name (sc-name sc))
430               (name-vec (cond ((member sc-name *byte-sc-names*)
431                                *byte-register-names*)
432                               ((member sc-name *word-sc-names*)
433                                *word-register-names*)
434                               ((member sc-name *dword-sc-names*)
435                                *dword-register-names*))))
436          (or (and name-vec
437                   (< -1 offset (length name-vec))
438                   (svref name-vec offset))
439              ;; FIXME: Shouldn't this be an ERROR?
440              (format nil "<unknown reg: off=~W, sc=~A>" offset sc-name))))
441       (float-registers (format nil "FR~D" offset))
442       (stack (format nil "S~D" offset))
443       (constant (format nil "Const~D" offset))
444       (immediate-constant "Immed")
445       (noise (symbol-name (sc-name sc))))))
446 ;;; FIXME: Could this, and everything that uses it, be made #!+SB-SHOW?
447
448 \f
449 ;;; The loader uses this to convert alien names to the form they need in
450 ;;; the symbol table (for example, prepending an underscore).
451 (defun extern-alien-name (name)
452   (declare (type simple-string name))
453   ;; OpenBSD is non-ELF, and needs a _ prefix
454   #!+openbsd (concatenate 'string "_" name)
455   ;; The other (ELF) ports currently don't need any prefix
456   #!-openbsd name)