PowerPC safepoints
[sbcl.git] / src / compiler / ppc / c-call.lisp
1 ;;;; VOPs and other machine-specific support routines for call-out to C
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 ;;; Return the number of bytes needed for the current non-descriptor
15 ;;; stack frame.  Non-descriptor stack frames must be multiples of 16
16 ;;; bytes under the PPC SVr4 ABI (though the EABI may be less
17 ;;; restrictive).  On linux, two words are reserved for the stack
18 ;;; backlink and saved LR (see SB!VM::NUMBER-STACK-DISPLACEMENT).
19
20 (defconstant +stack-alignment-bytes+
21   ;; Duh.  PPC Linux (and VxWorks) adhere to the EABI.
22   #!-darwin 7
23   ;; But Darwin doesn't
24   #!+darwin 15)
25
26 (defun my-make-wired-tn (prim-type-name sc-name offset)
27   (make-wired-tn (primitive-type-or-lose prim-type-name)
28                  (sc-number-or-lose sc-name)
29                  offset))
30
31 (defstruct arg-state
32   (gpr-args 0)
33   (fpr-args 0)
34   ;; SVR4 [a]abi wants two words on stack (callee saved lr,
35   ;; backpointer).
36   #!-darwin (stack-frame-size 2)
37   ;; PowerOpen ABI wants 8 words on the stack corresponding to GPR3-10
38   ;; in addition to the 6 words of link area (see number-stack-displacement)
39   #!+darwin (stack-frame-size (+ 8 6)))
40
41 (defun int-arg (state prim-type reg-sc stack-sc)
42   (let ((reg-args (arg-state-gpr-args state)))
43     (cond ((< reg-args 8)
44            (setf (arg-state-gpr-args state) (1+ reg-args))
45            (my-make-wired-tn prim-type reg-sc (+ reg-args nl0-offset)))
46           (t
47            (let ((frame-size (arg-state-stack-frame-size state)))
48              (setf (arg-state-stack-frame-size state) (1+ frame-size))
49              (my-make-wired-tn prim-type stack-sc frame-size))))))
50
51 (define-alien-type-method (integer :arg-tn) (type state)
52   (if (alien-integer-type-signed type)
53       (int-arg state 'signed-byte-32 'signed-reg 'signed-stack)
54       (int-arg state 'unsigned-byte-32 'unsigned-reg 'unsigned-stack)))
55
56 (define-alien-type-method (system-area-pointer :arg-tn) (type state)
57   (declare (ignore type))
58   (int-arg state 'system-area-pointer 'sap-reg 'sap-stack))
59
60 ;;; The Linux/PPC 32bit ABI says:
61 ;;;
62 ;;;   If a single-float arg has to go on the stack, it's promoted to
63 ;;;   a double.
64 ;;;
65 ;;; gcc does:
66 ;;;
67 ;;;   Excess floats stored on the stack are stored as floats.
68 ;;;
69 ;;; We follow gcc.
70 #!-darwin
71 (define-alien-type-method (single-float :arg-tn) (type state)
72   (declare (ignore type))
73   (let* ((fprs (arg-state-fpr-args state)))
74     (cond ((< fprs 8)
75            (incf (arg-state-fpr-args state))
76            ;; Assign outgoing FPRs starting at FP1
77            (my-make-wired-tn 'single-float 'single-reg (1+ fprs)))
78           (t
79            (let* ((stack-offset (arg-state-stack-frame-size state)))
80              (setf (arg-state-stack-frame-size state) (+ stack-offset 1))
81              (my-make-wired-tn 'single-float 'single-stack stack-offset))))))
82
83 ;;; If a single-float arg has to go on the stack, it's promoted to
84 ;;; double.  That way, C programs can get subtle rounding errors when
85 ;;; unrelated arguments are introduced.
86 #!+darwin
87 (define-alien-type-method (single-float :arg-tn) (type state)
88   (declare (ignore type))
89   (let* ((fprs (arg-state-fpr-args state))
90          (gprs (arg-state-gpr-args state)))
91     (cond ((< gprs 8) ; and by implication also (< fprs 13)
92            (incf (arg-state-fpr-args state))
93            ;; Assign outgoing FPRs starting at FP1
94            (list (my-make-wired-tn 'single-float 'single-reg (1+ fprs))
95                  (int-arg state 'signed-byte-32 'signed-reg 'signed-stack)))
96           ((< fprs 13)
97            ;; See comments below for double-float.
98            (incf (arg-state-fpr-args state))
99            (incf (arg-state-stack-frame-size state))
100            (my-make-wired-tn 'single-float 'single-reg (1+ fprs)))
101           (t
102            ;; Pass on stack only
103            (let ((stack-offset (arg-state-stack-frame-size state)))
104              (incf (arg-state-stack-frame-size state))
105              (my-make-wired-tn 'single-float 'single-stack stack-offset))))))
106
107 #!-darwin
108 (define-alien-type-method (double-float :arg-tn) (type state)
109   (declare (ignore type))
110   (let* ((fprs (arg-state-fpr-args state)))
111     (cond ((< fprs 8)
112            (incf (arg-state-fpr-args state))
113            ;; Assign outgoing FPRs starting at FP1
114            (my-make-wired-tn 'double-float 'double-reg (1+ fprs)))
115           (t
116            (let* ((stack-offset (arg-state-stack-frame-size state)))
117              (if (oddp stack-offset)
118                (incf stack-offset))
119              (setf (arg-state-stack-frame-size state) (+ stack-offset 2))
120              (my-make-wired-tn 'double-float 'double-stack stack-offset))))))
121
122 #!+darwin
123 (define-alien-type-method (double-float :arg-tn) (type state)
124   (declare (ignore type))
125   (let ((fprs (arg-state-fpr-args state))
126         (gprs (arg-state-gpr-args state)))
127     (cond ((< gprs 8) ; and by implication also (< fprs 13)
128            (incf (arg-state-fpr-args state))
129            ;; Assign outgoing FPRs starting at FP1
130            ;;
131            ;; The PowerOpen ABI says float values are stored in float
132            ;; regs.  But if we're calling a varargs function, we also
133            ;; need to put the float into some gprs.  We indicate this
134            ;; to %alien-funcall ir2-convert by making a list of the
135            ;; TNs for the float reg and for the int regs.
136            ;;
137            (list (my-make-wired-tn 'double-float 'double-reg (1+ fprs))
138                  (int-arg state 'signed-byte-32 'signed-reg 'signed-stack)
139                  (int-arg state 'unsigned-byte-32 'unsigned-reg 'unsigned-stack)))
140           ((< fprs 13)
141            (incf (arg-state-fpr-args state))
142            (list (my-make-wired-tn 'double-float 'double-reg (1+ fprs))
143                  (int-arg state 'signed-byte-32 'signed-reg 'signed-stack)
144                  (int-arg state 'unsigned-byte-32 'unsigned-reg 'unsigned-stack)))
145           (t
146            ;; Pass on stack only
147            (let ((stack-offset (arg-state-stack-frame-size state)))
148              (incf (arg-state-stack-frame-size state) 2)
149              (my-make-wired-tn 'double-float 'double-stack stack-offset))))))
150
151 ;;; Result state handling
152
153 (defstruct result-state
154   (num-results 0))
155
156 (defun result-reg-offset (slot)
157   (ecase slot
158     (0 nl0-offset)
159     (1 nl1-offset)))
160
161 ;;; FIXME: These #!-DARWIN methods should be adjusted to take a state
162 ;;; argument, firstly because that's our "official" API (see
163 ;;; src/code/host-alieneval) and secondly because that way we can
164 ;;; probably have less duplication of code.  -- CSR, 2003-07-29
165
166 (define-alien-type-method (system-area-pointer :result-tn) (type state)
167   (declare (ignore type))
168   (let ((num-results (result-state-num-results state)))
169     (setf (result-state-num-results state) (1+ num-results))
170     (my-make-wired-tn 'system-area-pointer 'sap-reg
171                       (result-reg-offset num-results))))
172
173 (define-alien-type-method (single-float :result-tn) (type state)
174   (declare (ignore type state))
175   (my-make-wired-tn 'single-float 'single-reg 1))
176
177 (define-alien-type-method (double-float :result-tn) (type state)
178   (declare (ignore type state))
179   (my-make-wired-tn 'double-float 'double-reg 1))
180
181 (define-alien-type-method (values :result-tn) (type state)
182   (let ((values (alien-values-type-values type)))
183     (when (> (length values) 2)
184       (error "Too many result values from c-call."))
185     (mapcar #'(lambda (type)
186                 (invoke-alien-type-method :result-tn type state))
187             values)))
188
189 (define-alien-type-method (integer :result-tn) (type state)
190   (let ((num-results (result-state-num-results state)))
191     (setf (result-state-num-results state) (1+ num-results))
192     (multiple-value-bind (ptype reg-sc)
193         (if (alien-integer-type-signed type)
194             (values 'signed-byte-32 'signed-reg)
195             (values 'unsigned-byte-32 'unsigned-reg))
196       (my-make-wired-tn ptype reg-sc (result-reg-offset num-results)))))
197
198 (!def-vm-support-routine make-call-out-tns (type)
199   (declare (type alien-fun-type type))
200   (let ((arg-state (make-arg-state)))
201     (collect ((arg-tns))
202       (dolist (arg-type (alien-fun-type-arg-types type))
203         (arg-tns (invoke-alien-type-method :arg-tn arg-type arg-state)))
204       (values (my-make-wired-tn 'positive-fixnum 'any-reg nsp-offset)
205               (* (arg-state-stack-frame-size arg-state) n-word-bytes)
206               (arg-tns)
207               (invoke-alien-type-method
208                :result-tn
209                (alien-fun-type-result-type type)
210                (make-result-state))))))
211
212
213 ;;; Sort out long longs, by splitting them up.  However, need to take
214 ;;; care about register/stack alignment and whether they will fully
215 ;;; fit into registers or must go on the stack.
216 #!-darwin
217 (deftransform %alien-funcall ((function type &rest args))
218   (aver (sb!c::constant-lvar-p type))
219   (let* ((type (sb!c::lvar-value type))
220          (arg-types (alien-fun-type-arg-types type))
221          (result-type (alien-fun-type-result-type type))
222          (gprs 0)
223          (fprs 0)
224          (stack 0))
225     (aver (= (length arg-types) (length args)))
226     ;; We need to do something special for 64-bit integer arguments
227     ;; and results.
228     (if (or (some #'(lambda (type)
229                       (and (alien-integer-type-p type)
230                            (> (sb!alien::alien-integer-type-bits type) 32)))
231                   arg-types)
232             (and (alien-integer-type-p result-type)
233                  (> (sb!alien::alien-integer-type-bits result-type) 32)))
234         (collect ((new-args) (lambda-vars) (new-arg-types))
235           (dolist (type arg-types)
236             (let ((arg (gensym)))
237               (lambda-vars arg)
238               (cond ((and (alien-integer-type-p type)
239                           (> (sb!alien::alien-integer-type-bits type) 32))
240                      (when (or
241                             (oddp gprs)
242                             (and
243                              (oddp stack)
244                              (> gprs 7)))
245                        ;; Need to pad for alignment.
246                        (if (oddp gprs)
247                            (incf gprs)
248                            (incf stack))
249                        (new-args 0)
250                        (new-arg-types (parse-alien-type
251                                        '(unsigned 32)
252                                        (sb!kernel:make-null-lexenv))))
253                      (if (< gprs 8)
254                          (incf gprs 2)
255                          (incf stack 2))
256                      (new-args `(ash ,arg -32))
257                      (new-args `(logand ,arg #xffffffff))
258                      (if (alien-integer-type-signed type)
259                          (new-arg-types (parse-alien-type
260                                          '(signed 32)
261                                          (sb!kernel:make-null-lexenv)))
262                          (new-arg-types (parse-alien-type
263                                          '(unsigned 32)
264                                          (sb!kernel:make-null-lexenv))))
265                      (new-arg-types (parse-alien-type
266                                      '(unsigned 32)
267                                      (sb!kernel:make-null-lexenv))))
268                     ((alien-single-float-type-p type)
269                      (if (< fprs 8)
270                          (incf fprs)
271                          (incf stack))
272                      (new-args arg)
273                      (new-arg-types type))
274                     ((alien-double-float-type-p type)
275                      (if (< fprs 8)
276                          (incf fprs)
277                          (if (oddp stack)
278                              (incf stack 3)   ; Doubles are aligned on
279                              (incf stack 2))) ; the stack.
280                      (new-args arg)
281                      (new-arg-types type))
282                     (t ;; integer or SAP
283                      (if (< gprs 8)
284                          (incf gprs 1)
285                          (incf stack 1))
286                      (new-args arg)
287                      (new-arg-types type)))))
288                  (cond ((and (alien-integer-type-p result-type)
289                              (> (sb!alien::alien-integer-type-bits result-type) 32))
290                         (let ((new-result-type
291                                (let ((sb!alien::*values-type-okay* t))
292                                  (parse-alien-type
293                                   (if (alien-integer-type-signed result-type)
294                                       '(values (signed 32) (unsigned 32))
295                                       '(values (unsigned 32) (unsigned 32)))
296                                   (sb!kernel:make-null-lexenv)))))
297                           `(lambda (function type ,@(lambda-vars))
298                             (declare (ignore type))
299                             (multiple-value-bind (high low)
300                                 (%alien-funcall function
301                                                 ',(make-alien-fun-type
302                                                    :arg-types (new-arg-types)
303                                                    :result-type new-result-type)
304                                                 ,@(new-args))
305                               (logior low (ash high 32))))))
306                        (t
307                         `(lambda (function type ,@(lambda-vars))
308                           (declare (ignore type))
309                           (%alien-funcall function
310                            ',(make-alien-fun-type
311                               :arg-types (new-arg-types)
312                               :result-type result-type)
313                            ,@(new-args))))))
314         (sb!c::give-up-ir1-transform))))
315
316 #!+darwin
317 (deftransform %alien-funcall ((function type &rest args))
318   (aver (sb!c::constant-lvar-p type))
319   (let* ((type (sb!c::lvar-value type))
320          (arg-types (alien-fun-type-arg-types type))
321          (result-type (alien-fun-type-result-type type)))
322     (aver (= (length arg-types) (length args)))
323     ;; We need to do something special for 64-bit integer arguments
324     ;; and results.
325     (if (or (some #'(lambda (type)
326                       (and (alien-integer-type-p type)
327                            (> (sb!alien::alien-integer-type-bits type) 32)))
328                   arg-types)
329             (and (alien-integer-type-p result-type)
330                  (> (sb!alien::alien-integer-type-bits result-type) 32)))
331         (collect ((new-args) (lambda-vars) (new-arg-types))
332                  (dolist (type arg-types)
333                    (let ((arg (gensym)))
334                      (lambda-vars arg)
335                      (cond ((and (alien-integer-type-p type)
336                                  (> (sb!alien::alien-integer-type-bits type) 32))
337                             ;; 64-bit long long types are stored in
338                             ;; consecutive locations, most significant word
339                             ;; first (big-endian).
340                             (new-args `(ash ,arg -32))
341                             (new-args `(logand ,arg #xffffffff))
342                             (if (alien-integer-type-signed type)
343                                 (new-arg-types (parse-alien-type '(signed 32) (sb!kernel:make-null-lexenv)))
344                                 (new-arg-types (parse-alien-type '(unsigned 32) (sb!kernel:make-null-lexenv))))
345                             (new-arg-types (parse-alien-type '(unsigned 32) (sb!kernel:make-null-lexenv))))
346                            (t
347                             (new-args arg)
348                             (new-arg-types type)))))
349                  (cond ((and (alien-integer-type-p result-type)
350                              (> (sb!alien::alien-integer-type-bits result-type) 32))
351                         (let ((new-result-type
352                                (let ((sb!alien::*values-type-okay* t))
353                                  (parse-alien-type
354                                   (if (alien-integer-type-signed result-type)
355                                       '(values (signed 32) (unsigned 32))
356                                       '(values (unsigned 32) (unsigned 32)))
357                                   (sb!kernel:make-null-lexenv)))))
358                           `(lambda (function type ,@(lambda-vars))
359                             (declare (ignore type))
360                             (multiple-value-bind (high low)
361                                 (%alien-funcall function
362                                                 ',(make-alien-fun-type
363                                                    :arg-types (new-arg-types)
364                                                    :result-type new-result-type)
365                                                 ,@(new-args))
366                               (logior low (ash high 32))))))
367                        (t
368                         `(lambda (function type ,@(lambda-vars))
369                           (declare (ignore type))
370                           (%alien-funcall function
371                            ',(make-alien-fun-type
372                               :arg-types (new-arg-types)
373                               :result-type result-type)
374                            ,@(new-args))))))
375         (sb!c::give-up-ir1-transform))))
376
377 (define-vop (foreign-symbol-sap)
378   (:translate foreign-symbol-sap)
379   (:policy :fast-safe)
380   (:args)
381   (:arg-types (:constant simple-string))
382   (:info foreign-symbol)
383   (:results (res :scs (sap-reg)))
384   (:result-types system-area-pointer)
385   (:generator 2
386     (inst lr res  (make-fixup foreign-symbol :foreign))))
387
388 #!+linkage-table
389 (define-vop (foreign-symbol-dataref-sap)
390   (:translate foreign-symbol-dataref-sap)
391   (:policy :fast-safe)
392   (:args)
393   (:arg-types (:constant simple-string))
394   (:info foreign-symbol)
395   (:results (res :scs (sap-reg)))
396   (:result-types system-area-pointer)
397   (:temporary (:scs (non-descriptor-reg)) addr)
398   (:generator 2
399     (inst lr addr (make-fixup foreign-symbol :foreign-dataref))
400     (loadw res addr)))
401
402 (define-vop (call-out)
403   (:args (function :scs (sap-reg) :target cfunc)
404          (args :more t))
405   (:results (results :more t))
406   (:ignore args results)
407   (:save-p t)
408   (:temporary (:sc any-reg :offset cfunc-offset
409                    :from (:argument 0) :to (:result 0)) cfunc)
410   (:temporary (:sc control-stack :offset nfp-save-offset) nfp-save)
411   (:temporary (:scs (non-descriptor-reg)) temp)
412   (:vop-var vop)
413   (:generator 0
414     (let ((cur-nfp (current-nfp-tn vop)))
415       (when cur-nfp
416         (store-stack-tn nfp-save cur-nfp))
417       (inst lr temp (make-fixup "call_into_c" :foreign))
418       (inst mtctr temp)
419       (move cfunc function)
420       (inst bctrl)
421       (when cur-nfp
422         (load-stack-tn cur-nfp nfp-save)))))
423
424
425 (define-vop (alloc-number-stack-space)
426   (:info amount)
427   (:results (result :scs (sap-reg any-reg)))
428   (:result-types system-area-pointer)
429   (:temporary (:scs (unsigned-reg) :to (:result 0)) temp)
430   (:generator 0
431     (unless (zerop amount)
432       ;; FIXME: I don't understand why we seem to be adding
433       ;; NUMBER-STACK-DISPLACEMENT twice here.  Weird.  -- CSR,
434       ;; 2003-08-20
435       (let ((delta (- (logandc2 (+ amount number-stack-displacement
436                                    +stack-alignment-bytes+)
437                                 +stack-alignment-bytes+))))
438         (cond ((>= delta (ash -1 16))
439                (inst stwu nsp-tn nsp-tn delta))
440               (t
441                (inst lr temp delta)
442                (inst stwux  nsp-tn nsp-tn temp)))))
443     (unless (location= result nsp-tn)
444       ;; They are only location= when the result tn was allocated by
445       ;; make-call-out-tns above, which takes the number-stack-displacement
446       ;; into account itself.
447       (inst addi result nsp-tn number-stack-displacement))))
448
449 (define-vop (dealloc-number-stack-space)
450   (:info amount)
451   (:policy :fast-safe)
452   (:generator 0
453     (unless (zerop amount)
454       (let ((delta (logandc2 (+ amount number-stack-displacement
455                                 +stack-alignment-bytes+)
456                              +stack-alignment-bytes+)))
457         (cond ((< delta (ash 1 16))
458                (inst addi nsp-tn nsp-tn delta))
459               (t
460                (inst lwz nsp-tn nsp-tn 0)))))))
461
462 #-sb-xc-host
463 (progn
464   (defun alien-callback-accessor-form (type sap offset)
465     (let ((parsed-type
466            (sb!alien::parse-alien-type type (sb!kernel:make-null-lexenv))))
467       (cond ((sb!alien::alien-integer-type-p parsed-type)
468              ;; Unaligned access is slower, but possible, so this is nice and
469              ;; simple. Also, we're a big-endian machine, so we need to get
470              ;; byte offsets correct.
471              (let ((bits (sb!alien::alien-type-bits parsed-type)))
472                (let ((byte-offset
473                       (cond ((< bits n-word-bits)
474                              (- n-word-bytes
475                                 (ceiling bits n-byte-bits)))
476                             (t 0))))
477                  `(deref (sap-alien (sap+ ,sap
478                                           ,(+ byte-offset offset))
479                                     (* ,type))))))
480             (t
481              `(deref (sap-alien (sap+ ,sap ,offset) (* ,type)))))))
482
483   ;;; The "Mach-O Runtime Conventions" document for OS X almost
484   ;;; specifies the calling convention (it neglects to mention that
485   ;;; the linkage area is 24 bytes).
486   #!+darwin
487   (defconstant n-foreign-linkage-area-bytes 24)
488
489   ;;; On linux only use 8 bytes for LR and Back chain.  JRXR
490   ;;; 2006/11/10.
491   #!-darwin
492   (defconstant n-foreign-linkage-area-bytes 8)
493
494   ;;; Returns a vector in static space containing machine code for the
495   ;;; callback wrapper.  Linux version.  JRXR.  2006/11/13
496   #!-darwin
497   (defun alien-callback-assembler-wrapper (index result-type argument-types)
498     (flet ((make-gpr (n)
499              (make-random-tn :kind :normal :sc (sc-or-lose 'any-reg) :offset n))
500            (make-fpr (n)
501              (make-random-tn :kind :normal :sc (sc-or-lose
502                                                 'double-reg) :offset
503                                                 n)))
504       (let* ((segment (make-segment)))
505         (assemble (segment)
506           ;; Copy args from registers or stack to new position
507           ;; on stack.
508           (let* (
509                  ;; Argument store.
510                  (arg-store-size
511                   (* n-word-bytes
512                      (apply '+
513                          (mapcar (lambda (type)
514                                    (ceiling (alien-type-bits type)
515                                             n-word-bits))
516                                  argument-types ))))
517                  ;; Return area allocation.
518                  (n-return-area-words
519                   (ceiling (or (alien-type-bits result-type) 0) n-word-bits))
520                  (n-return-area-bytes (* n-return-area-words
521                                          n-word-bytes))
522                  ;; FIXME: magic constant, and probably n-args-bytes
523                  ;; JRXR: What's this for?  Copied from Darwin.
524                  (args-size (* 3 n-word-bytes))
525                  (frame-size (logandc2
526                               (+ arg-store-size
527                                  n-return-area-bytes
528                                  args-size
529                                  SB!VM::NUMBER-STACK-DISPLACEMENT
530                                  +stack-alignment-bytes+)
531                               +stack-alignment-bytes+))
532                  (return-area-pos (- frame-size
533                                      SB!VM::NUMBER-STACK-DISPLACEMENT
534                                      args-size))
535                  (arg-store-pos (- return-area-pos
536                                    n-return-area-bytes))
537                  (stack-pointer (make-gpr 1))
538                  (r0 (make-gpr 0))
539                  (f0 (make-fpr 0))
540                  (in-words-processed 0)
541                  (out-words-processed 0)
542                  (gprs (mapcar #'make-gpr '(3 4 5 6 7 8 9 10)))
543                  (fprs (mapcar #'make-fpr
544                                '(1 2 3 4 5 6 7 8))) )
545             ;; Setup useful functions and then copy all args.
546             (flet ((load-address-into (reg addr)
547                        (let ((high (ldb (byte 16 16) addr))
548                              (low (ldb (byte 16 0) addr)))
549                          (inst lis reg high)
550                          (inst ori reg reg low)))
551                    (save-arg (type words)
552                      (let ((integerp (not (alien-float-type-p type)))
553                            (in-offset (+ (* in-words-processed n-word-bytes)
554                                          n-foreign-linkage-area-bytes))
555                            (out-offset (- (* out-words-processed n-word-bytes)
556                                           arg-store-pos)))
557                        (cond (integerp
558                               (if (and
559                                    ;; Only upto long longs are passed
560                                    ;; in registers.
561                                    (<= words 2)
562                                    ;; And needs space for whole arg,
563                                    ;; including alignment.
564                                    (<= (+ words
565                                           (rem (length gprs) words))
566                                        (length gprs)))
567                                   (progn
568                                     (if (/= 0
569                                             (rem (length gprs) words))
570                                         (pop gprs))
571                                     (dotimes (k words)
572                                       (let ((gpr (pop gprs)))
573                                         (inst stw gpr stack-pointer
574                                               out-offset))
575                                       (incf out-words-processed)
576                                       (incf out-offset n-word-bytes)))
577                                   (progn
578                                     ;; First ensure alignment.
579                                     ;; FIXME!  If passing structures
580                                     ;; becomes allowable, then this is
581                                     ;; broken.
582                                     (if (/= 0
583                                             (rem in-words-processed
584                                                  words))
585                                         (progn
586                                           (incf in-words-processed)
587                                           (incf in-offset
588                                                 n-word-bytes)))
589                                     (dotimes (k words)
590                                       ;; Copy from memory to memory.
591                                       (inst lwz r0 stack-pointer
592                                             in-offset)
593                                       (inst stw r0 stack-pointer
594                                             out-offset)
595                                       (incf out-words-processed)
596                                       (incf out-offset n-word-bytes)
597                                       (incf in-words-processed)
598                                       (incf in-offset n-word-bytes)))))
599                              ;; The handling of floats is a little ugly
600                              ;; because we hard-code the number of words
601                              ;; for single- and double-floats.
602                              ((alien-single-float-type-p type)
603                               (let ((fpr (pop fprs)))
604                                 (if fpr
605                                     (inst stfs fpr stack-pointer out-offset)
606                                     (progn
607                                       ;; The ABI says that floats
608                                       ;; stored on the stack are
609                                       ;; promoted to doubles.  gcc
610                                       ;; stores them as floats.
611                                       ;; Follow gcc here.
612                                       ;;  => no alignment needed either.
613                                       (inst lfs f0
614                                             stack-pointer in-offset)
615                                       (inst stfs f0
616                                             stack-pointer out-offset)
617                                       (incf in-words-processed))))
618                               (incf out-words-processed))
619                              ((alien-double-float-type-p type)
620                               (let ((fpr (pop fprs)))
621                                 (if fpr
622                                     (inst stfd fpr stack-pointer out-offset)
623                                     (progn
624                                       ;; Ensure alignment.
625                                       (if (oddp in-words-processed)
626                                           (progn
627                                             (incf in-words-processed)
628                                             (incf in-offset n-word-bytes)))
629                                       (inst lfd f0
630                                             stack-pointer in-offset)
631                                       (inst stfd f0
632                                             stack-pointer out-offset)
633                                       (incf in-words-processed 2))))
634                               (incf out-words-processed 2))
635                              (t
636                               (bug "Unknown alien floating point type: ~S" type))))))
637               (mapc #'save-arg
638                     argument-types
639                     (mapcar (lambda (arg)
640                               (ceiling (alien-type-bits arg) n-word-bits))
641                             argument-types))
642
643               ;; Arranged the args, allocated the return area.  Now
644               ;; actuall call funcall3:  funcall3 (call-alien-function,
645               ;; index, args, return-area)
646
647               (destructuring-bind (arg1 arg2 arg3 arg4)
648                   (mapcar #'make-gpr '(3 4 5 6))
649                 (load-address-into arg1 (+ nil-value (static-symbol-offset
650                                                       'sb!alien::*enter-alien-callback*)))
651                 (loadw arg1 arg1 symbol-value-slot other-pointer-lowtag)
652                 (inst li arg2 (fixnumize index))
653                 (inst addi arg3 stack-pointer (- arg-store-pos))
654                 (inst addi arg4 stack-pointer (- return-area-pos)))
655
656               ;; Setup everything.  Now save sp, setup the frame.
657               (inst mflr r0)
658               (inst stw r0 stack-pointer (* 2 n-word-bytes)) ; FIXME: magic
659                                         ; constant, copied from Darwin.
660               (inst stwu stack-pointer stack-pointer (- frame-size))
661
662               ;; And make the call.
663               (load-address-into
664                r0
665                (foreign-symbol-address
666                 #!-sb-safepoint "funcall3"
667                 #!+sb-safepoint "callback_wrapper_trampoline"))
668               (inst mtlr r0)
669               (inst blrl)
670
671               ;; We're back!  Restore sp and lr, load the
672               ;; return value from just under sp, and return.
673               (inst lwz stack-pointer stack-pointer 0)
674               (inst lwz r0 stack-pointer (* 2 n-word-bytes))
675               (inst mtlr r0)
676               (cond
677                 ((sb!alien::alien-single-float-type-p result-type)
678                  (let ((f1 (make-fpr 1)))
679                    (inst lfs f1 stack-pointer (- return-area-pos))))
680                 ((sb!alien::alien-double-float-type-p result-type)
681                  (let ((f1 (make-fpr 1)))
682                    (inst lfd f1 stack-pointer (- return-area-pos))))
683                 ((sb!alien::alien-void-type-p result-type)
684                  ;; Nothing to do
685                  )
686                 (t
687                  (loop with gprs = (mapcar #'make-gpr '(3 4))
688                        repeat n-return-area-words
689                        for gpr = (pop gprs)
690                        for offset from (- return-area-pos)
691                        by n-word-bytes
692                        do
693                        (unless gpr
694                          (bug "Out of return registers in alien-callback trampoline."))
695                        (inst lwz gpr stack-pointer offset))))
696               (inst blr))))
697         (finalize-segment segment)
698
699         ;; Now that the segment is done, convert it to a static
700         ;; vector we can point foreign code to.
701         (let* ((buffer (sb!assem::segment-buffer segment))
702                (vector (make-static-vector (length buffer)
703                                            :element-type '(unsigned-byte 8)
704                                            :initial-contents buffer))
705                (sap (sb!sys:vector-sap vector)))
706           (sb!alien:alien-funcall
707            (sb!alien:extern-alien "ppc_flush_icache"
708                                   (function void
709                                             system-area-pointer
710                                             unsigned-long))
711            sap (length buffer))
712           vector))))
713
714   ;;; Returns a vector in static space containing machine code for the
715   ;;; callback wrapper
716   #!+darwin
717   (defun alien-callback-assembler-wrapper (index result-type argument-types)
718     (flet ((make-gpr (n)
719              (make-random-tn :kind :normal :sc (sc-or-lose 'any-reg) :offset n))
720            (make-fpr (n)
721              (make-random-tn :kind :normal :sc (sc-or-lose 'double-reg) :offset n)))
722       (let* ((segment (make-segment)))
723         (assemble (segment)
724           ;; To save our arguments, we follow the algorithm sketched in the
725           ;; "PowerPC Calling Conventions" section of that document.
726           ;;
727           ;; CLH: There are a couple problems here. First, we bail if
728           ;; we run out of registers. AIUI, we can just ignore the extra
729           ;; args here and we will be ok...
730           (let ((words-processed 0)
731                 (gprs (mapcar #'make-gpr '(3 4 5 6 7 8 9 10)))
732                 (fprs (mapcar #'make-fpr '(1 2 3 4 5 6 7 8 9 10 11 12 13)))
733                 (stack-pointer (make-gpr 1)))
734             (labels ((save-arg (type words)
735                        (let ((integerp (not (alien-float-type-p type)))
736                              (offset (+ (* words-processed n-word-bytes)
737                                         n-foreign-linkage-area-bytes)))
738                          (cond (integerp
739                                 (dotimes (k words)
740                                   (let ((gpr (pop gprs)))
741                                     (when gpr
742                                       (inst stw gpr stack-pointer offset))
743                                     (incf words-processed)
744                                     (incf offset n-word-bytes))))
745                                ;; The handling of floats is a little ugly
746                                ;; because we hard-code the number of words
747                                ;; for single- and double-floats.
748                                ((alien-single-float-type-p type)
749                                 (pop gprs)
750                                 (let ((fpr (pop fprs)))
751                                   (when fpr
752                                     (inst stfs fpr stack-pointer offset)))
753                                 (incf words-processed))
754                                ((alien-double-float-type-p type)
755                                 (setf gprs (cddr gprs))
756                                 (let ((fpr (pop fprs)))
757                                   (when fpr
758                                     (inst stfd fpr stack-pointer offset)))
759                                 (incf words-processed 2))
760                                (t
761                                 (bug "Unknown alien floating point type: ~S" type))))))
762               (mapc #'save-arg
763                     argument-types
764                     (mapcar (lambda (arg)
765                               (ceiling (alien-type-bits arg) n-word-bits))
766                             argument-types))))
767           ;; Set aside room for the return area just below sp, then
768           ;; actually call funcall3: funcall3 (call-alien-function,
769           ;; index, args, return-area)
770           ;;
771           ;; INDEX is fixnumized, ARGS and RETURN-AREA don't need to be
772           ;; because they're word-aligned. Kinda gross, but hey ...
773           (let* ((n-return-area-words
774                   (ceiling (or (alien-type-bits result-type) 0) n-word-bits))
775                  (n-return-area-bytes (* n-return-area-words n-word-bytes))
776                  ;; FIXME: magic constant, and probably n-args-bytes
777                  (args-size (* 3 n-word-bytes))
778                  ;; FIXME: n-frame-bytes?
779                  (frame-size (logandc2 (+ n-foreign-linkage-area-bytes
780                                           n-return-area-bytes
781                                           args-size
782                                           +stack-alignment-bytes+)
783                                        +stack-alignment-bytes+)))
784             (destructuring-bind (sp r0 arg1 arg2 arg3 arg4)
785                 (mapcar #'make-gpr '(1 0 3 4 5 6))
786               ;; FIXME: This is essentially the same code as LR in
787               ;; insts.lisp, but attempting to use (INST LR ...) instead
788               ;; of this function results in callbacks not working.  Why?
789               ;;   --njf, 2006-01-04
790               (flet ((load-address-into (reg addr)
791                        (let ((high (ldb (byte 16 16) addr))
792                              (low (ldb (byte 16 0) addr)))
793                          (inst lis reg high)
794                          (inst ori reg reg low))))
795                 ;; Setup the args
796
797                 ;; CLH 2006/02/10 -Following JES' logic in
798                 ;; x86-64/c-call.lisp, we need to access
799                 ;; ENTER-ALIEN-CALLBACK through the symbol-value slot
800                 ;; of SB-ALIEN::*ENTER-ALIEN-CALLBACK* to ensure that
801                 ;; it works if GC moves ENTER-ALIEN-CALLBACK.
802                 ;;
803                 ;; old way:
804                 ;; (load-address-into arg1 (get-lisp-obj-address #'enter-alien-callback))
805
806                 ;; new way:
807                 ;; (load-symbol arg1 'sb!alien::*enter-alien-callback*)
808                 ;;
809                 ;; whoops: can't use load-symbol here as null-tn might
810                 ;; not be loaded with the proper value as we are
811                 ;; coming in from C code. Use nil-value constant
812                 ;; instead, following the logic in x86-64/c-call.lisp.
813                 (load-address-into arg1 (+ nil-value (static-symbol-offset
814                                                       'sb!alien::*enter-alien-callback*)))
815                 (loadw arg1 arg1 symbol-value-slot other-pointer-lowtag)
816
817                 (inst li arg2 (fixnumize index))
818                 (inst addi arg3 sp n-foreign-linkage-area-bytes)
819                 ;; FIXME: This was (- (* RETURN-AREA-SIZE N-WORD-BYTES)), while
820                 ;; RETURN-AREA-SIZE was (* N-RETURN-AREA-WORDS N-WORD-BYTES):
821                 ;; I assume the intention was (- N-RETURN-AREA-BYTES), but who knows?
822                 ;; --NS 2005-06-11
823                 (inst addi arg4 sp (- n-return-area-bytes))
824                 ;; FIXME! FIXME FIXME: What does this FIXME refer to?
825                 ;; Save sp, setup the frame
826                 (inst mflr r0)
827                 (inst stw r0 sp (* 2 n-word-bytes)) ; FIXME: magic constant
828                 (inst stwu sp sp (- frame-size))
829                 ;; Make the call
830                 (load-address-into r0 (foreign-symbol-address "funcall3"))
831                 (inst mtlr r0)
832                 (inst blrl))
833               ;; We're back!  Restore sp and lr, load the return value from just
834               ;; under sp, and return.
835               (inst lwz sp sp 0)
836               (inst lwz r0 sp (* 2 n-word-bytes))
837               (inst mtlr r0)
838               (cond
839                 ((sb!alien::alien-single-float-type-p result-type)
840                  (let ((f1 (make-fpr 1)))
841                    (inst lfs f1 sp (- (* n-return-area-words n-word-bytes)))))
842                 ((sb!alien::alien-double-float-type-p result-type)
843                  (let ((f1 (make-fpr 1)))
844                    (inst lfd f1 sp (- (* n-return-area-words n-word-bytes)))))
845                 ((sb!alien::alien-void-type-p result-type)
846                  ;; Nothing to do
847                  )
848                 (t
849                  (loop with gprs = (mapcar #'make-gpr '(3 4))
850                     repeat n-return-area-words
851                     for gpr = (pop gprs)
852                     for offset from (- (* n-return-area-words n-word-bytes))
853                     by n-word-bytes
854                     do
855                       (unless gpr
856                         (bug "Out of return registers in alien-callback trampoline."))
857                       (inst lwz gpr sp offset))))
858               (inst blr))))
859         (finalize-segment segment)
860         ;; Now that the segment is done, convert it to a static
861         ;; vector we can point foreign code to.
862         (let* ((buffer (sb!assem::segment-buffer segment))
863                (vector (make-static-vector (length buffer)
864                                            :element-type '(unsigned-byte 8)
865                                            :initial-contents buffer))
866                (sap (sb!sys:vector-sap vector)))
867           (sb!alien:alien-funcall
868            (sb!alien:extern-alien "ppc_flush_icache"
869                                   (function void
870                                             system-area-pointer
871                                             unsigned-long))
872            sap (length buffer))
873           vector)))))