0.7.13.5
[sbcl.git] / src / compiler / x86 / macros.lisp
1 ;;;; a bunch of handy macros 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 ;;; We can load/store into fp registers through the top of stack
15 ;;; %st(0) (fr0 here). Loads imply a push to an empty register which
16 ;;; then changes all the reg numbers. These macros help manage that.
17
18 ;;; Use this when we don't have to load anything. It preserves old tos
19 ;;; value, but probably destroys tn with operation.
20 (defmacro with-tn@fp-top((tn) &body body)
21   `(progn
22     (unless (zerop (tn-offset ,tn))
23       (inst fxch ,tn))
24     ,@body
25     (unless (zerop (tn-offset ,tn))
26       (inst fxch ,tn))))
27
28 ;;; Use this to prepare for load of new value from memory. This
29 ;;; changes the register numbering so the next instruction had better
30 ;;; be a FP load from memory; a register load from another register
31 ;;; will probably be loading the wrong register!
32 (defmacro with-empty-tn@fp-top((tn) &body body)
33   `(progn
34     (inst fstp ,tn)
35     ,@body
36     (unless (zerop (tn-offset ,tn))
37       (inst fxch ,tn))))                ; save into new dest and restore st(0)
38 \f
39 ;;;; instruction-like macros
40
41 (defmacro move (dst src)
42   #!+sb-doc
43   "Move SRC into DST unless they are location=."
44   (once-only ((n-dst dst)
45               (n-src src))
46     `(unless (location= ,n-dst ,n-src)
47        (inst mov ,n-dst ,n-src))))
48
49 (defmacro make-ea-for-object-slot (ptr slot lowtag)
50   `(make-ea :dword :base ,ptr :disp (- (* ,slot n-word-bytes) ,lowtag)))
51
52 (defmacro loadw (value ptr &optional (slot 0) (lowtag 0))
53   `(inst mov ,value (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
54
55 (defmacro storew (value ptr &optional (slot 0) (lowtag 0))
56   (once-only ((value value))
57     `(inst mov (make-ea-for-object-slot ,ptr ,slot ,lowtag) ,value)))
58
59 (defmacro pushw (ptr &optional (slot 0) (lowtag 0))
60   `(inst push (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
61
62 (defmacro popw (ptr &optional (slot 0) (lowtag 0))
63   `(inst pop (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
64 \f
65 ;;;; macros to generate useful values
66
67 (defmacro load-symbol (reg symbol)
68   `(inst mov ,reg (+ nil-value (static-symbol-offset ,symbol))))
69
70 (defmacro load-symbol-value (reg symbol)
71   `(inst mov ,reg
72          (make-ea :dword
73                   :disp (+ nil-value
74                            (static-symbol-offset ',symbol)
75                            (ash symbol-value-slot word-shift)
76                            (- other-pointer-lowtag)))))
77
78 (defmacro store-symbol-value (reg symbol)
79   `(inst mov
80          (make-ea :dword
81                   :disp (+ nil-value
82                            (static-symbol-offset ',symbol)
83                            (ash symbol-value-slot word-shift)
84                            (- other-pointer-lowtag)))
85          ,reg))
86
87
88 (defmacro load-type (target source &optional (offset 0))
89   #!+sb-doc
90   "Loads the type bits of a pointer into target independent of
91    byte-ordering issues."
92   (once-only ((n-target target)
93               (n-source source)
94               (n-offset offset))
95     (ecase *backend-byte-order*
96       (:little-endian
97        `(inst mov ,n-target
98               (make-ea :byte :base ,n-source :disp ,n-offset)))
99       (:big-endian
100        `(inst mov ,n-target
101               (make-ea :byte :base ,n-source :disp (+ ,n-offset 3)))))))
102 \f
103 ;;;; allocation helpers
104
105 ;;; Two allocation approaches are implemented. A call into C can be
106 ;;; used, and in that case special care can be taken to disable
107 ;;; interrupts. Alternatively with gencgc inline allocation is possible
108 ;;; although it isn't interrupt safe.
109
110 ;;; For GENCGC it is possible to inline object allocation, to permit
111 ;;; this set the following variable to True.
112 ;;;
113 ;;; FIXME: The comment above says that this isn't interrupt safe. Is that
114 ;;; right? If so, do we want to do this? And surely we don't want to do this by
115 ;;; default? How much time does it save to do this? Is it any different in the
116 ;;; current CMU CL version instead of the one that I grabbed in 1998?
117 ;;; (Later observation: In order to be interrupt safe, it'd probably
118 ;;; have to use PSEUDO-ATOMIC, so it's probably not -- yuck. Try benchmarks
119 ;;; with and without inline allocation, and unless the inline allocation
120 ;;; wins by a whole lot, it's not likely to be worth messing with. If
121 ;;; we want to hack up memory allocation for performance, effort spent
122 ;;; on DYNAMIC-EXTENT would probably give a better payoff.)
123 (defvar *maybe-use-inline-allocation* t)
124
125 ;;; Emit code to allocate an object with a size in bytes given by
126 ;;; Size. The size may be an integer of a TN. If Inline is a VOP
127 ;;; node-var then it is used to make an appropriate speed vs size
128 ;;; decision.
129 ;;;
130 ;;; FIXME: We call into C.. except when inline allocation is enabled..?
131 ;;;
132 ;;; FIXME: Also, calls to
133 ;;; ALLOCATION are always wrapped with PSEUDO-ATOMIC -- why? Is it to
134 ;;; make sure that no GC happens between the time of allocation and the
135 ;;; time that the allocated memory has its tag bits set correctly?
136 ;;; If so, then ALLOCATION itself might as well set the PSEUDO-ATOMIC
137 ;;; bits, so that the caller need only clear them. Check whether it's
138 ;;; true that every ALLOCATION is surrounded by PSEUDO-ATOMIC, and
139 ;;; that every PSEUDO-ATOMIC contains a single ALLOCATION, which is
140 ;;; its first instruction. If so, the connection should probably be
141 ;;; formalized, in documentation and in macro definition,
142 ;;; with the macro becoming e.g. PSEUDO-ATOMIC-ALLOCATION.
143 (defun allocation (alloc-tn size &optional inline)
144   (flet ((load-size (dst-tn size)
145            (unless (and (tn-p size) (location= alloc-tn size))
146              (inst mov dst-tn size))))
147     (let ((alloc-tn-offset (tn-offset alloc-tn)))
148           ;; C call to allocate via dispatch routines. Each
149           ;; destination has a special entry point. The size may be a
150           ;; register or a constant.
151           (ecase alloc-tn-offset
152             (#.eax-offset
153              (case size
154                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_eax")
155                                          :foreign)))
156                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_eax")
157                                           :foreign)))
158                (t
159                 (load-size eax-tn size)
160                 (inst call (make-fixup (extern-alien-name "alloc_to_eax")
161                                        :foreign)))))
162             (#.ecx-offset
163              (case size
164                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_ecx")
165                                          :foreign)))
166                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_ecx")
167                                           :foreign)))
168                (t
169                 (load-size ecx-tn size)
170                 (inst call (make-fixup (extern-alien-name "alloc_to_ecx")
171                                        :foreign)))))
172             (#.edx-offset
173              (case size
174                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_edx")
175                                          :foreign)))
176                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_edx")
177                                           :foreign)))
178                (t
179                 (load-size edx-tn size)
180                 (inst call (make-fixup (extern-alien-name "alloc_to_edx")
181                                        :foreign)))))
182             (#.ebx-offset
183              (case size
184                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_ebx")
185                                          :foreign)))
186                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_ebx")
187                                           :foreign)))
188                (t
189                 (load-size ebx-tn size)
190                 (inst call (make-fixup (extern-alien-name "alloc_to_ebx")
191                                        :foreign)))))
192             (#.esi-offset
193              (case size
194                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_esi")
195                                          :foreign)))
196                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_esi")
197                                           :foreign)))
198                (t
199                 (load-size esi-tn size)
200                 (inst call (make-fixup (extern-alien-name "alloc_to_esi")
201                                        :foreign)))))
202             (#.edi-offset
203              (case size
204                (8 (inst call (make-fixup (extern-alien-name "alloc_8_to_edi")
205                                          :foreign)))
206                (16 (inst call (make-fixup (extern-alien-name "alloc_16_to_edi")
207                                           :foreign)))
208                (t
209                 (load-size edi-tn size)
210                 (inst call (make-fixup (extern-alien-name "alloc_to_edi")
211                                    :foreign))))))))
212   (values))
213
214 ;;; Allocate an other-pointer object of fixed SIZE with a single word
215 ;;; header having the specified WIDETAG value. The result is placed in
216 ;;; RESULT-TN.
217 (defmacro with-fixed-allocation ((result-tn widetag size &optional inline)
218                                  &rest forms)
219   `(pseudo-atomic
220     (allocation ,result-tn (pad-data-block ,size) ,inline)
221     (storew (logior (ash (1- ,size) n-widetag-bits) ,widetag)
222             ,result-tn)
223     (inst lea ,result-tn
224      (make-ea :byte :base ,result-tn :disp other-pointer-lowtag))
225     ,@forms))
226 \f
227 ;;;; error code
228 (eval-when (:compile-toplevel :load-toplevel :execute)
229   (defun emit-error-break (vop kind code values)
230     (let ((vector (gensym)))
231       `((inst int 3)                            ; i386 breakpoint instruction
232         ;; The return PC points here; note the location for the debugger.
233         (let ((vop ,vop))
234           (when vop
235                 (note-this-location vop :internal-error)))
236         (inst byte ,kind)                       ; eg trap_Xyyy
237         (with-adjustable-vector (,vector)       ; interr arguments
238           (write-var-integer (error-number-or-lose ',code) ,vector)
239           ,@(mapcar (lambda (tn)
240                       `(let ((tn ,tn))
241                          ;; classic CMU CL comment:
242                          ;;   zzzzz jrd here. tn-offset is zero for constant
243                          ;;   tns.
244                          (write-var-integer (make-sc-offset (sc-number
245                                                              (tn-sc tn))
246                                                             (or (tn-offset tn)
247                                                                 0))
248                                             ,vector)))
249                     values)
250           (inst byte (length ,vector))
251           (dotimes (i (length ,vector))
252             (inst byte (aref ,vector i))))))))
253
254 (defmacro error-call (vop error-code &rest values)
255   #!+sb-doc
256   "Cause an error. ERROR-CODE is the error to cause."
257   (cons 'progn
258         (emit-error-break vop error-trap error-code values)))
259
260 ;;; not used in SBCL
261 #|
262 (defmacro cerror-call (vop label error-code &rest values)
263   #!+sb-doc
264   "Cause a continuable error. If the error is continued, execution resumes
265   at LABEL."
266   `(progn
267      ,@(emit-error-break vop cerror-trap error-code values)
268      (inst jmp ,label)))
269 |#
270
271 (defmacro generate-error-code (vop error-code &rest values)
272   #!+sb-doc
273   "Generate-Error-Code Error-code Value*
274   Emit code for an error with the specified Error-Code and context Values."
275   `(assemble (*elsewhere*)
276      (let ((start-lab (gen-label)))
277        (emit-label start-lab)
278        (error-call ,vop ,error-code ,@values)
279        start-lab)))
280
281 ;;; not used in SBCL
282 #|
283 (defmacro generate-cerror-code (vop error-code &rest values)
284   #!+sb-doc
285   "Generate-CError-Code Error-code Value*
286   Emit code for a continuable error with the specified Error-Code and
287   context Values. If the error is continued, execution resumes after
288   the GENERATE-CERROR-CODE form."
289   (let ((continue (gensym "CONTINUE-LABEL-"))
290         (error (gensym "ERROR-LABEL-")))
291     `(let ((,continue (gen-label))
292            (,error (gen-label)))
293        (emit-label ,continue)
294        (assemble (*elsewhere*)
295          (emit-label ,error)
296          (cerror-call ,vop ,continue ,error-code ,@values))
297        ,error)))
298 |#
299 \f
300 ;;;; PSEUDO-ATOMIC
301
302 ;;; FIXME: *PSEUDO-ATOMIC-FOO* could be made into *PSEUDO-ATOMIC-BITS*,
303 ;;; set with a single operation and cleared with SHR *PSEUDO-ATOMIC-BITS*,-2;
304 ;;; the ATOMIC bit is bit 0, the INTERRUPTED bit is bit 1, and you check
305 ;;; the C flag after the shift to see whether you were interrupted.
306
307 ;;; FIXME: It appears that PSEUDO-ATOMIC is used to wrap operations which leave
308 ;;; untagged memory lying around, but some documentation would be nice.
309 (defmacro pseudo-atomic (&rest forms)
310   (let ((label (gensym "LABEL-")))
311     `(let ((,label (gen-label)))
312       ;; FIXME: The MAKE-EA noise should become a MACROLET macro or
313       ;; something. (perhaps SVLB, for static variable low byte)
314       (inst mov (make-ea :byte :disp (+ nil-value
315                                         (static-symbol-offset
316                                          '*pseudo-atomic-interrupted*)
317                                         (ash symbol-value-slot word-shift)
318                                         ;; FIXME: Use mask, not minus, to
319                                         ;; take out type bits.
320                                         (- other-pointer-lowtag)))
321        0)
322       (inst mov (make-ea :byte :disp (+ nil-value
323                                         (static-symbol-offset
324                                          '*pseudo-atomic-atomic*)
325                                         (ash symbol-value-slot word-shift)
326                                         (- other-pointer-lowtag)))
327        (fixnumize 1))
328       ,@forms
329       (inst mov (make-ea :byte :disp (+ nil-value
330                                         (static-symbol-offset
331                                          '*pseudo-atomic-atomic*)
332                                         (ash symbol-value-slot word-shift)
333                                         (- other-pointer-lowtag)))
334        0)
335       ;; KLUDGE: Is there any requirement for interrupts to be
336       ;; handled in order? It seems as though an interrupt coming
337       ;; in at this point will be executed before any pending interrupts.
338       ;; Or do incoming interrupts check to see whether any interrupts
339       ;; are pending? I wish I could find the documentation for
340       ;; pseudo-atomics.. -- WHN 19991130
341       (inst cmp (make-ea :byte
342                  :disp (+ nil-value
343                           (static-symbol-offset
344                            '*pseudo-atomic-interrupted*)
345                           (ash symbol-value-slot word-shift)
346                           (- other-pointer-lowtag)))
347        0)
348       (inst jmp :eq ,label)
349       ;; if PAI was set, interrupts were disabled at the same time
350       ;; using the process signal mask.  
351       (inst break pending-interrupt-trap)
352       (emit-label ,label))))
353 \f
354 ;;;; indexed references
355
356 (defmacro define-full-reffer (name type offset lowtag scs el-type &optional translate)
357   `(progn
358      (define-vop (,name)
359        ,@(when translate
360            `((:translate ,translate)))
361        (:policy :fast-safe)
362        (:args (object :scs (descriptor-reg))
363               (index :scs (any-reg)))
364        (:arg-types ,type tagged-num)
365        (:results (value :scs ,scs))
366        (:result-types ,el-type)
367        (:generator 3                    ; pw was 5
368          (inst mov value (make-ea :dword :base object :index index
369                                   :disp (- (* ,offset n-word-bytes)
370                                            ,lowtag)))))
371      (define-vop (,(symbolicate name "-C"))
372        ,@(when translate
373            `((:translate ,translate)))
374        (:policy :fast-safe)
375        (:args (object :scs (descriptor-reg)))
376        (:info index)
377        (:arg-types ,type (:constant (signed-byte 30)))
378        (:results (value :scs ,scs))
379        (:result-types ,el-type)
380        (:generator 2                    ; pw was 5
381          (inst mov value (make-ea :dword :base object
382                                   :disp (- (* (+ ,offset index) n-word-bytes)
383                                            ,lowtag)))))))
384
385 (defmacro define-full-setter (name type offset lowtag scs el-type &optional translate)
386   `(progn
387      (define-vop (,name)
388        ,@(when translate
389            `((:translate ,translate)))
390        (:policy :fast-safe)
391        (:args (object :scs (descriptor-reg))
392               (index :scs (any-reg))
393               (value :scs ,scs :target result))
394        (:arg-types ,type tagged-num ,el-type)
395        (:results (result :scs ,scs))
396        (:result-types ,el-type)
397        (:generator 4                    ; was 5
398          (inst mov (make-ea :dword :base object :index index
399                             :disp (- (* ,offset n-word-bytes) ,lowtag))
400                value)
401          (move result value)))
402      (define-vop (,(symbolicate name "-C"))
403        ,@(when translate
404            `((:translate ,translate)))
405        (:policy :fast-safe)
406        (:args (object :scs (descriptor-reg))
407               (value :scs ,scs :target result))
408        (:info index)
409        (:arg-types ,type (:constant (signed-byte 30)) ,el-type)
410        (:results (result :scs ,scs))
411        (:result-types ,el-type)
412        (:generator 3                    ; was 5
413          (inst mov (make-ea :dword :base object
414                             :disp (- (* (+ ,offset index) n-word-bytes)
415                                      ,lowtag))
416                value)
417          (move result value)))))
418