0.8.21.21: fix & share EXTERN-ALIEN-NAME logic (fixes bug #373)
[sbcl.git] / src / compiler / x86-64 / 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 :qword :base ,ptr :disp (- (* ,slot n-word-bytes) ,lowtag)))
51 (defmacro make-ea-for-object-slot-half (ptr slot lowtag)
52   `(make-ea :dword :base ,ptr :disp (- (* ,slot n-word-bytes) ,lowtag)))
53
54 (defmacro loadw (value ptr &optional (slot 0) (lowtag 0))
55   `(inst mov ,value (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
56
57 (defmacro storew (value ptr &optional (slot 0) (lowtag 0))
58   (once-only ((value value))
59     `(cond ((and (integerp ,value) 
60                  (not (typep ,value '(signed-byte 32))))
61             (multiple-value-bind (lo hi) (dwords-for-quad ,value)
62               (inst mov (make-ea-for-object-slot-half
63                          ,ptr ,slot ,lowtag) lo)
64               (inst mov (make-ea-for-object-slot-half
65                          ,ptr (+ ,slot 1/2) ,lowtag) hi)))
66            (t
67             (inst mov (make-ea-for-object-slot ,ptr ,slot ,lowtag) ,value)))))
68
69 (defmacro pushw (ptr &optional (slot 0) (lowtag 0))
70   `(inst push (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
71
72 (defmacro popw (ptr &optional (slot 0) (lowtag 0))
73   `(inst pop (make-ea-for-object-slot ,ptr ,slot ,lowtag)))
74 \f
75 ;;;; macros to generate useful values
76
77 (defmacro load-symbol (reg symbol)
78   `(inst mov ,reg (+ nil-value (static-symbol-offset ,symbol))))
79
80 (defmacro load-symbol-value (reg symbol)
81   `(inst mov ,reg
82          (make-ea :qword
83                   :disp (+ nil-value
84                            (static-symbol-offset ',symbol)
85                            (ash symbol-value-slot word-shift)
86                            (- other-pointer-lowtag)))))
87
88 (defmacro store-symbol-value (reg symbol)
89   `(inst mov
90          (make-ea :qword
91                   :disp (+ nil-value
92                            (static-symbol-offset ',symbol)
93                            (ash symbol-value-slot word-shift)
94                            (- other-pointer-lowtag)))
95          ,reg))
96
97 #!+sb-thread
98 (defmacro load-tl-symbol-value (reg symbol)
99   `(progn
100     (inst mov ,reg
101      (make-ea :qword
102       :disp (+ nil-value
103                (static-symbol-offset ',symbol)
104                (ash symbol-tls-index-slot word-shift)
105                (- other-pointer-lowtag))))
106     (inst fs-segment-prefix)
107     (inst mov ,reg (make-ea :qword :scale 1 :index ,reg))))
108 #!-sb-thread
109 (defmacro load-tl-symbol-value (reg symbol) `(load-symbol-value ,reg ,symbol))
110
111 #!+sb-thread
112 (defmacro store-tl-symbol-value (reg symbol temp)
113   `(progn
114     (inst mov ,temp
115      (make-ea :qword
116       :disp (+ nil-value
117                (static-symbol-offset ',symbol)
118                (ash symbol-tls-index-slot word-shift)
119                (- other-pointer-lowtag))))
120     (inst fs-segment-prefix)
121     (inst mov (make-ea :qword :scale 1 :index ,temp) ,reg)))
122 #!-sb-thread
123 (defmacro store-tl-symbol-value (reg symbol temp)
124   (declare (ignore temp))
125   `(store-symbol-value ,reg ,symbol))
126   
127 (defmacro load-type (target source &optional (offset 0))
128   #!+sb-doc
129   "Loads the type bits of a pointer into target independent of
130    byte-ordering issues."
131   (once-only ((n-target target)
132               (n-source source)
133               (n-offset offset))
134     (ecase *backend-byte-order*
135       (:little-endian
136        `(inst mov ,n-target
137               (make-ea :byte :base ,n-source :disp ,n-offset)))
138       (:big-endian
139        `(inst mov ,n-target
140               (make-ea :byte :base ,n-source :disp (+ ,n-offset 4)))))))
141 \f
142 ;;;; allocation helpers
143
144 ;;; All allocation is done by calls to assembler routines that
145 ;;; eventually invoke the C alloc() function.
146
147 ;;; Emit code to allocate an object with a size in bytes given by
148 ;;; Size. The size may be an integer of a TN. If Inline is a VOP
149 ;;; node-var then it is used to make an appropriate speed vs size
150 ;;; decision.
151
152 ;;; This macro should only be used inside a pseudo-atomic section,
153 ;;; which should also cover subsequent initialization of the
154 ;;; object.
155 (defun allocation-tramp (alloc-tn size &optional ignored)
156   (declare (ignore ignored))
157   (inst push size)
158   (inst lea r13-tn (make-ea :qword
159                             :disp (make-fixup "alloc_tramp" :foreign)))
160   (inst call r13-tn)
161   (inst pop alloc-tn)
162   (values))
163
164 (defun allocation (alloc-tn size &optional ignored)
165   (declare (ignore ignored))
166   (let ((not-inline (gen-label))
167         (done (gen-label))
168         ;; Yuck.
169         (in-elsewhere (eq *elsewhere* sb!assem::**current-segment**))
170         (free-pointer
171          (make-ea :qword :disp 
172                   #!+sb-thread (* n-word-bytes thread-alloc-region-slot)
173                   #!-sb-thread (make-fixup "boxed_region" :foreign)
174                   :scale 1))            ; thread->alloc_region.free_pointer
175         (end-addr 
176          (make-ea :qword :disp
177                   #!+sb-thread (* n-word-bytes (1+ thread-alloc-region-slot))
178                   #!-sb-thread (make-fixup "boxed_region" :foreign 8)
179                   :scale 1)))           ; thread->alloc_region.end_addr
180     (cond (in-elsewhere
181            (allocation-tramp alloc-tn size))
182           (t
183            (unless (and (tn-p size) (location= alloc-tn size))
184              (inst mov alloc-tn size))
185            #!+sb-thread (inst fs-segment-prefix)
186            (inst add alloc-tn free-pointer)
187            #!+sb-thread (inst fs-segment-prefix)
188            (inst cmp end-addr alloc-tn)
189            (inst jmp :be NOT-INLINE)
190            #!+sb-thread (inst fs-segment-prefix)
191            (inst xchg free-pointer alloc-tn)
192            (emit-label DONE)
193            (assemble (*elsewhere*)
194              (emit-label NOT-INLINE)
195              (cond ((numberp size)
196                     (allocation-tramp alloc-tn size))
197                    (t
198                     (inst sub alloc-tn free-pointer)
199                     (allocation-tramp alloc-tn alloc-tn)))
200              (inst jmp DONE))
201            (values)))))
202
203 #+nil
204 (defun allocation (alloc-tn size &optional ignored)
205   (declare (ignore ignored))
206   (inst push size)
207   (inst lea r13-tn (make-ea :qword
208                             :disp (make-fixup "alloc_tramp" :foreign)))
209   (inst call r13-tn)
210   (inst pop alloc-tn)
211   (values))
212
213 ;;; Allocate an other-pointer object of fixed SIZE with a single word
214 ;;; header having the specified WIDETAG value. The result is placed in
215 ;;; RESULT-TN.
216 (defmacro with-fixed-allocation ((result-tn widetag size &optional inline)
217                                  &rest forms)
218   `(pseudo-atomic
219     (allocation ,result-tn (pad-data-block ,size) ,inline)
220     (storew (logior (ash (1- ,size) n-widetag-bits) ,widetag)
221             ,result-tn)
222     (inst lea ,result-tn
223           (make-ea :qword :base ,result-tn :disp other-pointer-lowtag))
224     ,@forms))
225 \f
226 ;;;; error code
227 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
228   (defun emit-error-break (vop kind code values)
229     (let ((vector (gensym)))
230       `((inst int 3)                            ; i386 breakpoint instruction
231         ;; The return PC points here; note the location for the debugger.
232         (let ((vop ,vop))
233           (when vop
234                 (note-this-location vop :internal-error)))
235         (inst byte ,kind)                       ; eg trap_Xyyy
236         (with-adjustable-vector (,vector)       ; interr arguments
237           (write-var-integer (error-number-or-lose ',code) ,vector)
238           ,@(mapcar (lambda (tn)
239                       `(let ((tn ,tn))
240                          ;; classic CMU CL comment:
241                          ;;   zzzzz jrd here. tn-offset is zero for constant
242                          ;;   tns.
243                          (write-var-integer (make-sc-offset (sc-number
244                                                              (tn-sc tn))
245                                                             (or (tn-offset tn)
246                                                                 0))
247                                             ,vector)))
248                     values)
249           (inst byte (length ,vector))
250           (dotimes (i (length ,vector))
251             (inst byte (aref ,vector i))))))))
252
253 (defmacro error-call (vop error-code &rest values)
254   #!+sb-doc
255   "Cause an error. ERROR-CODE is the error to cause."
256   (cons 'progn
257         (emit-error-break vop error-trap error-code values)))
258
259 (defmacro generate-error-code (vop error-code &rest values)
260   #!+sb-doc
261   "Generate-Error-Code Error-code Value*
262   Emit code for an error with the specified Error-Code and context Values."
263   `(assemble (*elsewhere*)
264      (let ((start-lab (gen-label)))
265        (emit-label start-lab)
266        (error-call ,vop ,error-code ,@values)
267        start-lab)))
268
269 \f
270 ;;;; PSEUDO-ATOMIC
271
272 ;;; This is used to wrap operations which leave untagged memory lying
273 ;;; around.  It's an operation which the AOP weenies would describe as
274 ;;; having "cross-cutting concerns", meaning it appears all over the
275 ;;; place and there's no logical single place to attach documentation.
276 ;;; grep (mostly in src/runtime) is your friend 
277
278 ;;; FIXME: *PSEUDO-ATOMIC-FOO* could be made into *PSEUDO-ATOMIC-BITS*,
279 ;;; set with a single operation and cleared with SHR *PSEUDO-ATOMIC-BITS*,-2;
280 ;;; the ATOMIC bit is bit 0, the INTERRUPTED bit is bit 1, and you check
281 ;;; the C flag after the shift to see whether you were interrupted.
282
283 (defmacro pseudo-atomic (&rest forms)
284   (with-unique-names (label)
285     `(let ((,label (gen-label)))
286       ;; FIXME: The MAKE-EA noise should become a MACROLET macro or
287       ;; something. (perhaps SVLB, for static variable low byte)
288       (inst mov (make-ea :byte :disp (+ nil-value
289                                         (static-symbol-offset
290                                          '*pseudo-atomic-interrupted*)
291                                         (ash symbol-value-slot word-shift)
292                                         ;; FIXME: Use mask, not minus, to
293                                         ;; take out type bits.
294                                         (- other-pointer-lowtag)))
295        0)
296       (inst mov (make-ea :byte :disp (+ nil-value
297                                         (static-symbol-offset
298                                          '*pseudo-atomic-atomic*)
299                                         (ash symbol-value-slot word-shift)
300                                         (- other-pointer-lowtag)))
301        (fixnumize 1))
302       ,@forms
303       (inst mov (make-ea :byte :disp (+ nil-value
304                                         (static-symbol-offset
305                                          '*pseudo-atomic-atomic*)
306                                         (ash symbol-value-slot word-shift)
307                                         (- other-pointer-lowtag)))
308        0)
309       ;; KLUDGE: Is there any requirement for interrupts to be
310       ;; handled in order? It seems as though an interrupt coming
311       ;; in at this point will be executed before any pending interrupts.
312       ;; Or do incoming interrupts check to see whether any interrupts
313       ;; are pending? I wish I could find the documentation for
314       ;; pseudo-atomics.. -- WHN 19991130
315       (inst cmp (make-ea :byte
316                  :disp (+ nil-value
317                           (static-symbol-offset
318                            '*pseudo-atomic-interrupted*)
319                           (ash symbol-value-slot word-shift)
320                           (- other-pointer-lowtag)))
321        0)
322       (inst jmp :eq ,label)
323       ;; if PAI was set, interrupts were disabled at the same time
324       ;; using the process signal mask.  
325       (inst break pending-interrupt-trap)
326       (emit-label ,label))))
327
328
329 \f
330 ;;;; indexed references
331
332 (defmacro define-full-reffer (name type offset lowtag scs el-type &optional translate)
333   `(progn
334      (define-vop (,name)
335        ,@(when translate
336            `((:translate ,translate)))
337        (:policy :fast-safe)
338        (:args (object :scs (descriptor-reg))
339               (index :scs (any-reg)))
340        (:arg-types ,type tagged-num)
341        (:results (value :scs ,scs))
342        (:result-types ,el-type)
343        (:generator 3                    ; pw was 5
344          (inst mov value (make-ea :qword :base object :index index
345                                   :disp (- (* ,offset n-word-bytes)
346                                            ,lowtag)))))
347      (define-vop (,(symbolicate name "-C"))
348        ,@(when translate
349            `((:translate ,translate)))
350        (:policy :fast-safe)
351        (:args (object :scs (descriptor-reg)))
352        (:info index)
353        (:arg-types ,type
354                    (:constant (load/store-index ,n-word-bytes ,(eval lowtag)
355                                                 ,(eval offset))))
356        (:results (value :scs ,scs))
357        (:result-types ,el-type)
358        (:generator 2                    ; pw was 5
359          (inst mov value (make-ea :qword :base object
360                                   :disp (- (* (+ ,offset index) n-word-bytes)
361                                            ,lowtag)))))))
362
363 (defmacro define-full-setter (name type offset lowtag scs el-type &optional translate)
364   `(progn
365      (define-vop (,name)
366        ,@(when translate
367            `((:translate ,translate)))
368        (:policy :fast-safe)
369        (:args (object :scs (descriptor-reg))
370               (index :scs (any-reg))
371               (value :scs ,scs :target result))
372        (:arg-types ,type tagged-num ,el-type)
373        (:results (result :scs ,scs))
374        (:result-types ,el-type)
375        (:generator 4                    ; was 5
376          (inst mov (make-ea :qword :base object :index index
377                             :disp (- (* ,offset n-word-bytes) ,lowtag))
378                value)
379          (move result value)))
380      (define-vop (,(symbolicate name "-C"))
381        ,@(when translate
382            `((:translate ,translate)))
383        (:policy :fast-safe)
384        (:args (object :scs (descriptor-reg))
385               (value :scs ,scs :target result))
386        (:info index)
387        (:arg-types ,type
388                    (:constant (load/store-index ,n-word-bytes ,(eval lowtag)
389                                                 ,(eval offset)))
390                    ,el-type)
391        (:results (result :scs ,scs))
392        (:result-types ,el-type)
393        (:generator 3                    ; was 5
394          (inst mov (make-ea :qword :base object
395                             :disp (- (* (+ ,offset index) n-word-bytes)
396                                      ,lowtag))
397                value)
398          (move result value)))))
399
400 ;;; helper for alien stuff.
401 (defmacro with-pinned-objects ((&rest objects) &body body)
402   "Arrange with the garbage collector that the pages occupied by
403 OBJECTS will not be moved in memory for the duration of BODY.
404 Useful for e.g. foreign calls where another thread may trigger
405 garbage collection"
406   `(multiple-value-prog1
407        (progn
408          ,@(loop for p in objects 
409                  collect `(push-word-on-c-stack
410                            (int-sap (sb!kernel:get-lisp-obj-address ,p))))
411          ,@body)
412      ;; If the body returned normally, we should restore the stack pointer
413      ;; for the benefit of any following code in the same function.  If
414      ;; there's a non-local exit in the body, sp is garbage anyway and
415      ;; will get set appropriately from {a, the} frame pointer before it's
416      ;; next needed
417      (pop-words-from-c-stack ,(length objects))))