]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmrun/power-rhapsody.S
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmrun / power-rhapsody.S
1 /*********************************************************************/
2 /*                                                                   */
3 /*                          Objective Caml                           */
4 /*                                                                   */
5 /*           Xavier Leroy, projet Cristal, INRIA Rocquencourt        */
6 /*                                                                   */
7 /* Copyright 1996 Institut National de Recherche en Informatique et  */
8 /* en Automatique.  All rights reserved.  This file is distributed   */
9 /* under the terms of the GNU Library General Public License, with   */
10 /* the special exception on linking described in file ../LICENSE.    */
11 /*                                                                   */
12 /*********************************************************************/
13
14 /* $Id: power-rhapsody.S 7812 2007-01-29 12:11:18Z xleroy $ */
15
16 #ifdef __ppc64__
17 #define X(a,b) b
18 #else
19 #define X(a,b) a
20 #endif
21
22 #define WORD X(4,8)
23 #define lg X(lwz,ld)
24 #define lgu X(lwzu,ldu)
25 #define stg X(stw,std)
26 #define stgu X(stwu,stdu)
27 #define gdata X(.long,.quad)
28
29 .macro Addrglobal       /* reg, glob */
30         addis   $0, 0, ha16($1)
31         addi    $0, $0, lo16($1)
32 .endmacro
33 .macro Loadglobal       /* reg,glob,tmp */
34         addis   $2, 0, ha16($1)
35         lg      $0, lo16($1)($2)
36 .endmacro
37 .macro Storeglobal      /* reg,glob,tmp */
38         addis   $2, 0, ha16($1)
39         stg     $0, lo16($1)($2)
40 .endmacro
41
42         .text
43
44 /* Invoke the garbage collector. */
45
46         .globl  _caml_call_gc
47 _caml_call_gc:
48     /* Set up stack frame */
49 #define FRAMESIZE (32*WORD + 32*8 + 32)
50         stwu    r1, -FRAMESIZE(r1)
51     /* Record return address into Caml code */
52         mflr    r0
53         Storeglobal r0, _caml_last_return_address, r11
54     /* Record lowest stack address */
55         addi    r0, r1, FRAMESIZE
56         Storeglobal r0, _caml_bottom_of_stack, r11
57     /* Record pointer to register array */
58         addi    r0, r1, 8*32 + 32
59         Storeglobal r0, _caml_gc_regs, r11
60     /* Save current allocation pointer for debugging purposes */
61         Storeglobal r31, _caml_young_ptr, r11
62     /* Save exception pointer (if e.g. a sighandler raises) */
63         Storeglobal r29, _caml_exception_pointer, r11
64     /* Save all registers used by the code generator */
65         addi    r11, r1, 8*32 + 32 - WORD
66         stgu    r3, WORD(r11)
67         stgu    r4, WORD(r11)
68         stgu    r5, WORD(r11)
69         stgu    r6, WORD(r11)
70         stgu    r7, WORD(r11)
71         stgu    r8, WORD(r11)
72         stgu    r9, WORD(r11)
73         stgu    r10, WORD(r11)
74         stgu    r14, WORD(r11)
75         stgu    r15, WORD(r11)
76         stgu    r16, WORD(r11)
77         stgu    r17, WORD(r11)
78         stgu    r18, WORD(r11)
79         stgu    r19, WORD(r11)
80         stgu    r20, WORD(r11)
81         stgu    r21, WORD(r11)
82         stgu    r22, WORD(r11)
83         stgu    r23, WORD(r11)
84         stgu    r24, WORD(r11)
85         stgu    r25, WORD(r11)
86         stgu    r26, WORD(r11)
87         stgu    r27, WORD(r11)
88         stgu    r28, WORD(r11)
89         addi    r11, r1, 32 - 8
90         stfdu   f1, 8(r11)
91         stfdu   f2, 8(r11)
92         stfdu   f3, 8(r11)
93         stfdu   f4, 8(r11)
94         stfdu   f5, 8(r11)
95         stfdu   f6, 8(r11)
96         stfdu   f7, 8(r11)
97         stfdu   f8, 8(r11)
98         stfdu   f9, 8(r11)
99         stfdu   f10, 8(r11)
100         stfdu   f11, 8(r11)
101         stfdu   f12, 8(r11)
102         stfdu   f13, 8(r11)
103         stfdu   f14, 8(r11)
104         stfdu   f15, 8(r11)
105         stfdu   f16, 8(r11)
106         stfdu   f17, 8(r11)
107         stfdu   f18, 8(r11)
108         stfdu   f19, 8(r11)
109         stfdu   f20, 8(r11)
110         stfdu   f21, 8(r11)
111         stfdu   f22, 8(r11)
112         stfdu   f23, 8(r11)
113         stfdu   f24, 8(r11)
114         stfdu   f25, 8(r11)
115         stfdu   f26, 8(r11)
116         stfdu   f27, 8(r11)
117         stfdu   f28, 8(r11)
118         stfdu   f29, 8(r11)
119         stfdu   f30, 8(r11)
120         stfdu   f31, 8(r11)
121     /* Call the GC */
122         bl      _caml_garbage_collection
123     /* Reload new allocation pointer and allocation limit */
124         Loadglobal r31, _caml_young_ptr, r11
125         Loadglobal r30, _caml_young_limit, r11
126     /* Restore all regs used by the code generator */
127         addi    r11, r1, 8*32 + 32 - WORD
128         lgu     r3, WORD(r11)
129         lgu     r4, WORD(r11)
130         lgu     r5, WORD(r11)
131         lgu     r6, WORD(r11)
132         lgu     r7, WORD(r11)
133         lgu     r8, WORD(r11)
134         lgu     r9, WORD(r11)
135         lgu     r10, WORD(r11)
136         lgu     r14, WORD(r11)
137         lgu     r15, WORD(r11)
138         lgu     r16, WORD(r11)
139         lgu     r17, WORD(r11)
140         lgu     r18, WORD(r11)
141         lgu     r19, WORD(r11)
142         lgu     r20, WORD(r11)
143         lgu     r21, WORD(r11)
144         lgu     r22, WORD(r11)
145         lgu     r23, WORD(r11)
146         lgu     r24, WORD(r11)
147         lgu     r25, WORD(r11)
148         lgu     r26, WORD(r11)
149         lgu     r27, WORD(r11)
150         lgu     r28, WORD(r11)
151         addi    r11, r1, 32 - 8
152         lfdu    f1, 8(r11)
153         lfdu    f2, 8(r11)
154         lfdu    f3, 8(r11)
155         lfdu    f4, 8(r11)
156         lfdu    f5, 8(r11)
157         lfdu    f6, 8(r11)
158         lfdu    f7, 8(r11)
159         lfdu    f8, 8(r11)
160         lfdu    f9, 8(r11)
161         lfdu    f10, 8(r11)
162         lfdu    f11, 8(r11)
163         lfdu    f12, 8(r11)
164         lfdu    f13, 8(r11)
165         lfdu    f14, 8(r11)
166         lfdu    f15, 8(r11)
167         lfdu    f16, 8(r11)
168         lfdu    f17, 8(r11)
169         lfdu    f18, 8(r11)
170         lfdu    f19, 8(r11)
171         lfdu    f20, 8(r11)
172         lfdu    f21, 8(r11)
173         lfdu    f22, 8(r11)
174         lfdu    f23, 8(r11)
175         lfdu    f24, 8(r11)
176         lfdu    f25, 8(r11)
177         lfdu    f26, 8(r11)
178         lfdu    f27, 8(r11)
179         lfdu    f28, 8(r11)
180         lfdu    f29, 8(r11)
181         lfdu    f30, 8(r11)
182         lfdu    f31, 8(r11)
183     /* Return to caller, restarting the allocation */
184         Loadglobal r0, _caml_last_return_address, r11
185         addic   r0, r0, -16     /* Restart the allocation (4 instructions) */
186         mtlr    r0
187     /* Say we are back into Caml code */
188         li      r12, 0
189         Storeglobal r12, _caml_last_return_address, r11
190     /* Deallocate stack frame */
191         addi    r1, r1, FRAMESIZE
192     /* Return */
193         blr
194 #undef FRAMESIZE
195
196 /* Call a C function from Caml */
197
198         .globl  _caml_c_call
199 _caml_c_call:
200     /* Save return address */
201         mflr    r25
202     /* Get ready to call C function (address in 11) */
203         mtctr   r11
204     /* Record lowest stack address and return address */
205         Storeglobal r1, _caml_bottom_of_stack, r12
206         Storeglobal r25, _caml_last_return_address, r12
207     /* Make the exception handler and alloc ptr available to the C code */
208         Storeglobal r31, _caml_young_ptr, r11
209         Storeglobal r29, _caml_exception_pointer, r11
210     /* Call the function (address in link register) */
211         bctrl
212     /* Restore return address (in 25, preserved by the C function) */
213         mtlr    r25
214     /* Reload allocation pointer and allocation limit*/
215         Loadglobal r31, _caml_young_ptr, r11
216         Loadglobal r30, _caml_young_limit, r11
217     /* Say we are back into Caml code */
218         li      r12, 0
219         Storeglobal r12, _caml_last_return_address, r11
220     /* Return to caller */
221         blr
222
223 /* Raise an exception from Caml */
224         .globl  _caml_raise_exn
225 _caml_raise_exn:
226         addis   r11, 0, ha16(_caml_backtrace_active)
227         lwz     r11, lo16(_caml_backtrace_active)(r11)
228         cmpwi   r11, 0
229         bne     L110
230 L111:
231     /* Pop trap frame */
232         lg      r0, 0(r29)
233         mr      r1, r29
234         mtlr    r0
235         lg      r29, WORD(r1)
236         addi    r1, r1, 16
237     /* Branch to handler */
238         blr
239
240 L110:
241         mr      r28, r3        /* preserve exn bucket in callee-save */
242                                /* arg 1: exception bucket (already in r3) */
243         mflr    r4             /* arg 2: PC of raise */
244         mr      r5, r1         /* arg 3: SP of raise */
245         mr      r6, r29        /* arg 4: SP of handler */
246         addi    r1, r1, -(16*WORD)    /* reserve stack space for C call */
247         bl      _caml_stash_backtrace
248         mr      r3, r28
249         b       L111
250
251 /* Raise an exception from C */
252
253         .globl  _caml_raise_exception
254 _caml_raise_exception:
255         addis   r11, 0, ha16(_caml_backtrace_active)
256         lwz     r11, lo16(_caml_backtrace_active)(r11)
257         cmpwi   r11, 0
258         bne     L112
259 L113:
260     /* Reload Caml global registers */
261         Loadglobal r1, _caml_exception_pointer, r11
262         Loadglobal r31, _caml_young_ptr, r11
263         Loadglobal r30, _caml_young_limit, r11
264     /* Say we are back into Caml code */
265         li      r0, 0
266         Storeglobal r0, _caml_last_return_address, r11
267     /* Pop trap frame */
268         lg      r0, 0(r1)
269         lg      r29, WORD(r1)
270         mtlr    r0
271         addi    r1, r1, 16
272     /* Branch to handler */
273         blr
274 L112:
275         mr      r28, r3        /* preserve exn bucket in callee-save */
276                                /* arg 1: exception bucket (already in r3) */
277         Loadglobal r4, _caml_last_return_address, r11 /* arg 2: PC of raise */
278         Loadglobal r5, _caml_bottom_of_stack, r11 /* arg 3: SP of raise */
279         Loadglobal r6, _caml_exception_pointer, r11 /* arg 4: SP of handler */
280         addi    r1, r1, -(16*WORD)    /* reserve stack space for C call */
281         bl      _caml_stash_backtrace
282         mr      r3, r28
283         b       L113
284
285 /* Start the Caml program */
286
287         .globl  _caml_start_program
288 _caml_start_program:
289         Addrglobal r12, _caml_program
290
291 /* Code shared between caml_start_program and caml_callback */
292 L102:
293     /* Allocate and link stack frame */
294 #define FRAMESIZE (16 + 20*WORD + 18*8)
295         stgu    r1, -FRAMESIZE(r1)
296     /* Save return address */
297         mflr    r0
298         stg     r0,  WORD(r1)
299     /* Save all callee-save registers */
300     /* GPR14 ... GPR31, then FPR14 ... FPR31 starting at sp+16 */
301         addi    r11, r1, 16-WORD
302         stgu    r14, WORD(r11)
303         stgu    r15, WORD(r11)
304         stgu    r16, WORD(r11)
305         stgu    r17, WORD(r11)
306         stgu    r18, WORD(r11)
307         stgu    r19, WORD(r11)
308         stgu    r20, WORD(r11)
309         stgu    r21, WORD(r11)
310         stgu    r22, WORD(r11)
311         stgu    r23, WORD(r11)
312         stgu    r24, WORD(r11)
313         stgu    r25, WORD(r11)
314         stgu    r26, WORD(r11)
315         stgu    r27, WORD(r11)
316         stgu    r28, WORD(r11)
317         stgu    r29, WORD(r11)
318         stgu    r30, WORD(r11)
319         stgu    r31, WORD(r11)
320         stfdu   f14, 8(r11)
321         stfdu   f15, 8(r11)
322         stfdu   f16, 8(r11)
323         stfdu   f17, 8(r11)
324         stfdu   f18, 8(r11)
325         stfdu   f19, 8(r11)
326         stfdu   f20, 8(r11)
327         stfdu   f21, 8(r11)
328         stfdu   f22, 8(r11)
329         stfdu   f23, 8(r11)
330         stfdu   f24, 8(r11)
331         stfdu   f25, 8(r11)
332         stfdu   f26, 8(r11)
333         stfdu   f27, 8(r11)
334         stfdu   f28, 8(r11)
335         stfdu   f29, 8(r11)
336         stfdu   f30, 8(r11)
337         stfdu   f31, 8(r11)
338     /* Set up a callback link */
339         addi    r1, r1, -32
340         Loadglobal r9, _caml_bottom_of_stack, r11
341         Loadglobal r10, _caml_last_return_address, r11
342         Loadglobal r11, _caml_gc_regs, r11
343         stg     r9, 0(r1)
344         stg     r10, WORD(r1)
345         stg     r11, 2*WORD(r1)
346     /* Build an exception handler to catch exceptions escaping out of Caml */
347         bl      L103
348         b       L104
349 L103:
350         addi    r1, r1, -16
351         mflr    r0
352         stg     r0, 0(r1)
353         Loadglobal r11, _caml_exception_pointer, r11
354         stg     r11, WORD(r1)
355         mr      r29, r1
356     /* Reload allocation pointers */
357         Loadglobal r31, _caml_young_ptr, r11
358         Loadglobal r30, _caml_young_limit, r11
359     /* Say we are back into Caml code */
360         li      r0, 0
361         Storeglobal r0, _caml_last_return_address, r11
362     /* Call the Caml code */
363         mtctr    r12
364 L105:
365         bctrl
366     /* Pop the trap frame, restoring caml_exception_pointer */
367         lg      r9, WORD(r1)
368         Storeglobal r9, _caml_exception_pointer, r11
369         addi    r1, r1, 16
370     /* Pop the callback link, restoring the global variables */
371 L106:
372         lg      r9, 0(r1)
373         lg      r10, WORD(r1)
374         lg      r11, 2*WORD(r1)
375         Storeglobal r9, _caml_bottom_of_stack, r12
376         Storeglobal r10, _caml_last_return_address, r12
377         Storeglobal r11, _caml_gc_regs, r12
378         addi    r1, r1, 32
379     /* Update allocation pointer */
380         Storeglobal r31, _caml_young_ptr, r11
381     /* Restore callee-save registers */
382         addi    r11, r1, 16-WORD
383         lgu     r14, WORD(r11)
384         lgu     r15, WORD(r11)
385         lgu     r16, WORD(r11)
386         lgu     r17, WORD(r11)
387         lgu     r18, WORD(r11)
388         lgu     r19, WORD(r11)
389         lgu     r20, WORD(r11)
390         lgu     r21, WORD(r11)
391         lgu     r22, WORD(r11)
392         lgu     r23, WORD(r11)
393         lgu     r24, WORD(r11)
394         lgu     r25, WORD(r11)
395         lgu     r26, WORD(r11)
396         lgu     r27, WORD(r11)
397         lgu     r28, WORD(r11)
398         lgu     r29, WORD(r11)
399         lgu     r30, WORD(r11)
400         lgu     r31, WORD(r11)
401         lfdu    f14, 8(r11)
402         lfdu    f15, 8(r11)
403         lfdu    f16, 8(r11)
404         lfdu    f17, 8(r11)
405         lfdu    f18, 8(r11)
406         lfdu    f19, 8(r11)
407         lfdu    f20, 8(r11)
408         lfdu    f21, 8(r11)
409         lfdu    f22, 8(r11)
410         lfdu    f23, 8(r11)
411         lfdu    f24, 8(r11)
412         lfdu    f25, 8(r11)
413         lfdu    f26, 8(r11)
414         lfdu    f27, 8(r11)
415         lfdu    f28, 8(r11)
416         lfdu    f29, 8(r11)
417         lfdu    f30, 8(r11)
418         lfdu    f31, 8(r11)
419     /* Reload return address */
420         lg      r0, WORD(r1)
421         mtlr    r0
422     /* Return */
423         addi    r1, r1, FRAMESIZE
424         blr
425
426     /* The trap handler: */
427 L104:
428     /* Update caml_exception_pointer */
429         Storeglobal r29, _caml_exception_pointer, r11
430     /* Encode exception bucket as an exception result and return it */
431         ori     r3, r3, 2
432         b       L106
433 #undef FRAMESIZE
434
435 /* Callback from C to Caml */
436
437         .globl  _caml_callback_exn
438 _caml_callback_exn:
439     /* Initial shuffling of arguments */
440         mr      r0, r3            /* Closure */
441         mr      r3, r4            /* Argument */
442         mr      r4, r0
443         lg      r12, 0(r4)        /* Code pointer */
444         b       L102
445
446         .globl  _caml_callback2_exn
447 _caml_callback2_exn:
448         mr      r0, r3            /* Closure */
449         mr      r3, r4            /* First argument */
450         mr      r4, r5            /* Second argument */
451         mr      r5, r0
452         Addrglobal r12, _caml_apply2
453         b       L102
454
455         .globl  _caml_callback3_exn
456 _caml_callback3_exn:
457         mr      r0, r3            /* Closure */
458         mr      r3, r4            /* First argument */
459         mr      r4, r5            /* Second argument */
460         mr      r5, r6            /* Third argument */
461         mr      r6, r0
462         Addrglobal r12, _caml_apply3
463         b       L102
464
465 /* Frame table */
466
467         .const
468         .globl  _caml_system__frametable
469 _caml_system__frametable:
470         gdata   1               /* one descriptor */
471         gdata   L105 + 4       /* return address into callback */
472         .short  -1              /* negative size count => use callback link */
473         .short  0               /* no roots here */
474         .align  X(2,3)