192de2223fbddaf817f959a4261d20a15066f27c
[sbcl.git] / src / compiler / x86-64 / c-call.lisp
1 ;;;; the VOPs and other necessary machine specific support
2 ;;;; routines for call-out to C
3
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.
12
13 (in-package "SB!VM")
14
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.
19
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))
24
25 (defstruct (arg-state (:copier nil))
26   (register-args 0)
27   (xmm-args 0)
28   (stack-frame-size 0))
29
30 (defconstant max-int-args #.(length *c-call-register-arg-offsets*))
31 (defconstant max-xmm-args #!+win32 4 #!-win32 8)
32
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*)))
40           (t
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))))))
44
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)))
49
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))
53
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*)))
61           (t
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))))))
65
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))
69
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))
73
74 (defstruct (result-state (:copier nil))
75   (num-results 0))
76
77 (defun result-reg-offset (slot)
78   (ecase slot
79     (0 eax-offset)
80     (1 edx-offset)))
81
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)))))
90
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))
97
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))))
104
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)))
110
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)))
116
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)))
124
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))))))
136
137
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))))
167                     (t
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))))))
188                 (t
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))))
197
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))
205
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)))))
222
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))))
230
231 #+sb-xc-host
232 (defun sign-extend (x size)
233   (if (logbitp (1- size) x)
234       (dpb x (byte size 0) -1)
235       x))
236
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))))
247
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))))
259
260 (define-vop (call-out)
261   (:args (function :scs (sap-reg))
262          (args :more t))
263   (:results (results :more t))
264   (:temporary (:sc unsigned-reg :offset rax-offset :to :result) rax)
265   ;; For safepoint builds: Force values of non-volatiles to the stack.
266   ;; These are the callee-saved registers in the native ABI, but
267   ;; safepoint-based GC needs to see all Lisp values on the stack.  Note
268   ;; that R12-R15 are non-volatile registers, but there is no need to
269   ;; spill R12 because it is our thread-base-tn.  RDI and RSI are
270   ;; non-volatile on Windows, but argument passing registers on other
271   ;; platforms.
272   #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r13-offset) r13)
273   #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r14-offset) r14)
274   #!+sb-safepoint (:temporary (:sc unsigned-reg :offset r15-offset) r15)
275   #!+(and sb-safepoint win32) (:temporary
276                                (:sc unsigned-reg :offset rdi-offset) rdi)
277   #!+(and sb-safepoint win32) (:temporary
278                                (:sc unsigned-reg :offset rsi-offset) rsi)
279   (:ignore results
280            #!+(and sb-safepoint win32) rdi
281            #!+(and sb-safepoint win32) rsi
282            #!+win32 args
283            #!+win32 rax
284            #!+sb-safepoint r15
285            #!+sb-safepoint r13)
286   (:vop-var vop)
287   (:save-p t)
288   (:generator 0
289     ;; ABI: Direction flag must be clear on function entry. -- JES, 2006-01-20
290     (inst cld)
291     #!+sb-safepoint
292     (progn
293       ;; Current PC - don't rely on function to keep it in a form that
294       ;; GC understands
295       (let ((label (gen-label)))
296         (inst lea r14 (make-fixup nil :code-object label))
297         (emit-label label)))
298     #!-win32
299     ;; ABI: AL contains amount of arguments passed in XMM registers
300     ;; for vararg calls.
301     (move-immediate rax
302                     (loop for tn-ref = args then (tn-ref-across tn-ref)
303                        while tn-ref
304                        count (eq (sb-name (sc-sb (tn-sc (tn-ref-tn tn-ref))))
305                                  'float-registers)))
306     #!+win32 (inst sub rsp-tn #x20)     ;MS_ABI: shadow zone
307     #!+sb-safepoint
308     (progn                              ;Store SP and PC in thread struct
309       (storew rsp-tn thread-base-tn thread-saved-csp-offset)
310       (storew r14 thread-base-tn thread-pc-around-foreign-call-slot))
311     (inst call function)
312     #!+win32 (inst add rsp-tn #x20)     ;MS_ABI: remove shadow space
313     #!+sb-safepoint
314     (progn
315       ;; Zeroing out
316       (inst xor r14 r14)
317       ;; Zero PC storage place. NB. CSP-then-PC: same sequence on
318       ;; entry/exit, is actually corrent.
319       (storew r14 thread-base-tn thread-saved-csp-offset)
320       (storew r14 thread-base-tn thread-pc-around-foreign-call-slot))
321     ;; To give the debugger a clue. XX not really internal-error?
322     (note-this-location vop :internal-error)))
323
324 (define-vop (alloc-number-stack-space)
325   (:info amount)
326   (:results (result :scs (sap-reg any-reg)))
327   (:result-types system-area-pointer)
328   (:generator 0
329     (aver (location= result rsp-tn))
330     (unless (zerop amount)
331       (let ((delta (logandc2 (+ amount 7) 7)))
332         (inst sub rsp-tn delta)))
333     ;; C stack must be 16 byte aligned
334     (inst and rsp-tn -16)
335     (move result rsp-tn)))
336
337 (define-vop (dealloc-number-stack-space)
338   (:info amount)
339   (:generator 0
340     (unless (zerop amount)
341       (let ((delta (logandc2 (+ amount 7) 7)))
342         (inst add rsp-tn delta)))))
343
344 (define-vop (alloc-alien-stack-space)
345   (:info amount)
346   #!+sb-thread (:temporary (:sc unsigned-reg) temp)
347   (:results (result :scs (sap-reg any-reg)))
348   (:result-types system-area-pointer)
349   #!+sb-thread
350   (:generator 0
351     (aver (not (location= result rsp-tn)))
352     (unless (zerop amount)
353       (let ((delta (logandc2 (+ amount 7) 7)))
354         (inst mov temp
355               (make-ea :qword
356                        :disp (+ nil-value
357                                 (static-symbol-offset '*alien-stack*)
358                                 (ash symbol-tls-index-slot word-shift)
359                                 (- other-pointer-lowtag))))
360         (inst sub (make-ea :qword :base thread-base-tn
361                            :scale 1 :index temp) delta)))
362     (load-tl-symbol-value result *alien-stack*))
363   #!-sb-thread
364   (:generator 0
365     (aver (not (location= result rsp-tn)))
366     (unless (zerop amount)
367       (let ((delta (logandc2 (+ amount 7) 7)))
368         (inst sub (make-ea :qword
369                            :disp (+ nil-value
370                                     (static-symbol-offset '*alien-stack*)
371                                     (ash symbol-value-slot word-shift)
372                                     (- other-pointer-lowtag)))
373               delta)))
374     (load-symbol-value result *alien-stack*)))
375
376 (define-vop (dealloc-alien-stack-space)
377   (:info amount)
378   #!+sb-thread (:temporary (:sc unsigned-reg) temp)
379   #!+sb-thread
380   (:generator 0
381     (unless (zerop amount)
382       (let ((delta (logandc2 (+ amount 7) 7)))
383         (inst mov temp
384               (make-ea :qword
385                        :disp (+ nil-value
386                                 (static-symbol-offset '*alien-stack*)
387                                 (ash symbol-tls-index-slot word-shift)
388                                 (- other-pointer-lowtag))))
389         (inst add (make-ea :qword :base thread-base-tn :scale 1 :index temp)
390               delta))))
391   #!-sb-thread
392   (:generator 0
393     (unless (zerop amount)
394       (let ((delta (logandc2 (+ amount 7) 7)))
395         (inst add (make-ea :qword
396                            :disp (+ nil-value
397                                     (static-symbol-offset '*alien-stack*)
398                                     (ash symbol-value-slot word-shift)
399                                     (- other-pointer-lowtag)))
400               delta)))))
401
402 ;;; not strictly part of the c-call convention, but needed for the
403 ;;; WITH-PINNED-OBJECTS macro used for "locking down" lisp objects so
404 ;;; that GC won't move them while foreign functions go to work.
405 (define-vop (touch-object)
406   (:translate touch-object)
407   (:args (object))
408   (:ignore object)
409   (:policy :fast-safe)
410   (:arg-types t)
411   (:generator 0))
412
413 ;;; Callbacks
414
415 #-sb-xc-host
416 (defun alien-callback-accessor-form (type sp offset)
417   `(deref (sap-alien (sap+ ,sp ,offset) (* ,type))))
418
419 #-sb-xc-host
420 (defun alien-callback-assembler-wrapper (index result-type argument-types)
421   (labels ((make-tn-maker (sc-name)
422              (lambda (offset)
423                (make-random-tn :kind :normal
424                                :sc (sc-or-lose sc-name)
425                                :offset offset)))
426            (out-of-registers-error ()
427              (error "Too many arguments in callback")))
428     (let* ((segment (make-segment))
429            (rax rax-tn)
430            #!+(or win32 (not sb-safepoint)) (rcx rcx-tn)
431            #!-win32 (rdi rdi-tn)
432            #!-win32 (rsi rsi-tn)
433            (rdx rdx-tn)
434            (rbp rbp-tn)
435            (rsp rsp-tn)
436            #!+win32 (r8 r8-tn)
437            (xmm0 float0-tn)
438            ([rsp] (make-ea :qword :base rsp :disp 0))
439            ;; How many arguments have been copied
440            (arg-count 0)
441            ;; How many arguments have been copied from the stack
442            (stack-argument-count #!-win32 0 #!+win32 4)
443            (gprs (mapcar (make-tn-maker 'any-reg) *c-call-register-arg-offsets*))
444            (fprs (mapcar (make-tn-maker 'double-reg)
445                          ;; Only 8 first XMM registers are used for
446                          ;; passing arguments
447                          (subseq *float-regs* 0 #!-win32 8 #!+win32 4))))
448       (assemble (segment)
449         ;; Make room on the stack for arguments.
450         (inst sub rsp (* n-word-bytes (length argument-types)))
451         ;; Copy arguments from registers to stack
452         (dolist (type argument-types)
453           (let ((integerp (not (alien-float-type-p type)))
454                 ;; A TN pointing to the stack location where the
455                 ;; current argument should be stored for the purposes
456                 ;; of ENTER-ALIEN-CALLBACK.
457                 (target-tn (make-ea :qword :base rsp
458                                    :disp (* arg-count
459                                             n-word-bytes)))
460                 ;; A TN pointing to the stack location that contains
461                 ;; the next argument passed on the stack.
462                 (stack-arg-tn (make-ea :qword :base rsp
463                                        :disp (* (+ 1
464                                                    (length argument-types)
465                                                    stack-argument-count)
466                                                 n-word-bytes))))
467             (incf arg-count)
468             (cond (integerp
469                    (let ((gpr (pop gprs)))
470                      #!+win32 (pop fprs)
471                      ;; Argument not in register, copy it from the old
472                      ;; stack location to a temporary register.
473                      (unless gpr
474                        (incf stack-argument-count)
475                        (setf gpr temp-reg-tn)
476                        (inst mov gpr stack-arg-tn))
477                      ;; Copy from either argument register or temporary
478                      ;; register to target.
479                      (inst mov target-tn gpr)))
480                   ((or (alien-single-float-type-p type)
481                        (alien-double-float-type-p type))
482                    (let ((fpr (pop fprs)))
483                      #!+win32 (pop gprs)
484                      (cond (fpr
485                             ;; Copy from float register to target location.
486                             (inst movq target-tn fpr))
487                            (t
488                             ;; Not in float register. Copy from stack to
489                             ;; temporary (general purpose) register, and
490                             ;; from there to the target location.
491                             (incf stack-argument-count)
492                             (inst mov temp-reg-tn stack-arg-tn)
493                             (inst mov target-tn temp-reg-tn)))))
494                   (t
495                    (bug "Unknown alien floating point type: ~S" type)))))
496
497         #!-sb-safepoint
498         (progn
499           ;; arg0 to FUNCALL3 (function)
500           ;;
501           ;; Indirect the access to ENTER-ALIEN-CALLBACK through
502           ;; the symbol-value slot of SB-ALIEN::*ENTER-ALIEN-CALLBACK*
503           ;; to ensure it'll work even if the GC moves ENTER-ALIEN-CALLBACK.
504           ;; Skip any SB-THREAD TLS magic, since we don't expect anyone
505           ;; to rebind the variable. -- JES, 2006-01-01
506           (inst mov rdi (+ nil-value (static-symbol-offset
507                                       'sb!alien::*enter-alien-callback*)))
508           (loadw rdi rdi symbol-value-slot other-pointer-lowtag)
509           ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
510           (inst mov rsi (fixnumize index))
511           ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
512           (inst mov rdx rsp)
513           ;; add room on stack for return value
514           (inst sub rsp 8)
515           ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
516           (inst mov rcx rsp)
517
518           ;; Make new frame
519           (inst push rbp)
520           (inst mov  rbp rsp)
521
522           ;; Call
523           (inst mov  rax (foreign-symbol-address "funcall3"))
524           (inst call rax)
525
526           ;; Back! Restore frame
527           (inst mov rsp rbp)
528           (inst pop rbp))
529
530         #!+sb-safepoint
531         (progn
532           ;; arg0 to ENTER-ALIEN-CALLBACK (trampoline index)
533           (inst mov #!-win32 rdi #!+win32 rcx (fixnumize index))
534           ;; arg1 to ENTER-ALIEN-CALLBACK (pointer to argument vector)
535           (inst mov #!-win32 rsi #!+win32 rdx rsp)
536           ;; add room on stack for return value
537           (inst sub rsp 8)
538           ;; arg2 to ENTER-ALIEN-CALLBACK (pointer to return value)
539           (inst mov #!-win32 rdx #!+win32 r8 rsp)
540           ;; Make new frame
541           (inst push rbp)
542           (inst mov  rbp rsp)
543           #!+win32 (inst sub rsp #x20)
544           #!+win32 (inst and rsp #x-20)
545           ;; Call
546           (inst mov rax (foreign-symbol-address "callback_wrapper_trampoline"))
547           (inst call rax)
548           ;; Back! Restore frame
549           (inst mov rsp rbp)
550           (inst pop rbp))
551
552         ;; Result now on top of stack, put it in the right register
553         (cond
554           ((or (alien-integer-type-p result-type)
555                (alien-pointer-type-p result-type)
556                (alien-type-= #.(parse-alien-type 'system-area-pointer nil)
557                              result-type))
558            (inst mov rax [rsp]))
559           ((or (alien-single-float-type-p result-type)
560                (alien-double-float-type-p result-type))
561            (inst movq xmm0 [rsp]))
562           ((alien-void-type-p result-type))
563           (t
564            (error "unrecognized alien type: ~A" result-type)))
565
566         ;; Pop the arguments and the return value from the stack to get
567         ;; the return address at top of stack.
568         (inst add rsp (* (1+ (length argument-types)) n-word-bytes))
569         ;; Return
570         (inst ret))
571       (finalize-segment segment)
572       ;; Now that the segment is done, convert it to a static
573       ;; vector we can point foreign code to.
574       (let ((buffer (sb!assem::segment-buffer segment)))
575         (make-static-vector (length buffer)
576                             :element-type '(unsigned-byte 8)
577                             :initial-contents buffer)))))