Eliminate COLD-FSET. It's just fop-funcall of %DEFUN
[sbcl.git] / src / compiler / x86-64 / c-call.lisp
blobda567fd6f5f9e3b0297172ec6fbabd9b399aac78
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
5 ;;;; more information.
6 ;;;;
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.
13 (in-package "SB!VM")
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 (defun my-make-wired-tn (prim-type-name sc-name offset)
21 (make-wired-tn (primitive-type-or-lose prim-type-name)
22 (sc-number-or-lose sc-name)
23 offset))
25 (defstruct (arg-state (:copier nil))
26 (register-args 0)
27 (xmm-args 0)
28 (stack-frame-size 0))
30 (defconstant max-int-args #.(length *c-call-register-arg-offsets*))
31 (defconstant max-xmm-args #!+win32 4 #!-win32 8)
33 (defun int-arg (state prim-type reg-sc stack-sc)
34 (let ((reg-args (max (arg-state-register-args state)
35 #!+win32 (arg-state-xmm-args state))))
36 (cond ((< reg-args max-int-args)
37 (setf (arg-state-register-args state) (1+ reg-args))
38 (my-make-wired-tn prim-type reg-sc
39 (nth reg-args *c-call-register-arg-offsets*)))
41 (let ((frame-size (arg-state-stack-frame-size state)))
42 (setf (arg-state-stack-frame-size state) (1+ frame-size))
43 (my-make-wired-tn prim-type stack-sc frame-size))))))
45 (define-alien-type-method (integer :arg-tn) (type state)
46 (if (alien-integer-type-signed type)
47 (int-arg state 'signed-byte-64 'signed-reg 'signed-stack)
48 (int-arg state 'unsigned-byte-64 'unsigned-reg 'unsigned-stack)))
50 (define-alien-type-method (system-area-pointer :arg-tn) (type state)
51 (declare (ignore type))
52 (int-arg state 'system-area-pointer 'sap-reg 'sap-stack))
54 (defun float-arg (state prim-type reg-sc stack-sc)
55 (let ((xmm-args (max (arg-state-xmm-args state)
56 #!+win32 (arg-state-register-args state))))
57 (cond ((< xmm-args max-xmm-args)
58 (setf (arg-state-xmm-args state) (1+ xmm-args))
59 (my-make-wired-tn prim-type reg-sc
60 (nth xmm-args *float-regs*)))
62 (let ((frame-size (arg-state-stack-frame-size state)))
63 (setf (arg-state-stack-frame-size state) (1+ frame-size))
64 (my-make-wired-tn prim-type stack-sc frame-size))))))
66 (define-alien-type-method (double-float :arg-tn) (type state)
67 (declare (ignore type))
68 (float-arg state 'double-float 'double-reg 'double-stack))
70 (define-alien-type-method (single-float :arg-tn) (type state)
71 (declare (ignore type))
72 (float-arg state 'single-float 'single-reg 'single-stack))
74 (defstruct (result-state (:copier nil))
75 (num-results 0))
77 (defun result-reg-offset (slot)
78 (ecase slot
79 (0 eax-offset)
80 (1 edx-offset)))
82 (define-alien-type-method (integer :result-tn) (type state)
83 (let ((num-results (result-state-num-results state)))
84 (setf (result-state-num-results state) (1+ num-results))
85 (multiple-value-bind (ptype reg-sc)
86 (if (alien-integer-type-signed type)
87 (values 'signed-byte-64 'signed-reg)
88 (values 'unsigned-byte-64 'unsigned-reg))
89 (my-make-wired-tn ptype reg-sc (result-reg-offset num-results)))))
91 (define-alien-type-method (integer :naturalize-gen) (type alien)
92 (if (<= (alien-type-bits type) 32)
93 (if (alien-integer-type-signed type)
94 `(sign-extend ,alien ,(alien-type-bits type))
95 `(logand ,alien ,(1- (ash 1 (alien-type-bits type)))))
96 alien))
98 (define-alien-type-method (system-area-pointer :result-tn) (type state)
99 (declare (ignore type))
100 (let ((num-results (result-state-num-results state)))
101 (setf (result-state-num-results state) (1+ num-results))
102 (my-make-wired-tn 'system-area-pointer 'sap-reg
103 (result-reg-offset num-results))))
105 (define-alien-type-method (double-float :result-tn) (type state)
106 (declare (ignore type))
107 (let ((num-results (result-state-num-results state)))
108 (setf (result-state-num-results state) (1+ num-results))
109 (my-make-wired-tn 'double-float 'double-reg num-results)))
111 (define-alien-type-method (single-float :result-tn) (type state)
112 (declare (ignore type))
113 (let ((num-results (result-state-num-results state)))
114 (setf (result-state-num-results state) (1+ num-results))
115 (my-make-wired-tn 'single-float 'single-reg num-results)))
117 (define-alien-type-method (values :result-tn) (type state)
118 (let ((values (alien-values-type-values type)))
119 (when (> (length values) 2)
120 (error "Too many result values from c-call."))
121 (mapcar (lambda (type)
122 (invoke-alien-type-method :result-tn type state))
123 values)))
125 (defun make-call-out-tns (type)
126 (let ((arg-state (make-arg-state)))
127 (collect ((arg-tns))
128 (dolist (arg-type (alien-fun-type-arg-types type))
129 (arg-tns (invoke-alien-type-method :arg-tn arg-type arg-state)))
130 (values (my-make-wired-tn 'positive-fixnum 'any-reg esp-offset)
131 (* (arg-state-stack-frame-size arg-state) n-word-bytes)
132 (arg-tns)
133 (invoke-alien-type-method :result-tn
134 (alien-fun-type-result-type type)
135 (make-result-state))))))
138 (deftransform %alien-funcall ((function type &rest args) * * :node node)
139 (aver (sb!c::constant-lvar-p type))
140 (let* ((type (sb!c::lvar-value type))
141 (env (sb!c::node-lexenv node))
142 (arg-types (alien-fun-type-arg-types type))
143 (result-type (alien-fun-type-result-type type)))
144 (aver (= (length arg-types) (length args)))
145 (if (or (some #'(lambda (type)
146 (and (alien-integer-type-p type)
147 (> (sb!alien::alien-integer-type-bits type) 64)))
148 arg-types)
149 (and (alien-integer-type-p result-type)
150 (> (sb!alien::alien-integer-type-bits result-type) 64)))
151 (collect ((new-args) (lambda-vars) (new-arg-types))
152 (dolist (type arg-types)
153 (let ((arg (gensym)))
154 (lambda-vars arg)
155 (cond ((and (alien-integer-type-p type)
156 (> (sb!alien::alien-integer-type-bits type) 64))
157 ;; CLH: FIXME! This should really be
158 ;; #xffffffffffffffff. nyef says: "Passing
159 ;; 128-bit integers to ALIEN functions on x86-64
160 ;; believed to be broken."
161 (new-args `(logand ,arg #xffffffff))
162 (new-args `(ash ,arg -64))
163 (new-arg-types (parse-alien-type '(unsigned 64) env))
164 (if (alien-integer-type-signed type)
165 (new-arg-types (parse-alien-type '(signed 64) env))
166 (new-arg-types (parse-alien-type '(unsigned 64) env))))
168 (new-args arg)
169 (new-arg-types type)))))
170 (cond ((and (alien-integer-type-p result-type)
171 (> (sb!alien::alien-integer-type-bits result-type) 64))
172 (let ((new-result-type
173 (let ((sb!alien::*values-type-okay* t))
174 (parse-alien-type
175 (if (alien-integer-type-signed result-type)
176 '(values (unsigned 64) (signed 64))
177 '(values (unsigned 64) (unsigned 64)))
178 env))))
179 `(lambda (function type ,@(lambda-vars))
180 (declare (ignore type))
181 (multiple-value-bind (low high)
182 (%alien-funcall function
183 ',(make-alien-fun-type
184 :arg-types (new-arg-types)
185 :result-type new-result-type)
186 ,@(new-args))
187 (logior low (ash high 64))))))
189 `(lambda (function type ,@(lambda-vars))
190 (declare (ignore type))
191 (%alien-funcall function
192 ',(make-alien-fun-type
193 :arg-types (new-arg-types)
194 :result-type result-type)
195 ,@(new-args))))))
196 (sb!c::give-up-ir1-transform))))
198 ;;; The ABI is vague about how signed sub-word integer return values
199 ;;; are handled, but since gcc versions >=4.3 no longer do sign
200 ;;; extension in the callee, we need to do it in the caller. FIXME:
201 ;;; If the value to be extended is known to already be of the target
202 ;;; type at compile time, we can (and should) elide the extension.
203 (defknown sign-extend ((signed-byte 64) t) fixnum
204 (foldable flushable movable))
206 (define-vop (sign-extend)
207 (:translate sign-extend)
208 (:policy :fast-safe)
209 (:args (val :scs (signed-reg)))
210 (:arg-types signed-num (:constant fixnum))
211 (:info size)
212 (:results (res :scs (signed-reg)))
213 (:result-types fixnum)
214 (:generator 1
215 (inst movsxd res
216 (make-random-tn :kind :normal
217 :sc (sc-or-lose (ecase size
218 (8 'byte-reg)
219 (16 'word-reg)
220 (32 'dword-reg)))
221 :offset (tn-offset val)))))
223 #-sb-xc-host
224 (defun sign-extend (x size)
225 (declare (type (signed-byte 64) x))
226 (ecase size
227 (8 (sign-extend x size))
228 (16 (sign-extend x size))
229 (32 (sign-extend x size))))
231 #+sb-xc-host
232 (defun sign-extend (x size)
233 (if (logbitp (1- size) x)
234 (dpb x (byte size 0) -1)
237 (define-vop (foreign-symbol-sap)
238 (:translate foreign-symbol-sap)
239 (:policy :fast-safe)
240 (:args)
241 (:arg-types (:constant simple-string))
242 (:info foreign-symbol)
243 (:results (res :scs (sap-reg)))
244 (:result-types system-area-pointer)
245 (:generator 2
246 (inst mov res (make-fixup foreign-symbol :foreign))))
248 #!+linkage-table
249 (define-vop (foreign-symbol-dataref-sap)
250 (:translate foreign-symbol-dataref-sap)
251 (:policy :fast-safe)
252 (:args)
253 (:arg-types (:constant simple-string))
254 (:info foreign-symbol)
255 (:results (res :scs (sap-reg)))
256 (:result-types system-area-pointer)
257 (:generator 2
258 (inst mov res (make-fixup foreign-symbol :foreign-dataref))))
260 (define-vop (call-out)
261 (:args (function :scs (sap-reg)
262 :target rbx)
263 (args :more t))
264 (:results (results :more t))
265 ;; RBX is used to first load the address, allowing the debugger to
266 ;; determine which alien was accessed in case it's undefined.
267 (:temporary (:sc sap-reg :offset rbx-offset) rbx)
268 (:temporary (:sc unsigned-reg :offset rax-offset :to :result) rax)
269 ;; For safepoint builds: Force values of non-volatiles to the stack.
270 ;; These are the callee-saved registers in the native ABI, but
271 ;; safepoint-based GC needs to see all Lisp values on the stack. Note
272 ;; that R12-R15 are non-volatile registers, but there is no need to
273 ;; spill R12 because it is our thread-base-tn. RDI and RSI are
274 ;; non-volatile on Windows, but argument passing registers on other
275 ;; platforms.
276 #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r13-offset) r13)
277 #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r14-offset) r14)
278 #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r15-offset) r15)
279 #!+(and sb-safepoint win32) (:temporary
280 (:sc unsigned-reg :offset rdi-offset) rdi)
281 #!+(and sb-safepoint win32) (:temporary
282 (:sc unsigned-reg :offset rsi-offset) rsi)
283 (:ignore results
284 #!+(and sb-safepoint win32) rdi
285 #!+(and sb-safepoint win32) rsi
286 #!+win32 args
287 #!+win32 rax
288 #!+sb-safepoint r15
289 #!+sb-safepoint r13)
290 (:vop-var vop)
291 (:save-p t)
292 (:generator 0
293 ;; ABI: Direction flag must be clear on function entry. -- JES, 2006-01-20
294 (inst cld)
295 #!+sb-safepoint
296 (progn
297 ;; Current PC - don't rely on function to keep it in a form that
298 ;; GC understands
299 (let ((label (gen-label)))
300 (inst lea r14 (make-fixup nil :code-object label))
301 (emit-label label)))
302 #!-win32
303 ;; ABI: AL contains amount of arguments passed in XMM registers
304 ;; for vararg calls.
305 (move-immediate rax
306 (loop for tn-ref = args then (tn-ref-across tn-ref)
307 while tn-ref
308 count (eq (sb-name (sc-sb (tn-sc (tn-ref-tn tn-ref))))
309 'float-registers)))
310 #!+win32 (inst sub rsp-tn #x20) ;MS_ABI: shadow zone
311 #!+sb-safepoint
312 (progn ;Store SP and PC in thread struct
313 (storew rsp-tn thread-base-tn thread-saved-csp-offset)
314 (storew r14 thread-base-tn thread-pc-around-foreign-call-slot))
315 (move rbx function)
316 (inst call rbx)
317 #!+win32 (inst add rsp-tn #x20) ;MS_ABI: remove shadow space
318 #!+sb-safepoint
319 (progn
320 ;; Zeroing out
321 (inst xor r14 r14)
322 ;; Zero PC storage place. NB. CSP-then-PC: same sequence on
323 ;; entry/exit, is actually corrent.
324 (storew r14 thread-base-tn thread-saved-csp-offset)
325 (storew r14 thread-base-tn thread-pc-around-foreign-call-slot))
326 ;; To give the debugger a clue. XX not really internal-error?
327 (note-this-location vop :internal-error)))
329 (define-vop (alloc-number-stack-space)
330 (:info amount)
331 (:results (result :scs (sap-reg any-reg)))
332 (:result-types system-area-pointer)
333 (:generator 0
334 (aver (location= result rsp-tn))
335 (unless (zerop amount)
336 (let ((delta (logandc2 (+ amount 7) 7)))
337 (inst sub rsp-tn delta)))
338 ;; C stack must be 16 byte aligned
339 (inst and rsp-tn -16)
340 (move result rsp-tn)))
342 (define-vop (dealloc-number-stack-space)
343 (:info amount)
344 (:generator 0
345 (unless (zerop amount)
346 (let ((delta (logandc2 (+ amount 7) 7)))
347 (inst add rsp-tn delta)))))
349 (macrolet ((alien-stack-ptr ()
350 #!+sb-thread '(symbol-known-tls-cell '*alien-stack-pointer*)
351 #!-sb-thread '(static-symbol-value-ea '*alien-stack-pointer*)))
352 (define-vop (alloc-alien-stack-space)
353 (:info amount)
354 (:results (result :scs (sap-reg any-reg)))
355 (:result-types system-area-pointer)
356 (:generator 0
357 (aver (not (location= result rsp-tn)))
358 (unless (zerop amount)
359 (let ((delta (logandc2 (+ amount 7) 7)))
360 (inst sub (alien-stack-ptr) delta)))
361 (inst mov result (alien-stack-ptr)))))
363 ;;; not strictly part of the c-call convention, but needed for the
364 ;;; WITH-PINNED-OBJECTS macro used for "locking down" lisp objects so
365 ;;; that GC won't move them while foreign functions go to work.
366 (define-vop (touch-object)
367 (:translate touch-object)
368 (:args (object))
369 (:ignore object)
370 (:policy :fast-safe)
371 (:arg-types t)
372 (:generator 0))
374 ;;; Callbacks
376 #-sb-xc-host
377 (defun alien-callback-accessor-form (type sp offset)
378 `(deref (sap-alien (sap+ ,sp ,offset) (* ,type))))
380 #-sb-xc-host
381 (defun alien-callback-assembler-wrapper (index result-type argument-types)
382 (labels ((make-tn-maker (sc-name)
383 (lambda (offset)
384 (make-random-tn :kind :normal
385 :sc (sc-or-lose sc-name)
386 :offset offset))))
387 (let* ((segment (make-segment))
388 (rax rax-tn)
389 #!+(or win32 (not sb-safepoint)) (rcx rcx-tn)
390 #!-win32 (rdi rdi-tn)
391 #!-win32 (rsi rsi-tn)
392 (rdx rdx-tn)
393 (rbp rbp-tn)
394 (rsp rsp-tn)
395 #!+win32 (r8 r8-tn)
396 (xmm0 float0-tn)
397 ([rsp] (make-ea :qword :base rsp :disp 0))
398 ;; How many arguments have been copied
399 (arg-count 0)
400 ;; How many arguments have been copied from the stack
401 (stack-argument-count #!-win32 0 #!+win32 4)
402 (gprs (mapcar (make-tn-maker 'any-reg) *c-call-register-arg-offsets*))
403 (fprs (mapcar (make-tn-maker 'double-reg)
404 ;; Only 8 first XMM registers are used for
405 ;; passing arguments
406 (subseq *float-regs* 0 #!-win32 8 #!+win32 4))))
407 (assemble (segment)
408 ;; Make room on the stack for arguments.
409 (inst sub rsp (* n-word-bytes (length argument-types)))
410 ;; Copy arguments from registers to stack
411 (dolist (type argument-types)
412 (let ((integerp (not (alien-float-type-p type)))
413 ;; A TN pointing to the stack location where the
414 ;; current argument should be stored for the purposes
415 ;; of ENTER-ALIEN-CALLBACK.
416 (target-tn (make-ea :qword :base rsp
417 :disp (* arg-count
418 n-word-bytes)))
419 ;; A TN pointing to the stack location that contains
420 ;; the next argument passed on the stack.
421 (stack-arg-tn (make-ea :qword :base rsp
422 :disp (* (+ 1
423 (length argument-types)
424 stack-argument-count)
425 n-word-bytes))))
426 (incf arg-count)
427 (cond (integerp
428 (let ((gpr (pop gprs)))
429 #!+win32 (pop fprs)
430 ;; Argument not in register, copy it from the old
431 ;; stack location to a temporary register.
432 (unless gpr
433 (incf stack-argument-count)
434 (setf gpr temp-reg-tn)
435 (inst mov gpr stack-arg-tn))
436 ;; Copy from either argument register or temporary
437 ;; register to target.
438 (inst mov target-tn gpr)))
439 ((or (alien-single-float-type-p type)
440 (alien-double-float-type-p type))
441 (let ((fpr (pop fprs)))
442 #!+win32 (pop gprs)
443 (cond (fpr
444 ;; Copy from float register to target location.
445 (inst movq target-tn fpr))
447 ;; Not in float register. Copy from stack to
448 ;; temporary (general purpose) register, and
449 ;; from there to the target location.
450 (incf stack-argument-count)
451 (inst mov temp-reg-tn stack-arg-tn)
452 (inst mov target-tn temp-reg-tn)))))
454 (bug "Unknown alien floating point type: ~S" type)))))
456 #!-sb-safepoint
457 (progn
458 ;; arg0 to FUNCALL3 (function)
460 ;; Indirect the access to ENTER-ALIEN-CALLBACK through
461 ;; the symbol-value slot of SB-ALIEN::*ENTER-ALIEN-CALLBACK*
462 ;; to ensure it'll work even if the GC moves ENTER-ALIEN-CALLBACK.
463 ;; Skip any SB-THREAD TLS magic, since we don't expect anyone
464 ;; to rebind the variable. -- JES, 2006-01-01
465 (inst mov rdi (+ nil-value (static-symbol-offset
466 'sb!alien::*enter-alien-callback*)))
467 (loadw rdi rdi symbol-value-slot other-pointer-lowtag)
468 ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
469 (inst mov rsi (fixnumize index))
470 ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
471 (inst mov rdx rsp)
472 ;; add room on stack for return value
473 (inst sub rsp 8)
474 ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
475 (inst mov rcx rsp)
477 ;; Make new frame
478 (inst push rbp)
479 (inst mov rbp rsp)
481 ;; Call
482 (inst mov rax (foreign-symbol-address "funcall3"))
483 (inst call rax)
485 ;; Back! Restore frame
486 (inst mov rsp rbp)
487 (inst pop rbp))
489 #!+sb-safepoint
490 (progn
491 ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
492 (inst mov #!-win32 rdi #!+win32 rcx (fixnumize index))
493 ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
494 (inst mov #!-win32 rsi #!+win32 rdx rsp)
495 ;; add room on stack for return value
496 (inst sub rsp 8)
497 ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
498 (inst mov #!-win32 rdx #!+win32 r8 rsp)
499 ;; Make new frame
500 (inst push rbp)
501 (inst mov rbp rsp)
502 #!+win32 (inst sub rsp #x20)
503 #!+win32 (inst and rsp #x-20)
504 ;; Call
505 (inst mov rax (foreign-symbol-address "callback_wrapper_trampoline"))
506 (inst call rax)
507 ;; Back! Restore frame
508 (inst mov rsp rbp)
509 (inst pop rbp))
511 ;; Result now on top of stack, put it in the right register
512 (cond
513 ((or (alien-integer-type-p result-type)
514 (alien-pointer-type-p result-type)
515 (alien-type-= #.(parse-alien-type 'system-area-pointer nil)
516 result-type))
517 (inst mov rax [rsp]))
518 ((or (alien-single-float-type-p result-type)
519 (alien-double-float-type-p result-type))
520 (inst movq xmm0 [rsp]))
521 ((alien-void-type-p result-type))
523 (error "Unrecognized alien type: ~A" result-type)))
525 ;; Pop the arguments and the return value from the stack to get
526 ;; the return address at top of stack.
527 (inst add rsp (* (1+ (length argument-types)) n-word-bytes))
528 ;; Return
529 (inst ret))
530 (finalize-segment segment)
531 ;; Now that the segment is done, convert it to a static
532 ;; vector we can point foreign code to.
533 (let ((buffer (sb!assem::segment-buffer segment)))
534 (make-static-vector (length buffer)
535 :element-type '(unsigned-byte 8)
536 :initial-contents buffer)))))