]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmrun/ia64.S
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmrun / ia64.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 Q Public License version 1.0.               */
10 /*                                                                     */
11 /***********************************************************************/
12
13 /* $Id: ia64.S 9341 2009-09-17 13:05:47Z xleroy $ */
14
15 /* Asm part of the runtime system, IA64 processor */
16
17 #undef BROKEN_POSTINCREMENT
18
19 #define ADDRGLOBAL(reg,symb) \
20   add reg = @ltoff(symb), gp;; ld8 reg = [reg]
21 #define LOADGLOBAL(reg,symb) \
22   add r3 = @ltoff(symb), gp;; ld8 r3 = [r3];; ld8 reg = [r3]
23 #define STOREGLOBAL(reg,symb) \
24   add r3 = @ltoff(symb), gp;; ld8 r3 = [r3];; st8 [r3] = reg
25
26 #define ST8OFF(a,b,d) st8 [a] = b, d
27 #define LD8OFF(a,b,d) ld8 a = [b], d
28 #define STFDOFF(a,b,d) stfd [a] = b, d
29 #define LDFDOFF(a,b,d) ldfd a = [b], d
30 #define STFSPILLOFF(a,b,d) stf.spill [a] = b, d
31 #define LDFFILLOFF(a,b,d) ldf.fill a = [b], d
32
33 #define SAVE2(a,b) ST8OFF(r2, a, 16); ST8OFF(r3, b, 16)
34 #define SAVE4(a,b,c,d) SAVE2(a,b);; SAVE2(c,d)
35 #define SAVE8(a,b,c,d,e,f,g,h) SAVE4(a,b,c,d);; SAVE4(e,f,g,h)
36
37 #define LOAD2(a,b) LD8OFF(a, r2, 16); LD8OFF(b, r3, 16)
38 #define LOAD4(a,b,c,d) LOAD2(a,b);; LOAD2(c,d)
39 #define LOAD8(a,b,c,d,e,f,g,h) LOAD4(a,b,c,d);; LOAD4(e,f,g,h)
40
41 #define FSAVE2(a,b) STFDOFF(r2, a, 16); STFDOFF(r3, b, 16)
42 #define FSAVE4(a,b,c,d) FSAVE2(a,b);; FSAVE2(c,d)
43 #define FSAVE8(a,b,c,d,e,f,g,h) FSAVE4(a,b,c,d);; FSAVE4(e,f,g,h)
44
45 #define FLOAD2(a,b) LDFDOFF(a, r2, 16); LDFDOFF(b, r3, 16)
46 #define FLOAD4(a,b,c,d) FLOAD2(a,b);; FLOAD2(c,d)
47 #define FLOAD8(a,b,c,d,e,f,g,h) FLOAD4(a,b,c,d);; FLOAD4(e,f,g,h)
48
49 #define FSPILL2(a,b) STFSPILLOFF(r2, a, 32); STFSPILLOFF(r3, b, 32)
50 #define FSPILL4(a,b,c,d) FSPILL2(a,b);; FSPILL2(c,d)
51 #define FSPILL8(a,b,c,d,e,f,g,h) FSPILL4(a,b,c,d);; FSPILL4(e,f,g,h)
52
53 #define FFILL2(a,b) LDFFILLOFF(a, r2, 32); LDFFILLOFF(b, r3, 32)
54 #define FFILL4(a,b,c,d) FFILL2(a,b);; FFILL2(c,d)
55 #define FFILL8(a,b,c,d,e,f,g,h) FFILL4(a,b,c,d);; FFILL4(e,f,g,h)
56
57 /* Allocation */
58         .text
59
60         .global caml_allocN#
61         .proc   caml_allocN#
62         .align 16
63
64 /* caml_allocN: all code generator registers preserved,
65    gp preserved, r2 = requested size */
66
67 caml_allocN:
68         sub     r4 = r4, r2 ;;
69         cmp.ltu p0, p6 = r4, r5
70         (p6) br.ret.sptk b0 ;;
71         /* Fall through caml_call_gc */
72         br.sptk.many    caml_call_gc#
73
74         .endp   caml_allocN#
75
76 /* caml_call_gc: all code generator registers preserved,
77    gp preserved, r2 = requested size */
78
79         .global caml_call_gc#
80         .proc   caml_call_gc#
81         .align 16
82 caml_call_gc:
83         /* Allocate stack frame */
84         add     sp = -(16 + 16 + 80*8 + 42*8), sp ;;
85
86         /* Save requested size and GP on stack */
87         add     r3 = 16, sp ;;
88         ST8OFF(r3, r2, 8) ;;
89         st8     [r3] = gp
90
91         /* Record lowest stack address, return address, GC regs */
92         mov     r2 = b0 ;;
93         STOREGLOBAL(r2, caml_last_return_address#)
94         add     r2 = (16 + 16 + 80*8 + 42*8), sp ;;
95         STOREGLOBAL(r2, caml_bottom_of_stack#)
96         add     r2 = (16 + 16), sp ;;
97         STOREGLOBAL(r2, caml_gc_regs#)
98
99         /* Save all integer regs used by the code generator in the context */
100 .L100:  add     r3 = 8, r2 ;;
101         SAVE4(r8,r9,r10,r11) ;;
102         SAVE8(r16,r17,r18,r19,r20,r21,r22,r23) ;;
103         SAVE8(r24,r25,r26,r27,r28,r29,r30,r31) ;;
104         SAVE8(r32,r33,r34,r35,r36,r37,r38,r39) ;;
105         SAVE8(r40,r41,r42,r43,r44,r45,r46,r47) ;;
106         SAVE8(r48,r49,r50,r51,r52,r53,r54,r55) ;;
107         SAVE8(r56,r57,r58,r59,r60,r61,r62,r63) ;;
108         SAVE8(r64,r65,r66,r67,r68,r69,r70,r71) ;;
109         SAVE8(r72,r73,r74,r75,r76,r77,r78,r79) ;;
110         SAVE8(r80,r81,r82,r83,r84,r85,r86,r87) ;;
111         SAVE4(r88,r89,r90,r91) ;;
112
113         /* Save all floating-point registers not preserved by C */
114         FSAVE2(f6,f7) ;;
115         FSAVE8(f8,f9,f10,f11,f12,f13,f14,f15) ;;
116         FSAVE8(f32,f33,f34,f35,f36,f37,f38,f39) ;;
117         FSAVE8(f40,f41,f42,f43,f44,f45,f46,f47) ;;
118         FSAVE8(f48,f49,f50,f51,f52,f53,f54,f55) ;;
119         FSAVE8(f56,f57,f58,f59,f60,f61,f62,f63) ;;
120
121         /* Save current allocation pointer for debugging purposes */
122         STOREGLOBAL(r4, caml_young_ptr#)
123
124         /* Save trap pointer in case an exception is raised */
125         STOREGLOBAL(r6, caml_exception_pointer#)
126
127         /* Call the garbage collector */
128         br.call.sptk    b0 = caml_garbage_collection# ;;
129
130         /* Restore gp */
131         add     r3 = 24, sp ;;
132         ld8     gp = [r3]
133
134         /* Restore all integer regs from GC context */
135         add     r2 = (16 + 16), sp ;;
136         add     r3 = 8, r2 ;;
137         LOAD4(r8,r9,r10,r11) ;;
138         LOAD8(r16,r17,r18,r19,r20,r21,r22,r23) ;;
139         LOAD8(r24,r25,r26,r27,r28,r29,r30,r31) ;;
140         LOAD8(r32,r33,r34,r35,r36,r37,r38,r39) ;;
141         LOAD8(r40,r41,r42,r43,r44,r45,r46,r47) ;;
142         LOAD8(r48,r49,r50,r51,r52,r53,r54,r55) ;;
143         LOAD8(r56,r57,r58,r59,r60,r61,r62,r63) ;;
144         LOAD8(r64,r65,r66,r67,r68,r69,r70,r71) ;;
145         LOAD8(r72,r73,r74,r75,r76,r77,r78,r79) ;;
146         LOAD8(r80,r81,r82,r83,r84,r85,r86,r87) ;;
147         LOAD4(r88,r89,r90,r91) ;;
148
149         /* Restore all floating-point registers not preserved by C */
150         FLOAD2(f6,f7) ;;
151         FLOAD8(f8,f9,f10,f11,f12,f13,f14,f15) ;;
152         FLOAD8(f32,f33,f34,f35,f36,f37,f38,f39) ;;
153         FLOAD8(f40,f41,f42,f43,f44,f45,f46,f47) ;;
154         FLOAD8(f48,f49,f50,f51,f52,f53,f54,f55) ;;
155         FLOAD8(f56,f57,f58,f59,f60,f61,f62,f63) ;;
156
157         /* Reload new allocation pointer and allocation limit */
158         LOADGLOBAL(r4, caml_young_ptr#)
159         LOADGLOBAL(r5, caml_young_limit#)
160
161         /* Allocate space for the block */
162         add     r3 = 16, sp ;;
163         ld8     r2 = [r3] ;;
164         sub     r4 = r4, r2 ;;
165         cmp.ltu p6, p0 = r4, r5         /* enough space? */
166         (p6) br.cond.spnt .L100 ;;      /* no: call GC again */
167
168         /* Reload return address and say that we are back into Caml code */
169         ADDRGLOBAL(r3, caml_last_return_address#) ;;
170         ld8     r2 = [r3]
171         st8     [r3] = r0 ;;
172
173         /* Return to caller */
174         mov     b0 = r2
175         add     sp = (16 + 16 + 80*8 + 42*8), sp ;;
176         br.ret.sptk b0
177
178         .endp   caml_call_gc#
179
180 /* Call a C function from Caml */
181 /* Function to call is in r2 */
182
183         .global caml_c_call#
184         .proc   caml_c_call#
185         .align  16
186
187 caml_c_call:
188         /* The Caml code that called us does not expect any
189            code-generator registers to be preserved */
190
191         /* Recover entry point from the function pointer in r2 */
192         LD8OFF(r3, r2, 8) ;;
193         mov     b6 = r3
194
195         /* Preserve gp in r7 */
196         mov     r7 = gp
197
198         /* Record lowest stack address and return address */
199         mov     r14 = b0
200         STOREGLOBAL(sp, caml_bottom_of_stack#) ;;
201         STOREGLOBAL(r14, caml_last_return_address#)
202
203         /* Make the exception handler and alloc ptr available to the C code */
204         STOREGLOBAL(r4, caml_young_ptr#)
205         STOREGLOBAL(r6, caml_exception_pointer#)
206
207         /* Recover gp from the function pointer in r2 */
208         ld8     gp = [r2]
209
210         /* Call the function */
211         br.call.sptk    b0 = b6 ;;
212
213         /* Restore gp */
214         mov     gp = r7 ;;
215
216         /* Reload alloc ptr and alloc limit */
217         LOADGLOBAL(r4, caml_young_ptr#)
218         LOADGLOBAL(r5, caml_young_limit#)
219
220         /* Reload return address and say that we are back into Caml code */
221         ADDRGLOBAL(r3, caml_last_return_address#) ;;
222         ld8     r2 = [r3]
223         st8     [r3] = r0 ;;
224
225         /* Return to caller */
226         mov     b0 = r2 ;;
227         br.ret.sptk b0
228
229         .endp   caml_c_call#
230
231 /* Start the Caml program */
232
233         .global caml_start_program#
234         .proc   caml_start_program#
235         .align  16
236
237 caml_start_program:
238         ADDRGLOBAL(r2, caml_program#) ;;
239         mov     b6 = r2
240
241         /* Code shared with caml_callback* */
242 .L103:        
243         /* Allocate 64 "out" registers (for the Caml code) and no locals */
244         alloc   r3 = ar.pfs, 0, 0, 64, 0
245         add     sp = -(56 * 8), sp ;;
246
247         /* Save all callee-save registers on stack */
248         add     r2 = 16, sp ;;
249         ST8OFF(r2, r3, 8)       /* 0 : ar.pfs */
250         mov     r3 = b0 ;;
251         ST8OFF(r2, r3, 8) ;;    /* 1 : return address */
252         ST8OFF(r2, gp, 8)       /* 2 : gp */
253         mov     r3 = pr ;;
254         ST8OFF(r2, r3, 8)       /* 3 : predicates */
255         mov     r3 = ar.fpsr ;;
256         ST8OFF(r2, r3, 8)       /* 4 : ar.fpsr */
257         mov     r3 = ar.unat ;;
258         ST8OFF(r2, r3, 8)       /* 5 : ar.unat */
259         mov     r3 = ar.lc ;;
260         ST8OFF(r2, r3, 8)       /* 6 : ar.lc */
261         mov     r3 = b1 ;;
262         ST8OFF(r2, r3, 8)       /* 7 - 11 : b1 - b5 */
263         mov     r3 = b2 ;;
264         ST8OFF(r2, r3, 8)
265         mov     r3 = b3 ;;
266         ST8OFF(r2, r3, 8)
267         mov     r3 = b4 ;;
268         ST8OFF(r2, r3, 8)
269         mov     r3 = b5 ;;
270         ST8OFF(r2, r3, 8) ;;
271
272         add     r3 = 8, r2 ;;
273         SAVE4(r4,r5,r6,r7) ;;   /* 12 - 15 : r4 - r7 */
274
275         add     r3 = 16, r2 ;;  /* 16 - 55 : f2 - f5, f16 - f31 */
276         FSPILL4(f2,f3,f4,f5) ;;
277         FSPILL8(f16,f17,f18,f19,f20,f21,f22,f23) ;;
278         FSPILL8(f24,f25,f26,f27,f28,f29,f30,f31) ;;
279
280         /* Set up a callback link on the stack.  In addition to
281            the normal callback link contents (saved values of
282            caml_bottom_of_stack, caml_last_return_address and
283            caml_gc_regs), we also save there caml_saved_bsp
284            and caml_saved_rnat */
285         add     sp = -48, sp
286         LOADGLOBAL(r3, caml_bottom_of_stack#)
287         add     r2 = 16, sp ;;
288         ST8OFF(r2, r3, 8)
289         LOADGLOBAL(r3, caml_last_return_address#) ;;
290         ST8OFF(r2, r3, 8)
291         LOADGLOBAL(r3, caml_gc_regs#) ;;
292         ST8OFF(r2, r3, 8)
293         LOADGLOBAL(r3, caml_saved_bsp#) ;;
294         ST8OFF(r2, r3, 8)
295         LOADGLOBAL(r3, caml_saved_rnat#) ;;
296         ST8OFF(r2, r3, 8)
297
298         /* Set up a trap frame to catch exceptions escaping the Caml code */
299         mov     r6 = sp
300         add     sp = -16, sp ;;
301         LOADGLOBAL(r3, caml_exception_pointer#)
302         add     r2 = 16, sp ;;
303         ST8OFF(r2, r3, 8)
304 .L110:  mov     r3 = ip ;;
305         add     r3 = .L101 - .L110, r3 ;;
306         ST8OFF(r2, r3, 8) ;;
307
308         /* Save ar.bsp, flush register window, and save ar.rnat */
309         mov     r2 = ar.bsp ;;
310         STOREGLOBAL(r2, caml_saved_bsp#) ;;
311         mov     r14 = ar.rsc ;;
312         and     r2 = ~0x3, r14;;        /* set rsc.mode = 0 */
313         mov     ar.rsc = r2 ;;          /* RSE is in enforced lazy mode */
314         flushrs ;;                      /* must be first instr in group */
315         mov     r2 = ar.rnat ;;
316         STOREGLOBAL(r2, caml_saved_rnat#)
317         mov     ar.rsc = r14            /* restore original RSE mode */
318
319         /* Reload allocation pointers */
320         LOADGLOBAL(r4, caml_young_ptr#)
321         LOADGLOBAL(r5, caml_young_limit#)
322
323         /* We are back into Caml code */
324         STOREGLOBAL(r0, caml_last_return_address#)
325
326         /* Call the Caml code */
327         br.call.sptk b0 = b6 ;;
328 .L102:
329
330         /* Pop the trap frame, restoring caml_exception_pointer */
331         add     sp = 16, sp ;;
332         ld8     r2 = [sp] ;;
333         STOREGLOBAL(r2, caml_exception_pointer#)
334
335 .L104:
336         /* Pop the callback link, restoring the global variables */
337         add     r14 = 16, sp ;;
338         LD8OFF(r2, r14, 8) ;;
339         STOREGLOBAL(r2, caml_bottom_of_stack#)
340         LD8OFF(r2, r14, 8) ;;
341         STOREGLOBAL(r2, caml_last_return_address#)
342         LD8OFF(r2, r14, 8) ;;
343         STOREGLOBAL(r2, caml_gc_regs#)
344         LD8OFF(r2, r14, 8) ;;
345         STOREGLOBAL(r2, caml_saved_bsp#)
346         LD8OFF(r2, r14, 8) ;;
347         STOREGLOBAL(r2, caml_saved_rnat#)
348         add     sp = 48, sp
349
350         /* Update allocation pointer */
351         STOREGLOBAL(r4, caml_young_ptr#)
352
353         /* Restore all callee-save registers from stack */
354         add     r2 = 16, sp ;;
355         LD8OFF(r3, r2, 8) ;;    /* 0 : ar.pfs */
356         mov     ar.pfs = r3
357         LD8OFF(r3, r2, 8) ;;    /* 1 : return address */
358         mov     b0 = r3
359         LD8OFF(gp, r2, 8) ;;    /* 2 : gp */
360         LD8OFF(r3, r2, 8) ;;    /* 3 : predicates */
361         mov     pr = r3, -1
362         LD8OFF(r3, r2, 8) ;;    /* 4 : ar.fpsr */
363         mov     ar.fpsr = r3
364         LD8OFF(r3, r2, 8) ;;    /* 5 : ar.unat */
365         mov     ar.unat = r3
366         LD8OFF(r3, r2, 8) ;;    /* 6 : ar.lc */
367         mov     ar.lc = r3
368         LD8OFF(r3, r2, 8) ;;    /* 7 - 11 : b1 - b5 */
369         mov     b1 = r3
370         LD8OFF(r3, r2, 8) ;;
371         mov     b2 = r3
372         LD8OFF(r3, r2, 8) ;;
373         mov     b3 = r3
374         LD8OFF(r3, r2, 8) ;;
375         mov     b4 = r3
376         LD8OFF(r3, r2, 8) ;;
377         mov     b5 = r3
378
379         add     r3 = 8, r2 ;;
380         LOAD4(r4,r5,r6,r7) ;;   /* 12 - 15 : r4 - r7 */
381
382         add     r3 = 16, r2 ;;  /* 16 - 55 : f2 - f5, f16 - f31 */
383         FFILL4(f2,f3,f4,f5) ;;
384         FFILL8(f16,f17,f18,f19,f20,f21,f22,f23) ;;
385         FFILL8(f24,f25,f26,f27,f28,f29,f30,f31) ;;
386
387         /* Pop stack frame and return */
388         add     sp = (56 * 8), sp
389         br.ret.sptk.many b0 ;;
390
391         /* The trap handler */
392 .L101:
393         /* Save exception pointer */
394         STOREGLOBAL(r6, caml_exception_pointer#)
395
396         /* Encode exception bucket as exception result */
397         or      r8 = 2, r8
398
399         /* Return it */
400         br.sptk .L104 ;;
401
402         .endp   caml_start_program#
403
404 /* Raise an exception from C */
405
406         .global caml_raise_exception#
407         .proc   caml_raise_exception#
408         .align  16
409 caml_raise_exception:
410         /* Allocate 64 "out" registers (for the Caml code) and no locals */
411         /* Since we don't return, don't bother saving the PFS */
412         alloc   r2 = ar.pfs, 0, 0, 64, 0
413
414         /* Move exn bucket where Caml expects it */
415         mov     r8 = r32 ;;
416
417         /* Perform "context switch" as per the Software Conventions Guide,
418            chapter 10 */
419         flushrs ;;                      /* flush dirty registers to stack */
420         mov     r14 = ar.rsc ;;
421         and     r2 = ~0x3, r14;;        /* set rsc.mode = 0 */
422         dep     r2 = r0, r2, 16, 4 ;;   /* clear rsc.loadrs */
423         mov     ar.rsc = r2 ;;          /* RSE is in enforced lazy mode */
424         invala ;;                       /* Invalidate ALAT */
425         LOADGLOBAL(r2, caml_saved_bsp#) ;;
426         mov     ar.bspstore = r2        /* Restore ar.bspstore */
427         LOADGLOBAL(r2, caml_saved_rnat#) ;;
428         mov     ar.rnat = r2            /* Restore ar.rnat */
429         mov     ar.rsc = r14 ;;         /* Restore original RSE mode */
430
431         /* Reload allocation pointers and exception pointer */
432         LOADGLOBAL(r4, caml_young_ptr#)
433         LOADGLOBAL(r5, caml_young_limit#)
434         LOADGLOBAL(r6, caml_exception_pointer#)
435
436         /* Say that we're back into Caml */
437         STOREGLOBAL(r0, caml_last_return_address#)
438
439         /* Raise the exception proper */
440         mov     sp = r6
441         add     r2 = 8, r6 ;;
442         ld8     r6 = [r6]
443         ld8     r2 = [r2] ;;
444         mov     b6 = r2 ;;
445
446         /* Branch to handler.  Must use a call so as to set up the
447            CFM and PFS correctly. */
448         br.call.sptk.many b0 = b6
449
450         .endp   caml_raise_exception
451
452 /* Callbacks from C to Caml */
453
454         .global caml_callback_exn#
455         .proc   caml_callback_exn#
456         .align  16
457 caml_callback_exn:
458         /* Initial shuffling of arguments */
459         ld8     r3 = [r32]              /* code pointer */
460         mov     r2 = r32
461         mov     r32 = r33 ;;            /* first arg */
462         mov     r33 = r2                /* environment */
463         mov     b6 = r3
464         br.sptk .L103 ;;
465
466         .endp   caml_callback_exn#
467
468         .global caml_callback2_exn#
469         .proc   caml_callback2_exn#
470         .align  16
471 caml_callback2_exn:
472         /* Initial shuffling of arguments */
473         ADDRGLOBAL(r3, caml_apply2)    /* code pointer */
474         mov     r2 = r32
475         mov     r32 = r33               /* first arg */
476         mov     r33 = r34 ;;            /* second arg */
477         mov     r34 = r2                /* environment */
478         mov     b6 = r3
479         br.sptk .L103 ;;
480
481         .endp   caml_callback2_exn#
482
483         .global caml_callback3_exn#
484         .proc   caml_callback3_exn#
485         .align  16
486 caml_callback3_exn:
487         /* Initial shuffling of arguments */
488         ADDRGLOBAL(r3, caml_apply3)    /* code pointer */
489         mov     r2 = r32
490         mov     r32 = r33               /* first arg */
491         mov     r33 = r34               /* second arg */
492         mov     r34 = r35 ;;            /* third arg */
493         mov     r35 = r2                /* environment */
494         mov     b6 = r3
495         br.sptk .L103 ;;
496
497         .endp   caml_callback3_exn#
498
499 /* Glue code to call [caml_array_bound_error] */
500
501         .global caml_ml_array_bound_error#
502         .proc   caml_ml_array_bound_error#
503         .align  16
504 caml_ml_array_bound_error:
505         ADDRGLOBAL(r2, @fptr(caml_array_bound_error#))
506         br.sptk caml_c_call             /* never returns */        
507
508         .rodata
509
510         .global caml_system__frametable#
511         .type   caml_system__frametable#, @object
512         .size   caml_system__frametable#, 8
513 caml_system__frametable:
514         data8   1               /* one descriptor */
515         data8   .L102           /* return address into callback */
516         data2   -1              /* negative frame size => use callback link */
517         data2   0               /* no roots here */
518         .align  8
519
520 /* Global variables used by caml_raise_exception */
521
522         .common caml_saved_bsp#, 8, 8
523         .common caml_saved_rnat#, 8, 8