1 ;;;; the VOPs and other necessary machine specific support
2 ;;;; routines for call-out to C
4 ;;;; This software is part of the SBCL system. See the README file for
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
15 ;; The MOVE-ARG vop is going to store args on the stack for
16 ;; call-out. These tn's will be used for that. move-arg is normally
17 ;; used for things going down the stack but C wants to have args
18 ;; indexed in the positive direction.
20 (defstruct (arg-state (:copier nil
))
25 (defconstant max-int-args
#.
(length *c-call-register-arg-offsets
*))
26 (defconstant max-xmm-args
#!+win32
4 #!-win32
8)
28 (defun int-arg (state prim-type reg-sc stack-sc
)
29 (let ((reg-args (max (arg-state-register-args state
)
30 #!+win32
(arg-state-xmm-args state
))))
31 (cond ((< reg-args max-int-args
)
32 (setf (arg-state-register-args state
) (1+ reg-args
))
33 (make-wired-tn* prim-type reg-sc
34 (nth reg-args
*c-call-register-arg-offsets
*)))
36 (let ((frame-size (arg-state-stack-frame-size state
)))
37 (setf (arg-state-stack-frame-size state
) (1+ frame-size
))
38 (make-wired-tn* prim-type stack-sc frame-size
))))))
40 (define-alien-type-method (integer :arg-tn
) (type state
)
41 (if (alien-integer-type-signed type
)
42 (int-arg state
'signed-byte-64 signed-reg-sc-number signed-stack-sc-number
)
43 (int-arg state
'unsigned-byte-64 unsigned-reg-sc-number unsigned-stack-sc-number
)))
45 (define-alien-type-method (system-area-pointer :arg-tn
) (type state
)
46 (declare (ignore type
))
47 (int-arg state
'system-area-pointer sap-reg-sc-number sap-stack-sc-number
))
49 (defun float-arg (state prim-type reg-sc stack-sc
)
50 (let ((xmm-args (max (arg-state-xmm-args state
)
51 #!+win32
(arg-state-register-args state
))))
52 (cond ((< xmm-args max-xmm-args
)
53 (setf (arg-state-xmm-args state
) (1+ xmm-args
))
54 (make-wired-tn* prim-type reg-sc
55 (nth xmm-args
*float-regs
*)))
57 (let ((frame-size (arg-state-stack-frame-size state
)))
58 (setf (arg-state-stack-frame-size state
) (1+ frame-size
))
59 (make-wired-tn* prim-type stack-sc frame-size
))))))
61 (define-alien-type-method (double-float :arg-tn
) (type state
)
62 (declare (ignore type
))
63 (float-arg state
'double-float double-reg-sc-number double-stack-sc-number
))
65 (define-alien-type-method (single-float :arg-tn
) (type state
)
66 (declare (ignore type
))
67 (float-arg state
'single-float single-reg-sc-number single-stack-sc-number
))
69 (defstruct (result-state (:copier nil
))
72 (defun result-reg-offset (slot)
77 (define-alien-type-method (integer :result-tn
) (type state
)
78 (let ((num-results (result-state-num-results state
)))
79 (setf (result-state-num-results state
) (1+ num-results
))
80 (multiple-value-bind (ptype reg-sc
)
81 (if (alien-integer-type-signed type
)
82 (values 'signed-byte-64 signed-reg-sc-number
)
83 (values 'unsigned-byte-64 unsigned-reg-sc-number
))
84 (make-wired-tn* ptype reg-sc
(result-reg-offset num-results
)))))
86 (define-alien-type-method (integer :naturalize-gen
) (type alien
)
87 (if (<= (alien-type-bits type
) 32)
88 (if (alien-integer-type-signed type
)
89 `(sign-extend ,alien
,(alien-type-bits type
))
90 `(logand ,alien
,(1- (ash 1 (alien-type-bits type
)))))
93 (define-alien-type-method (system-area-pointer :result-tn
) (type state
)
94 (declare (ignore type
))
95 (let ((num-results (result-state-num-results state
)))
96 (setf (result-state-num-results state
) (1+ num-results
))
97 (make-wired-tn* 'system-area-pointer sap-reg-sc-number
98 (result-reg-offset num-results
))))
100 (define-alien-type-method (double-float :result-tn
) (type state
)
101 (declare (ignore type
))
102 (let ((num-results (result-state-num-results state
)))
103 (setf (result-state-num-results state
) (1+ num-results
))
104 (make-wired-tn* 'double-float double-reg-sc-number num-results
)))
106 (define-alien-type-method (single-float :result-tn
) (type state
)
107 (declare (ignore type
))
108 (let ((num-results (result-state-num-results state
)))
109 (setf (result-state-num-results state
) (1+ num-results
))
110 (make-wired-tn* 'single-float single-reg-sc-number num-results
)))
112 (define-alien-type-method (values :result-tn
) (type state
)
113 (let ((values (alien-values-type-values type
)))
114 (when (> (length values
) 2)
115 (error "Too many result values from c-call."))
116 (mapcar (lambda (type)
117 (invoke-alien-type-method :result-tn type state
))
120 (defun make-call-out-tns (type)
121 (let ((arg-state (make-arg-state)))
123 (dolist (arg-type (alien-fun-type-arg-types type
))
124 (arg-tns (invoke-alien-type-method :arg-tn arg-type arg-state
)))
125 (values (make-wired-tn* 'positive-fixnum any-reg-sc-number esp-offset
)
126 (* (arg-state-stack-frame-size arg-state
) n-word-bytes
)
128 (invoke-alien-type-method :result-tn
129 (alien-fun-type-result-type type
)
130 (make-result-state))))))
133 (deftransform %alien-funcall
((function type
&rest args
) * * :node node
)
134 (aver (sb!c
::constant-lvar-p type
))
135 (let* ((type (sb!c
::lvar-value type
))
136 (env (sb!c
::node-lexenv node
))
137 (arg-types (alien-fun-type-arg-types type
))
138 (result-type (alien-fun-type-result-type type
)))
139 (aver (= (length arg-types
) (length args
)))
140 (if (or (some #'(lambda (type)
141 (and (alien-integer-type-p type
)
142 (> (sb!alien
::alien-integer-type-bits type
) 64)))
144 (and (alien-integer-type-p result-type
)
145 (> (sb!alien
::alien-integer-type-bits result-type
) 64)))
146 (collect ((new-args) (lambda-vars) (new-arg-types))
147 (dolist (type arg-types
)
148 (let ((arg (gensym)))
150 (cond ((and (alien-integer-type-p type
)
151 (> (sb!alien
::alien-integer-type-bits type
) 64))
152 ;; CLH: FIXME! This should really be
153 ;; #xffffffffffffffff. nyef says: "Passing
154 ;; 128-bit integers to ALIEN functions on x86-64
155 ;; believed to be broken."
156 (new-args `(logand ,arg
#xffffffff
))
157 (new-args `(ash ,arg -
64))
158 (new-arg-types (parse-alien-type '(unsigned 64) env
))
159 (if (alien-integer-type-signed type
)
160 (new-arg-types (parse-alien-type '(signed 64) env
))
161 (new-arg-types (parse-alien-type '(unsigned 64) env
))))
164 (new-arg-types type
)))))
165 (cond ((and (alien-integer-type-p result-type
)
166 (> (sb!alien
::alien-integer-type-bits result-type
) 64))
167 (let ((new-result-type
168 (let ((sb!alien
::*values-type-okay
* t
))
170 (if (alien-integer-type-signed result-type
)
171 '(values (unsigned 64) (signed 64))
172 '(values (unsigned 64) (unsigned 64)))
174 `(lambda (function type
,@(lambda-vars))
175 (declare (ignore type
))
176 (multiple-value-bind (low high
)
177 (%alien-funcall function
178 ',(make-alien-fun-type
179 :arg-types
(new-arg-types)
180 :result-type new-result-type
)
182 (logior low
(ash high
64))))))
184 `(lambda (function type
,@(lambda-vars))
185 (declare (ignore type
))
186 (%alien-funcall function
187 ',(make-alien-fun-type
188 :arg-types
(new-arg-types)
189 :result-type result-type
)
191 (sb!c
::give-up-ir1-transform
))))
193 ;;; The ABI is vague about how signed sub-word integer return values
194 ;;; are handled, but since gcc versions >=4.3 no longer do sign
195 ;;; extension in the callee, we need to do it in the caller. FIXME:
196 ;;; If the value to be extended is known to already be of the target
197 ;;; type at compile time, we can (and should) elide the extension.
198 (defknown sign-extend
((signed-byte 64) t
) fixnum
199 (foldable flushable movable
))
201 (define-vop (sign-extend)
202 (:translate sign-extend
)
204 (:args
(val :scs
(signed-reg)))
205 (:arg-types signed-num
(:constant fixnum
))
207 (:results
(res :scs
(signed-reg)))
208 (:result-types fixnum
)
211 (make-random-tn :kind
:normal
212 :sc
(sc-or-lose (ecase size
216 :offset
(tn-offset val
)))))
219 (defun sign-extend (x size
)
220 (declare (type (signed-byte 64) x
))
222 (8 (sign-extend x size
))
223 (16 (sign-extend x size
))
224 (32 (sign-extend x size
))))
227 (defun sign-extend (x size
)
228 (if (logbitp (1- size
) x
)
229 (dpb x
(byte size
0) -
1)
232 (define-vop (foreign-symbol-sap)
233 (:translate foreign-symbol-sap
)
236 (:arg-types
(:constant simple-string
))
237 (:info foreign-symbol
)
238 (:results
(res :scs
(sap-reg)))
239 (:result-types system-area-pointer
)
241 (inst mov res
(make-fixup foreign-symbol
:foreign
))))
244 (define-vop (foreign-symbol-dataref-sap)
245 (:translate foreign-symbol-dataref-sap
)
248 (:arg-types
(:constant simple-string
))
249 (:info foreign-symbol
)
250 (:results
(res :scs
(sap-reg)))
251 (:result-types system-area-pointer
)
253 (inst mov res
(make-fixup foreign-symbol
:foreign-dataref
))))
256 (defconstant thread-saved-csp-offset -
1)
258 (define-vop (call-out)
259 (:args
(function :scs
(sap-reg)
262 (:results
(results :more t
))
263 ;; RBX is used to first load the address, allowing the debugger to
264 ;; determine which alien was accessed in case it's undefined.
265 (:temporary
(:sc sap-reg
:offset rbx-offset
:from
(:argument
0)) rbx
)
266 (:temporary
(:sc unsigned-reg
:offset rax-offset
:to
:result
) rax
)
268 (:temporary
(:sc unsigned-stack
:from
:eval
:to
:result
) pc-save
)
274 (emit-c-call vop rax rbx args
#!+sb-safepoint pc-save
)))
276 ;;; Calls to C can generally be made without loading a register
277 ;;; with the function. We receive the function name as an info argument.
278 (define-vop (call-out-named)
279 (:args
(args :more t
))
280 (:results
(results :more t
))
282 (:temporary
(:sc unsigned-reg
:offset rax-offset
:to
:result
) rax
)
284 (:temporary
(:sc unsigned-stack
:from
:eval
:to
:result
) pc-save
)
289 (emit-c-call vop rax c-symbol args
#!+sb-safepoint pc-save
)))
291 (defun emit-c-call (vop rax fun args
#!+sb-safepoint pc-save
)
292 ;; Current PC - don't rely on function to keep it in a form that
295 (let ((label (gen-label)))
296 (inst lea
(reg-in-size rax
:immobile-code-pc
) (make-fixup nil
:code-object label
))
298 (move-dword-if-immobile-code pc-save rax
))
299 (when sb
!c
::*msan-compatible-stack-unpoison
*
300 (inst mov rax
(static-symbol-value-ea 'msan-param-tls
))
301 ;; Unpoison parameters
302 (do ((n 0 (+ n n-word-bytes
))
303 (arg args
(tn-ref-across arg
)))
305 ;; KLUDGE: assume all parameters are 8 bytes or less
307 (inst mov
(make-ea :qword
:base rax
:disp n
) 0)))
309 ;; ABI: AL contains amount of arguments passed in XMM registers
312 (loop for tn-ref
= args then
(tn-ref-across tn-ref
)
314 count
(eq (sb-name (sc-sb (tn-sc (tn-ref-tn tn-ref
))))
317 ;; Store SP in thread struct
318 (storew rsp-tn thread-base-tn thread-saved-csp-offset
)
319 #!+win32
(inst sub rsp-tn
#x20
) ;MS_ABI: shadow zone
320 ;; From immobile space we use the "CALL rel32" format to the linkage
321 ;; table jump, and from dynamic space we use "CALL [ea]" format
322 ;; where ea is the address of the linkage table entry's operand.
323 ;; So while the former is a jump to a jump, we can optimize out
324 ;; one jump in a statically linked executable.
326 (inst call
(cond ((tn-p fun
) fun
)
327 ((sb!c
::code-immobile-p
(sb!c
::vop-node vop
))
328 (make-fixup fun
:foreign
))
329 (t (make-ea :qword
:disp
(make-fixup fun
:foreign
8)))))
330 (let ((*location-context
* (and (stringp fun
)
332 ;; For the undefined alien error
333 (note-this-location vop
:internal-error
))
334 #!+win32
(inst add rsp-tn
#x20
) ;MS_ABI: remove shadow space
336 ;; Zero the saved CSP
337 (inst xor
(make-ea-for-object-slot thread-base-tn thread-saved-csp-offset
0)
340 (define-vop (alloc-number-stack-space)
342 (:results
(result :scs
(sap-reg any-reg
)))
343 (:result-types system-area-pointer
)
345 (aver (location= result rsp-tn
))
346 (unless (zerop amount
)
347 (let ((delta (logandc2 (+ amount
7) 7)))
348 (inst sub rsp-tn delta
)))
349 ;; C stack must be 16 byte aligned
350 (inst and rsp-tn -
16)
351 (move result rsp-tn
)))
353 (macrolet ((alien-stack-ptr ()
354 #!+sb-thread
'(symbol-known-tls-cell '*alien-stack-pointer
*)
355 #!-sb-thread
'(static-symbol-value-ea '*alien-stack-pointer
*)))
356 (define-vop (alloc-alien-stack-space)
358 (:results
(result :scs
(sap-reg any-reg
)))
359 (:result-types system-area-pointer
)
361 (aver (not (location= result rsp-tn
)))
362 (unless (zerop amount
)
363 (let ((delta (logandc2 (+ amount
7) 7)))
364 (inst sub
(alien-stack-ptr) delta
)))
365 (inst mov result
(alien-stack-ptr)))))
367 ;;; not strictly part of the c-call convention, but needed for the
368 ;;; WITH-PINNED-OBJECTS macro used for "locking down" lisp objects so
369 ;;; that GC won't move them while foreign functions go to work.
370 (define-vop (touch-object)
371 (:translate touch-object
)
381 (defun alien-callback-accessor-form (type sp offset
)
382 `(deref (sap-alien (sap+ ,sp
,offset
) (* ,type
))))
385 (defun alien-callback-assembler-wrapper (index result-type argument-types
)
386 (labels ((make-tn-maker (sc-name)
388 (make-random-tn :kind
:normal
389 :sc
(sc-or-lose sc-name
)
391 (let* ((segment (make-segment))
393 #!+(or win32
(not sb-thread
)) (rcx rcx-tn
)
394 #!-
(and win32 sb-thread
) (rdi rdi-tn
)
395 #!-
(and win32 sb-thread
) (rsi rsi-tn
)
399 #!+(and win32 sb-thread
) (r8 r8-tn
)
401 ([rsp] (make-ea :qword :base rsp :disp 0))
402 ;; How many arguments have been copied
404 ;; How many arguments have been copied from the stack
405 (stack-argument-count #!-win32 0 #!+win32 4)
406 (gprs (mapcar (make-tn-maker 'any-reg) *c-call-register-arg-offsets*))
407 (fprs (mapcar (make-tn-maker 'double-reg)
408 ;; Only 8 first XMM registers are used for
410 (subseq *float-regs* 0 #!-win32 8 #!+win32 4))))
412 ;; Make room on the stack for arguments.
414 (inst sub rsp (* n-word-bytes (length argument-types))))
415 ;; Copy arguments from registers to stack
416 (dolist (type argument-types)
417 (let ((integerp (not (alien-float-type-p type)))
418 ;; A TN pointing to the stack location where the
419 ;; current argument should be stored for the purposes
420 ;; of ENTER-ALIEN-CALLBACK.
421 (target-tn (make-ea :qword :base rsp
424 ;; A TN pointing to the stack location that contains
425 ;; the next argument passed on the stack.
426 (stack-arg-tn (make-ea :qword :base rsp
428 (length argument-types)
429 stack-argument-count)
433 (let ((gpr (pop gprs)))
435 ;; Argument not in register, copy it from the old
436 ;; stack location to a temporary register.
438 (incf stack-argument-count)
439 (setf gpr temp-reg-tn)
440 (inst mov gpr stack-arg-tn))
441 ;; Copy from either argument register or temporary
442 ;; register to target.
443 (inst mov target-tn gpr)))
444 ((or (alien-single-float-type-p type)
445 (alien-double-float-type-p type))
446 (let ((fpr (pop fprs)))
449 ;; Copy from float register to target location.
450 (inst movq target-tn fpr))
452 ;; Not in float register. Copy from stack to
453 ;; temporary (general purpose) register, and
454 ;; from there to the target location.
455 (incf stack-argument-count)
456 (inst mov temp-reg-tn stack-arg-tn)
457 (inst mov target-tn temp-reg-tn)))))
459 (bug "Unknown alien floating point type: ~S" type)))))
463 ;; arg0 to FUNCALL3 (function)
464 (inst mov rdi (make-ea :qword :disp (static-fdefn-fun-addr 'enter-alien-callback)))
465 ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
466 (inst mov rsi (fixnumize index))
467 ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
469 ;; add room on stack for return value
470 (inst sub rsp (if (evenp arg-count)
473 ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
481 (inst mov rax (foreign-symbol-address "funcall3"))
484 ;; Back! Restore frame
490 ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
491 (inst mov #!-win32 rdi #!+win32 rcx (fixnumize index))
492 ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
493 (inst mov #!-win32 rsi #!+win32 rdx rsp)
494 ;; add room on stack for return value
495 (inst sub rsp (if (evenp arg-count)
498 ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
499 (inst mov #!-win32 rdx #!+win32 r8 rsp)
503 #!+win32 (inst sub rsp #x20)
504 #!+win32 (inst and rsp #x-20)
506 (inst mov rax (foreign-symbol-address "callback_wrapper_trampoline"))
508 ;; Back! Restore frame
512 ;; Result now on top of stack, put it in the right register
514 ((or (alien-integer-type-p result-type)
515 (alien-pointer-type-p result-type)
516 (alien-type-= #.(parse-alien-type 'system-area-pointer nil)
518 (inst mov rax [rsp]))
519 ((or (alien-single-float-type-p result-type
)
520 (alien-double-float-type-p result-type
))
521 (inst movq xmm0
[rsp]))
522 ((alien-void-type-p result-type))
524 (error "Unrecognized alien type: ~A" result-type)))
526 ;; Pop the arguments and the return value from the stack to get
527 ;; the return address at top of stack.
529 (inst add rsp (* (+ arg-count
530 ;; Plus the return value and make sure it's aligned
531 (if (evenp arg-count)
537 (finalize-segment segment)
538 ;; Now that the segment is done, convert it to a static
539 ;; vector we can point foreign code to.
540 (let ((buffer (sb!assem::segment-buffer segment)))
541 (make-static-vector (length buffer)
542 :element-type '(unsigned-byte 8)
543 :initial-contents buffer)))))