1/**************************************************************************/
2/*                                                                        */
3/*                                 OCaml                                  */
4/*                                                                        */
5/*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           */
6/*                                                                        */
7/*   Copyright 1996 Institut National de Recherche en Informatique et     */
8/*     en Automatique.                                                    */
9/*                                                                        */
10/*   All rights reserved.  This file is distributed under the terms of    */
11/*   the GNU Lesser General Public License version 2.1, with the          */
12/*   special exception on linking described in the file LICENSE.          */
13/*                                                                        */
14/**************************************************************************/
15
16#if _CALL_ELF == 2
17        .abiversion 2
18#endif
19
20#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
21#define EITHER(a,b) b
22#else
23#define EITHER(a,b) a
24#endif
25
26#define WORD EITHER(4,8)
27#define lg EITHER(lwz,ld)
28#define lgu EITHER(lwzu,ldu)
29#define stg EITHER(stw,std)
30#define stgu EITHER(stwu,stdu)
31#define datag EITHER(.long,.quad)
32#define wordalign EITHER(2,3)
33
34/* Stack layout */
35#if defined(MODEL_ppc)
36#define RESERVED_STACK 16
37#define PARAM_SAVE_AREA 0
38#define LR_SAVE 4
39#define TRAP_SIZE 16
40#define TRAP_HANDLER_OFFSET 0
41#define TRAP_PREVIOUS_OFFSET 4
42#define CALLBACK_LINK_SIZE 16
43#define CALLBACK_LINK_OFFSET 0
44#endif
45#if _CALL_ELF == 1
46#define RESERVED_STACK 48
47#define PARAM_SAVE_AREA (8*8)
48#define LR_SAVE 16
49#define TOC_SAVE 40
50#define TOC_SAVE_PARENT 8
51#define TRAP_SIZE 32
52#define TRAP_HANDLER_OFFSET 56
53#define TRAP_PREVIOUS_OFFSET 64
54#define CALLBACK_LINK_SIZE 32
55#define CALLBACK_LINK_OFFSET 48
56#endif
57#if _CALL_ELF == 2
58#define RESERVED_STACK 32
59#define PARAM_SAVE_AREA 0
60#define LR_SAVE 16
61#define TOC_SAVE_PARENT 8
62#define TOC_SAVE 24
63#define TRAP_SIZE 32
64#define TRAP_HANDLER_OFFSET 40
65#define TRAP_PREVIOUS_OFFSET 48
66#define CALLBACK_LINK_SIZE 32
67#define CALLBACK_LINK_OFFSET 32
68#endif
69
70/* Function definitions */
71
72#if defined(MODEL_ppc)
73#define FUNCTION(name) \
74  .section ".text"; \
75  .globl name; \
76  .type name, @function; \
77  .align 2; \
78  name:
79
80#define ENDFUNCTION(name) \
81  .size name, . - name
82
83#endif
84
85#if _CALL_ELF == 1
86#define FUNCTION(name) \
87  .section ".opd","aw"; \
88  .align 3; \
89  .globl name; \
90  .type name, @function; \
91  name: .quad .L.name,.TOC.@tocbase; \
92  .text; \
93  .align 2; \
94  .L.name:
95
96#define ENDFUNCTION(name) \
97  .size name, . - .L.name
98
99#endif
100
101#if _CALL_ELF == 2
102#define FUNCTION(name) \
103  .section ".text"; \
104  .globl name; \
105  .type name, @function; \
106  .align 2; \
107  name: ; \
108  0: addis 2, 12, (.TOC. - 0b)@ha; \
109  addi 2, 2, (.TOC. - 0b)@l; \
110  .localentry name, . - 0b
111
112#define ENDFUNCTION(name) \
113  .size name, . - name
114
115#endif
116
117/* Accessing global variables.  */
118
119#if defined(MODEL_ppc)
120
121#define Addrglobal(reg,glob) \
122        addis   reg, 0, glob@ha; \
123        addi    reg, reg, glob@l
124#define Loadglobal(reg,glob,tmp) \
125        addis   tmp, 0, glob@ha; \
126        lg      reg, glob@l(tmp)
127#define Storeglobal(reg,glob,tmp) \
128        addis   tmp, 0, glob@ha; \
129        stg     reg, glob@l(tmp)
130#define Loadglobal32(reg,glob,tmp) \
131        addis   tmp, 0, glob@ha; \
132        lwz     reg, glob@l(tmp)
133#define Storeglobal32(reg,glob,tmp) \
134        addis   tmp, 0, glob@ha; \
135        stw     reg, glob@l(tmp)
136
137#endif
138
139#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
140
141#define LSYMB(glob) .L##glob
142
143#define Addrglobal(reg,glob) \
144        ld      reg, LSYMB(glob)@toc(2)
145#define Loadglobal(reg,glob,tmp) \
146        Addrglobal(tmp,glob); \
147        lg      reg, 0(tmp)
148#define Storeglobal(reg,glob,tmp) \
149        Addrglobal(tmp,glob); \
150        stg     reg, 0(tmp)
151#define Loadglobal32(reg,glob,tmp) \
152        Addrglobal(tmp,glob); \
153        lwz     reg, 0(tmp)
154#define Storeglobal32(reg,glob,tmp) \
155        Addrglobal(tmp,glob); \
156        stw     reg, 0(tmp)
157
158#endif
159
160#if _CALL_ELF == 1
161        .section ".opd","aw"
162#else
163        .section ".text"
164#endif
165        .globl  caml_system__code_begin
166caml_system__code_begin:
167
168/* Invoke the garbage collector. */
169
170FUNCTION(caml_call_gc)
171#define STACKSIZE (WORD*32 + 8*32 + PARAM_SAVE_AREA + RESERVED_STACK)
172    /* 32 integer registers + 32 float registers + space for C call */
173    /* Set up stack frame */
174        stwu    1, -STACKSIZE(1)
175    /* Record return address into OCaml code */
176        mflr    0
177        Storeglobal(0, caml_last_return_address, 11)
178    /* Record lowest stack address */
179        addi    0, 1, STACKSIZE
180        Storeglobal(0, caml_bottom_of_stack, 11)
181    /* Record pointer to register array */
182        addi    0, 1, 8*32 + PARAM_SAVE_AREA + RESERVED_STACK
183        Storeglobal(0, caml_gc_regs, 11)
184    /* Save current allocation pointer for debugging purposes */
185        Storeglobal(31, caml_young_ptr, 11)
186    /* Save exception pointer (if e.g. a sighandler raises) */
187        Storeglobal(29, caml_exception_pointer, 11)
188    /* Save all registers used by the code generator */
189        addi    11, 1, 8*32 + PARAM_SAVE_AREA + RESERVED_STACK - WORD
190        stgu    3, WORD(11)
191        stgu    4, WORD(11)
192        stgu    5, WORD(11)
193        stgu    6, WORD(11)
194        stgu    7, WORD(11)
195        stgu    8, WORD(11)
196        stgu    9, WORD(11)
197        stgu    10, WORD(11)
198        stgu    14, WORD(11)
199        stgu    15, WORD(11)
200        stgu    16, WORD(11)
201        stgu    17, WORD(11)
202        stgu    18, WORD(11)
203        stgu    19, WORD(11)
204        stgu    20, WORD(11)
205        stgu    21, WORD(11)
206        stgu    22, WORD(11)
207        stgu    23, WORD(11)
208        stgu    24, WORD(11)
209        stgu    25, WORD(11)
210        stgu    26, WORD(11)
211        stgu    27, WORD(11)
212        stgu    28, WORD(11)
213        addi    11, 1, PARAM_SAVE_AREA + RESERVED_STACK - 8
214        stfdu   1, 8(11)
215        stfdu   2, 8(11)
216        stfdu   3, 8(11)
217        stfdu   4, 8(11)
218        stfdu   5, 8(11)
219        stfdu   6, 8(11)
220        stfdu   7, 8(11)
221        stfdu   8, 8(11)
222        stfdu   9, 8(11)
223        stfdu   10, 8(11)
224        stfdu   11, 8(11)
225        stfdu   12, 8(11)
226        stfdu   13, 8(11)
227        stfdu   14, 8(11)
228        stfdu   15, 8(11)
229        stfdu   16, 8(11)
230        stfdu   17, 8(11)
231        stfdu   18, 8(11)
232        stfdu   19, 8(11)
233        stfdu   20, 8(11)
234        stfdu   21, 8(11)
235        stfdu   22, 8(11)
236        stfdu   23, 8(11)
237        stfdu   24, 8(11)
238        stfdu   25, 8(11)
239        stfdu   26, 8(11)
240        stfdu   27, 8(11)
241        stfdu   28, 8(11)
242        stfdu   29, 8(11)
243        stfdu   30, 8(11)
244        stfdu   31, 8(11)
245    /* Call the GC */
246        bl      caml_garbage_collection
247#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
248        nop
249#endif
250    /* Reload new allocation pointer and allocation limit */
251        Loadglobal(31, caml_young_ptr, 11)
252        Loadglobal(30, caml_young_limit, 11)
253    /* Restore all regs used by the code generator */
254        addi    11, 1, 8*32 + PARAM_SAVE_AREA + RESERVED_STACK - WORD
255        lgu     3, WORD(11)
256        lgu     4, WORD(11)
257        lgu     5, WORD(11)
258        lgu     6, WORD(11)
259        lgu     7, WORD(11)
260        lgu     8, WORD(11)
261        lgu     9, WORD(11)
262        lgu     10, WORD(11)
263        lgu     14, WORD(11)
264        lgu     15, WORD(11)
265        lgu     16, WORD(11)
266        lgu     17, WORD(11)
267        lgu     18, WORD(11)
268        lgu     19, WORD(11)
269        lgu     20, WORD(11)
270        lgu     21, WORD(11)
271        lgu     22, WORD(11)
272        lgu     23, WORD(11)
273        lgu     24, WORD(11)
274        lgu     25, WORD(11)
275        lgu     26, WORD(11)
276        lgu     27, WORD(11)
277        lgu     28, WORD(11)
278        addi    11, 1, PARAM_SAVE_AREA + RESERVED_STACK - 8
279        lfdu    1, 8(11)
280        lfdu    2, 8(11)
281        lfdu    3, 8(11)
282        lfdu    4, 8(11)
283        lfdu    5, 8(11)
284        lfdu    6, 8(11)
285        lfdu    7, 8(11)
286        lfdu    8, 8(11)
287        lfdu    9, 8(11)
288        lfdu    10, 8(11)
289        lfdu    11, 8(11)
290        lfdu    12, 8(11)
291        lfdu    13, 8(11)
292        lfdu    14, 8(11)
293        lfdu    15, 8(11)
294        lfdu    16, 8(11)
295        lfdu    17, 8(11)
296        lfdu    18, 8(11)
297        lfdu    19, 8(11)
298        lfdu    20, 8(11)
299        lfdu    21, 8(11)
300        lfdu    22, 8(11)
301        lfdu    23, 8(11)
302        lfdu    24, 8(11)
303        lfdu    25, 8(11)
304        lfdu    26, 8(11)
305        lfdu    27, 8(11)
306        lfdu    28, 8(11)
307        lfdu    29, 8(11)
308        lfdu    30, 8(11)
309        lfdu    31, 8(11)
310    /* Return to caller, restarting the allocation */
311        Loadglobal(11, caml_last_return_address, 11)
312        addi    11, 11, -16     /* Restart the allocation (4 instructions) */
313        mtlr    11
314    /* For PPC64: restore the TOC that the caller saved at the usual place */
315#ifdef TOC_SAVE
316        ld      2, (STACKSIZE + TOC_SAVE)(1)
317#endif
318    /* Deallocate stack frame */
319        addi    1, 1, STACKSIZE
320        blr
321#undef STACKSIZE
322ENDFUNCTION(caml_call_gc)
323
324/* Call a C function from OCaml */
325
326FUNCTION(caml_c_call)
327        .cfi_startproc
328    /* Save return address in a callee-save register */
329        mflr    27
330        .cfi_register 65, 27
331    /* Record lowest stack address and return address */
332        Storeglobal(1, caml_bottom_of_stack, 11)
333        Storeglobal(27, caml_last_return_address, 11)
334    /* Make the exception handler and alloc ptr available to the C code */
335        Storeglobal(31, caml_young_ptr, 11)
336        Storeglobal(29, caml_exception_pointer, 11)
337    /* Call C function (address in r28) */
338#if defined(MODEL_ppc)
339        mtctr   28
340        bctrl
341#elif _CALL_ELF == 1
342        ld      0, 0(28)
343        mr      26, 2   /* save current TOC in a callee-save register */
344        mtctr   0
345        ld      2, 8(28)
346        bctrl
347        mr      2, 26   /* restore current TOC */
348#elif _CALL_ELF == 2
349        mtctr   28
350        mr      12, 28
351        mr      26, 2   /* save current TOC in a callee-save register */
352        bctrl
353        mr      2, 26   /* restore current TOC */
354#else
355#error "wrong MODEL"
356#endif
357    /* Restore return address (in 27, preserved by the C function) */
358        mtlr    27
359    /* Reload allocation pointer and allocation limit*/
360        Loadglobal(31, caml_young_ptr, 11)
361        Loadglobal(30, caml_young_limit, 11)
362    /* Return to caller */
363        blr
364        .cfi_endproc
365ENDFUNCTION(caml_c_call)
366
367/* Raise an exception from OCaml */
368
369FUNCTION(caml_raise_exn)
370        Loadglobal32(0, caml_backtrace_active, 11)
371        cmpwi   0, 0
372        bne     .L111
373.L110:
374    /* Pop trap frame */
375        lg      0, TRAP_HANDLER_OFFSET(29)
376        mr      1, 29
377        mtctr   0
378        lg      29, TRAP_PREVIOUS_OFFSET(1)
379        addi    1, 1, TRAP_SIZE
380    /* Branch to handler */
381        bctr
382.L111:
383        mr      28, 3           /* preserve exn bucket in callee-save reg */
384                                /* arg1: exception bucket, already in r3 */
385        mflr    4               /* arg2: PC of raise */
386        mr      5, 1            /* arg3: SP of raise */
387        mr      6, 29           /* arg4: SP of handler */
388        addi    1, 1, -(PARAM_SAVE_AREA + RESERVED_STACK)
389                                /* reserve stack space for C call */
390        bl      caml_stash_backtrace
391#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
392        nop
393#endif
394        mr      3, 28           /* restore exn bucket */
395        b       .L110           /* raise the exn */
396ENDFUNCTION(caml_raise_exn)
397
398/* Raise an exception from C */
399
400FUNCTION(caml_raise_exception)
401        Loadglobal32(0, caml_backtrace_active, 11)
402        cmpwi   0, 0
403        bne     .L121
404.L120:
405    /* Reload OCaml global registers */
406        Loadglobal(1, caml_exception_pointer, 11)
407        Loadglobal(31, caml_young_ptr, 11)
408        Loadglobal(30, caml_young_limit, 11)
409    /* Pop trap frame */
410        lg      0, TRAP_HANDLER_OFFSET(1)
411        mtctr   0
412        lg      29, TRAP_PREVIOUS_OFFSET(1)
413        addi    1, 1, TRAP_SIZE
414    /* Branch to handler */
415        bctr
416.L121:
417        li      0, 0
418        Storeglobal32(0, caml_backtrace_pos, 11)
419        mr      28, 3           /* preserve exn bucket in callee-save reg */
420                                /* arg1: exception bucket, already in r3 */
421        Loadglobal(4, caml_last_return_address, 11) /* arg2: PC of raise */
422        Loadglobal(5, caml_bottom_of_stack, 11)     /* arg3: SP of raise */
423        Loadglobal(6, caml_exception_pointer, 11)   /* arg4: SP of handler */
424        addi    1, 1, -(PARAM_SAVE_AREA + RESERVED_STACK)
425                                         /* reserve stack space for C call */
426        bl      caml_stash_backtrace
427#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
428        nop
429#endif
430        mr      3, 28           /* restore exn bucket */
431        b       .L120           /* raise the exn */
432ENDFUNCTION(caml_raise_exception)
433
434/* Start the OCaml program */
435
436FUNCTION(caml_start_program)
437        .cfi_startproc
438#define STACKSIZE (WORD*18 + 8*18 + CALLBACK_LINK_SIZE + RESERVED_STACK)
439  /* 18 callee-save GPR14...GPR31 + 18 callee-save FPR14...FPR31 */
440        Addrglobal(12, caml_program)
441/* Code shared between caml_start_program and caml_callback */
442.L102:
443    /* Allocate and link stack frame */
444        stgu    1, -STACKSIZE(1)
445        .cfi_adjust_cfa_offset STACKSIZE
446    /* Save return address */
447        mflr    0
448        stg     0, (STACKSIZE + LR_SAVE)(1)
449        .cfi_offset 65, LR_SAVE
450    /* Save TOC pointer if applicable */
451#ifdef TOC_SAVE_PARENT
452        std     2, (STACKSIZE + TOC_SAVE_PARENT)(1)
453#endif
454    /* Save all callee-save registers */
455        addi    11, 1, CALLBACK_LINK_SIZE + RESERVED_STACK - WORD
456        stgu    14, WORD(11)
457        stgu    15, WORD(11)
458        stgu    16, WORD(11)
459        stgu    17, WORD(11)
460        stgu    18, WORD(11)
461        stgu    19, WORD(11)
462        stgu    20, WORD(11)
463        stgu    21, WORD(11)
464        stgu    22, WORD(11)
465        stgu    23, WORD(11)
466        stgu    24, WORD(11)
467        stgu    25, WORD(11)
468        stgu    26, WORD(11)
469        stgu    27, WORD(11)
470        stgu    28, WORD(11)
471        stgu    29, WORD(11)
472        stgu    30, WORD(11)
473        stgu    31, WORD(11)
474        stfdu   14, 8(11)
475        stfdu   15, 8(11)
476        stfdu   16, 8(11)
477        stfdu   17, 8(11)
478        stfdu   18, 8(11)
479        stfdu   19, 8(11)
480        stfdu   20, 8(11)
481        stfdu   21, 8(11)
482        stfdu   22, 8(11)
483        stfdu   23, 8(11)
484        stfdu   24, 8(11)
485        stfdu   25, 8(11)
486        stfdu   26, 8(11)
487        stfdu   27, 8(11)
488        stfdu   28, 8(11)
489        stfdu   29, 8(11)
490        stfdu   30, 8(11)
491        stfdu   31, 8(11)
492    /* Set up a callback link */
493        Loadglobal(11, caml_bottom_of_stack, 11)
494        stg     11, CALLBACK_LINK_OFFSET(1)
495        Loadglobal(11, caml_last_return_address, 11)
496        stg     11, (CALLBACK_LINK_OFFSET + WORD)(1)
497        Loadglobal(11, caml_gc_regs, 11)
498        stg     11, (CALLBACK_LINK_OFFSET + 2 * WORD)(1)
499    /* Build an exception handler to catch exceptions escaping out of OCaml */
500        bl      .L103
501        b       .L104
502.L103:
503        addi    1, 1, -TRAP_SIZE
504        .cfi_adjust_cfa_offset TRAP_SIZE
505        mflr    0
506        stg     0, TRAP_HANDLER_OFFSET(1)
507        Loadglobal(11, caml_exception_pointer, 11)
508        stg     11, TRAP_PREVIOUS_OFFSET(1)
509        mr      29, 1
510    /* Reload allocation pointers */
511        Loadglobal(31, caml_young_ptr, 11)
512        Loadglobal(30, caml_young_limit, 11)
513    /* Call the OCaml code (address in r12) */
514#if defined(MODEL_ppc)
515        mtctr   12
516.L105:  bctrl
517#elif _CALL_ELF == 1
518        ld      0, 0(12)
519        mtctr   0
520        std     2, TOC_SAVE(1)
521        ld      2, 8(12)
522.L105:  bctrl
523        ld      2, TOC_SAVE(1)
524#elif _CALL_ELF == 2
525        mtctr   12
526        std     2, TOC_SAVE(1)
527.L105:  bctrl
528        ld      2, TOC_SAVE(1)
529#else
530#error "wrong MODEL"
531#endif
532    /* Pop the trap frame, restoring caml_exception_pointer */
533        lg      0, TRAP_PREVIOUS_OFFSET(1)
534        Storeglobal(0, caml_exception_pointer, 11)
535        addi    1, 1, TRAP_SIZE
536        .cfi_adjust_cfa_offset -TRAP_SIZE
537    /* Pop the callback link, restoring the global variables */
538.L106:
539        lg      0, CALLBACK_LINK_OFFSET(1)
540        Storeglobal(0, caml_bottom_of_stack, 11)
541        lg      0, (CALLBACK_LINK_OFFSET + WORD)(1)
542        Storeglobal(0, caml_last_return_address, 11)
543        lg      0, (CALLBACK_LINK_OFFSET + 2 * WORD)(1)
544        Storeglobal(0, caml_gc_regs, 11)
545    /* Update allocation pointer */
546        Storeglobal(31, caml_young_ptr, 11)
547    /* Restore callee-save registers */
548        addi    11, 1, CALLBACK_LINK_SIZE + RESERVED_STACK - WORD
549        lgu     14, WORD(11)
550        lgu     15, WORD(11)
551        lgu     16, WORD(11)
552        lgu     17, WORD(11)
553        lgu     18, WORD(11)
554        lgu     19, WORD(11)
555        lgu     20, WORD(11)
556        lgu     21, WORD(11)
557        lgu     22, WORD(11)
558        lgu     23, WORD(11)
559        lgu     24, WORD(11)
560        lgu     25, WORD(11)
561        lgu     26, WORD(11)
562        lgu     27, WORD(11)
563        lgu     28, WORD(11)
564        lgu     29, WORD(11)
565        lgu     30, WORD(11)
566        lgu     31, WORD(11)
567        lfdu    14, 8(11)
568        lfdu    15, 8(11)
569        lfdu    16, 8(11)
570        lfdu    17, 8(11)
571        lfdu    18, 8(11)
572        lfdu    19, 8(11)
573        lfdu    20, 8(11)
574        lfdu    21, 8(11)
575        lfdu    22, 8(11)
576        lfdu    23, 8(11)
577        lfdu    24, 8(11)
578        lfdu    25, 8(11)
579        lfdu    26, 8(11)
580        lfdu    27, 8(11)
581        lfdu    28, 8(11)
582        lfdu    29, 8(11)
583        lfdu    30, 8(11)
584        lfdu    31, 8(11)
585    /* Reload return address */
586        lg      0, (STACKSIZE + LR_SAVE)(1)
587        mtlr    0
588    /* Return */
589        addi    1, 1, STACKSIZE
590        blr
591
592    /* The trap handler: */
593.L104:
594    /* Restore TOC pointer */
595#ifdef TOC_SAVE_PARENT
596        ld      2, (STACKSIZE + TOC_SAVE_PARENT)(1)
597#endif
598    /* Update caml_exception_pointer */
599        Storeglobal(29, caml_exception_pointer, 11)
600    /* Encode exception bucket as an exception result and return it */
601        ori     3, 3, 2
602        b       .L106
603#undef STACKSIZE
604        .cfi_endproc
605ENDFUNCTION(caml_start_program)
606
607/* Callback from C to OCaml */
608
609FUNCTION(caml_callback_exn)
610    /* Initial shuffling of arguments */
611        mr      0, 3            /* Closure */
612        mr      3, 4            /* Argument */
613        mr      4, 0
614        lg      12, 0(4)        /* Code pointer */
615        b       .L102
616ENDFUNCTION(caml_callback_exn)
617
618FUNCTION(caml_callback2_exn)
619        mr      0, 3            /* Closure */
620        mr      3, 4            /* First argument */
621        mr      4, 5            /* Second argument */
622        mr      5, 0
623        Addrglobal(12, caml_apply2)
624        b       .L102
625ENDFUNCTION(caml_callback2_exn)
626
627FUNCTION(caml_callback3_exn)
628        mr      0, 3            /* Closure */
629        mr      3, 4            /* First argument */
630        mr      4, 5            /* Second argument */
631        mr      5, 6            /* Third argument */
632        mr      6, 0
633        Addrglobal(12, caml_apply3)
634        b       .L102
635ENDFUNCTION(caml_callback3_exn)
636
637#if _CALL_ELF == 1
638        .section ".opd","aw"
639#else
640        .section ".text"
641#endif
642
643        .globl  caml_system__code_end
644caml_system__code_end:
645
646/* Frame table */
647
648        .section ".data"
649        .globl  caml_system__frametable
650        .type   caml_system__frametable, @object
651caml_system__frametable:
652        datag   1               /* one descriptor */
653        datag   .L105 + 4       /* return address into callback */
654        .short  -1              /* negative size count => use callback link */
655        .short  0               /* no roots here */
656
657/* TOC entries */
658
659#if defined(MODEL_ppc64) || defined(MODEL_ppc64le)
660
661        .section ".toc", "aw"
662
663#define TOCENTRY(glob) LSYMB(glob): .quad glob
664
665TOCENTRY(caml_apply2)
666TOCENTRY(caml_apply3)
667TOCENTRY(caml_backtrace_active)
668TOCENTRY(caml_backtrace_pos)
669TOCENTRY(caml_bottom_of_stack)
670TOCENTRY(caml_exception_pointer)
671TOCENTRY(caml_gc_regs)
672TOCENTRY(caml_last_return_address)
673TOCENTRY(caml_program)
674TOCENTRY(caml_young_limit)
675TOCENTRY(caml_young_ptr)
676
677#endif
678
679/* Mark stack as non-executable */
680        .section .note.GNU-stack,"",%progbits
681