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