Domain state support for s390x

master
KC Sivaramakrishnan 2019-06-17 12:00:24 +00:00
parent 750fd7a795
commit 8d49d48767
3 changed files with 122 additions and 113 deletions

View File

@ -430,7 +430,8 @@ let emit_instr i =
gc_frame_lbl = lbl_frame } :: !call_gc_sites;
`{emit_label lbl_redo}:`;
` lay {emit_reg i.res.(0)}, {emit_int(-n+8)}(%r11)\n`;
` clgr {emit_reg i.res.(0)}, %r10\n`;
let offset = Domainstate.(idx_of_field Domain_young_limit) * 8 in
` clg {emit_reg i.res.(0)}, {emit_int offset}(%r10)\n`;
` brcl 12, {emit_label lbl_call_gc}\n`;
(* less than or equal *)
` lay %r11, -8({emit_reg i.res.(0)})\n`
@ -629,10 +630,16 @@ let emit_instr i =
stack_offset := !stack_offset - 16
| Lraise k ->
begin match k with
| Cmm.Raise_withtrace ->
| Lambda.Raise_regular->
let offset = Domainstate.(idx_of_field Domain_backtrace_pos) * 8 in
` lghi %r1, 0\n`;
` stg %r1, {emit_int offset}(%r10)\n`;
emit_call "caml_raise_exn";
`{record_frame Reg.Set.empty true i.dbg}\n`
| Cmm.Raise_notrace ->
| Lambda.Raise_reraise ->
emit_call "caml_raise_exn";
`{record_frame Reg.Set.empty true i.dbg}\n`
| Lambda.Raise_notrace ->
` lg %r1, 0(%r13)\n`;
` lgr %r15, %r13\n`;
` lg %r13, {emit_int size_addr}(%r15)\n`;

View File

@ -35,7 +35,7 @@ let word_addressed = false
2 - 5 function arguments and results (volatile)
6 function arguments and results (preserved by C)
7 - 9 general purpose, preserved by C
10 allocation limit (preserved by C)
10 domain state pointer (preserved by C)
11 allocation pointer (preserved by C)
12 general purpose (preserved by C)
13 trap pointer (preserved by C)

View File

@ -19,30 +19,24 @@
#define Addrglobal(reg,glob) \
lgrl reg, glob@GOTENT
#define Loadglobal(reg,glob) \
lgrl %r1, glob@GOTENT; lg reg, 0(%r1)
#define Storeglobal(reg,glob) \
lgrl %r1, glob@GOTENT; stg reg, 0(%r1)
#define Loadglobal32(reg,glob) \
lgrl %r1, glob@GOTENT; lgf reg, 0(%r1)
#define Storeglobal32(reg,glob) \
lgrl %r1, glob@GOTENT; sty reg, 0(%r1)
#else
#define Addrglobal(reg,glob) \
larl reg, glob
#define Loadglobal(reg,glob) \
lgrl reg, glob
#define Storeglobal(reg,glob) \
stgrl reg, glob
#define Loadglobal32(reg,glob) \
lgfrl reg, glob
#define Storeglobal32(reg,glob) \
strl reg, glob
#endif
#define CAML_CONFIG_H_NO_TYPEDEFS
#include "../runtime/caml/config.h"
.set domain_curr_field, 0
#define DOMAIN_STATE(c_type, name) \
.equ domain_field_caml_##name, domain_curr_field ; \
.set domain_curr_field, domain_curr_field + 1
#include "../runtime/caml/domain_state.tbl"
#undef DOMAIN_STATE
#define Caml_state(var) 8*domain_field_caml_##var(%r10)
.section ".text"
/* Invoke the garbage collector. */
@ -57,17 +51,17 @@ caml_call_gc:
#define FRAMESIZE (16*8 + 16*8)
lay %r15, -FRAMESIZE(%r15)
/* Record return address into OCaml code */
Storeglobal(%r14, caml_last_return_address)
stg %r14, Caml_state(last_return_address)
/* Record lowest stack address */
lay %r0, FRAMESIZE(%r15)
Storeglobal(%r0, caml_bottom_of_stack)
stg %r0, Caml_state(bottom_of_stack)
/* Record pointer to register array */
lay %r0, (8*16)(%r15)
Storeglobal(%r0, caml_gc_regs)
stg %r0, Caml_state(gc_regs)
/* Save current allocation pointer for debugging purposes */
Storeglobal(%r11, caml_young_ptr)
stg %r11, Caml_state(young_ptr)
/* Save exception pointer (if e.g. a sighandler raises) */
Storeglobal(%r13, caml_exception_pointer)
stg %r13, Caml_state(exception_pointer)
/* Save all registers used by the code generator */
stmg %r2,%r9, (8*16)(%r15)
stg %r12, (8*16 + 8*8)(%r15)
@ -88,13 +82,12 @@ caml_call_gc:
std %f14, 112(%r15)
std %f15, 120(%r15)
/* Call the GC */
lay %r15, -160(%r15)
lay %r15, -160(%r15)
stg %r15, 0(%r15)
brasl %r14, caml_garbage_collection@PLT
lay %r15, 160(%r15)
/* Reload new allocation pointer and allocation limit */
Loadglobal(%r11, caml_young_ptr)
Loadglobal(%r10, caml_young_limit)
lay %r15, 160(%r15)
/* Reload new allocation pointer */
lg %r11, Caml_state(young_ptr)
/* Restore all regs used by the code generator */
lmg %r2,%r9, (8*16)(%r15)
lg %r12, (8*16 + 8*8)(%r15)
@ -115,34 +108,33 @@ caml_call_gc:
ld %f14, 112(%r15)
ld %f15, 120(%r15)
/* Return to caller */
Loadglobal(%r1, caml_last_return_address)
lg %r1, Caml_state(last_return_address)
/* Deallocate stack frame */
lay %r15, FRAMESIZE(%r15)
/* Return */
br %r1
br %r1
/* Call a C function from OCaml */
.globl caml_c_call
.type caml_c_call, @function
caml_c_call:
Storeglobal(%r15, caml_bottom_of_stack)
stg %r15, Caml_state(bottom_of_stack)
.L101:
/* Save return address */
ldgr %f15, %r14
/* Get ready to call C function (address in r7) */
/* Record lowest stack address and return address */
Storeglobal(%r14, caml_last_return_address)
stg %r14, Caml_state(last_return_address)
/* Make the exception handler and alloc ptr available to the C code */
Storeglobal(%r11, caml_young_ptr)
Storeglobal(%r13, caml_exception_pointer)
stg %r11, Caml_state(young_ptr)
stg %r13, Caml_state(exception_pointer)
/* Call the function */
basr %r14, %r7
/* restore return address */
lgdr %r14,%f15
/* Reload allocation pointer and allocation limit*/
Loadglobal(%r11, caml_young_ptr)
Loadglobal(%r10, caml_young_limit)
/* Reload allocation pointer */
lg %r11, Caml_state(young_ptr)
/* Return to caller */
br %r14
@ -150,24 +142,24 @@ caml_c_call:
.globl caml_raise_exn
.type caml_raise_exn, @function
caml_raise_exn:
Loadglobal32(%r0, caml_backtrace_active)
lg %r0, Caml_state(backtrace_active)
cgfi %r0, 0
jne .L110
.L111:
/* Pop trap frame */
lg %r1, 0(%r13)
lgr %r15, %r13
lg %r13, 8(13)
agfi %r15, 16
lg %r13, 8(13)
agfi %r15, 16
/* Branch to handler */
br %r1
.L110:
ldgr %f15, %r2 /* preserve exn bucket in callee-save reg */
/* arg1: exception bucket, already in r3 */
lgr %r3,%r14 /* arg2: PC of raise */
/* arg1: exception bucket, already in r2 */
lgr %r3, %r14 /* arg2: PC of raise */
lgr %r4, %r15 /* arg3: SP of raise */
lgr %r5, %r13 /* arg4: SP of handler */
agfi %r15, -160 /* reserve stack space for C call */
lgr %r5, %r13 /* arg4: SP of handler */
agfi %r15, -160 /* reserve stack space for C call */
brasl %r14, caml_stash_backtrace@PLT
agfi %r15, 160
lgdr %r2,%f15 /* restore exn bucket */
@ -178,14 +170,15 @@ caml_raise_exn:
.globl caml_raise_exception
.type caml_raise_exception, @function
caml_raise_exception:
Loadglobal32(%r0, caml_backtrace_active)
lgr %r10, %r2 /* Load domain state pointer */
lgr %r2, %r3 /* Move exception bucket to arg1 register */
lg %r0, Caml_state(backtrace_active)
cgfi %r0, 0
jne .L112
.L113:
/* Reload OCaml global registers */
Loadglobal(%r15, caml_exception_pointer)
Loadglobal(%r11, caml_young_ptr)
Loadglobal(%r10, caml_young_limit)
lg %r15, Caml_state(exception_pointer)
lg %r11, Caml_state(young_ptr)
/* Pop trap frame */
lg %r1, 0(%r15)
lg %r13, 8(%r15)
@ -193,17 +186,17 @@ caml_raise_exception:
/* Branch to handler */
br %r1;
.L112:
lgfi %r0, 0
Storeglobal32(%r0, caml_backtrace_pos)
lgfi %r0, 0
stg %r0, Caml_state(backtrace_pos)
ldgr %f15,%r2 /* preserve exn bucket in callee-save reg */
/* arg1: exception bucket, already in r2 */
Loadglobal(%r3, caml_last_return_address) /* arg2: PC of raise */
Loadglobal(%r4, caml_bottom_of_stack) /* arg3: SP of raise */
Loadglobal(%r5, caml_exception_pointer) /* arg4: SP of handler */
/* reserve stack space for C call */
lay %r15, -160(%r15)
lg %r3, Caml_state(last_return_address) /* arg2: PC of raise */
lg %r4, Caml_state(bottom_of_stack) /* arg3: SP of raise */
lg %r5, Caml_state(exception_pointer) /* arg4: SP of handler */
/* reserve stack space for C call */
lay %r15, -160(%r15)
brasl %r14, caml_stash_backtrace@PLT
lay %r15, 160(%r15)
lay %r15, 160(%r15)
lgdr %r2,%f15 /* restore exn bucket */
j .L113 /* raise the exn */
@ -212,6 +205,8 @@ caml_raise_exception:
.globl caml_start_program
.type caml_start_program, @function
caml_start_program:
/* Move Caml_state passed as first argument to r1 */
lgr %r1, %r2
Addrglobal(%r0, caml_program)
/* Code shared between caml_start_program and caml_callback */
@ -230,14 +225,16 @@ caml_start_program:
std %f13, 112(%r15)
std %f14, 120(%r15)
std %f15, 128(%r15)
/* Load Caml_state to r10 register */
lgr %r10, %r1
/* Set up a callback link */
lay %r15, -32(%r15)
Loadglobal(%r1, caml_bottom_of_stack)
lg %r1, Caml_state(bottom_of_stack)
stg %r1, 0(%r15)
Loadglobal(%r1, caml_last_return_address)
lg %r1, Caml_state(last_return_address)
stg %r1, 8(%r15)
Loadglobal(%r1, caml_gc_regs)
lg %r1, Caml_state(gc_regs)
stg %r1, 16(%r15)
/* Build an exception handler to catch exceptions escaping out of OCaml */
brasl %r14, .L103
@ -245,44 +242,43 @@ caml_start_program:
.L103:
lay %r15, -16(%r15)
stg %r14, 0(%r15)
Loadglobal(%r1, caml_exception_pointer)
lg %r1, Caml_state(exception_pointer)
stg %r1, 8(%r15)
lgr %r13, %r15
/* Reload allocation pointers */
Loadglobal(%r11, caml_young_ptr)
Loadglobal(%r10, caml_young_limit)
/* Reload allocation pointer */
lg %r11, Caml_state(young_ptr)
/* Call the OCaml code */
lgr %r1,%r0
basr %r14, %r1
lgr %r1,%r0
basr %r14, %r1
.L105:
/* Pop the trap frame, restoring caml_exception_pointer */
lg %r0, 8(%r15)
Storeglobal(%r0, caml_exception_pointer)
lg %r0, 8(%r15)
stg %r0, Caml_state(exception_pointer)
la %r15, 16(%r15)
/* Pop the callback link, restoring the global variables */
.L106:
lg %r5, 0(%r15)
lg %r6, 8(%r15)
lg %r0, 16(%r15)
Storeglobal(%r5, caml_bottom_of_stack)
Storeglobal(%r6, caml_last_return_address)
Storeglobal(%r0, caml_gc_regs)
stg %r5, Caml_state(bottom_of_stack)
stg %r6, Caml_state(last_return_address)
stg %r0, Caml_state(gc_regs)
la %r15, 32(%r15)
/* Update allocation pointer */
Storeglobal(%r11, caml_young_ptr)
/* Restore registers */
lmg %r6,%r14, 0(%r15)
ld %f8, 72(%r15)
ld %f9, 80(%r15)
ld %f10, 88(%r15)
ld %f11, 96(%r15)
ld %f12, 104(%r15)
ld %f13, 112(%r15)
ld %f14, 120(%r15)
ld %f15, 128(%r15)
stg %r11, Caml_state(young_ptr)
/* Restore registers */
lmg %r6,%r14, 0(%r15)
ld %f8, 72(%r15)
ld %f9, 80(%r15)
ld %f10, 88(%r15)
ld %f11, 96(%r15)
ld %f12, 104(%r15)
ld %f13, 112(%r15)
ld %f14, 120(%r15)
ld %f15, 128(%r15)
/* Return */
lay %r15, 144(%r15)
br %r14
@ -290,42 +286,48 @@ caml_start_program:
/* The trap handler: */
.L104:
/* Update caml_exception_pointer */
Storeglobal(%r13, caml_exception_pointer)
stg %r13, Caml_state(exception_pointer)
/* Encode exception bucket as an exception result and return it */
oill %r2, 2
j .L106
/* Callback from C to OCaml */
.globl caml_callback_exn
.type caml_callback_exn, @function
caml_callback_exn:
.globl caml_callback_asm
.type caml_callback_asm, @function
caml_callback_asm:
/* Initial shuffling of arguments */
lgr %r0, %r2 /* Closure */
lgr %r2, %r3 /* Argument */
lgr %r3, %r0
lg %r0, 0(%r3) /* Code pointer */
/* (r2 = Caml_state, r3 = closure, 0(r4) = arg1) */
lgr %r1, %r2 /* r1 = Caml_state */
lg %r2, 0(%r4) /* r2 = Argument */
/* r3 = Closure */
lg %r0, 0(%r3) /* r0 = Code pointer */
j .L102
.globl caml_callback2_exn
.type caml_callback2_exn, @function
caml_callback2_exn:
lgr %r0, %r2 /* Closure */
lgr %r2, %r3 /* First argument */
lgr %r3, %r4 /* Second argument */
lgr %r4, %r0
Addrglobal(%r0, caml_apply2)
.globl caml_callback2_asm
.type caml_callback2_asm, @function
caml_callback2_asm:
/* Initial shuffling of arguments */
/* (r2 = Caml_state, r3 = closure, 0(r4) = arg1, 8(r4) = arg2) */
lgr %r1, %r2 /* r1 = Caml_state */
lgr %r0, %r3
lg %r2, 0(%r4) /* r2 = First argument */
lg %r3, 8(%r4) /* r3 = Second argument */
lgr %r4, %r0 /* r4 = Closure */
Addrglobal(%r0, caml_apply2) /* r0 = Code pointer */
j .L102
.globl caml_callback3_exn
.type caml_callback3_exn, @function
caml_callback3_exn:
lgr %r0, %r2 /* Closure */
lgr %r2, %r3 /* First argument */
lgr %r3, %r4 /* Second argument */
lgr %r4, %r5 /* Third argument */
lgr %r5, %r0
Addrglobal(%r0, caml_apply3)
.globl caml_callback3_asm
.type caml_callback3_asm, @function
caml_callback3_asm:
/* Initial shuffling of arguments */
/* (r2 = Caml_state, r3 = closure, 0(r4) = arg1, 8(r4) = arg2, 16(r4) = arg3) */
lgr %r1, %r2 /* r1 = Caml_state */
lgr %r5, %r3 /* r5 = Closure */
lg %r2, 0(%r4) /* r2 = First argument */
lg %r3, 8(%r4) /* r3 = Second argument */
lg %r4, 16(%r4) /* r4 = Third argument */
Addrglobal(%r0, caml_apply3) /* r0 = Code pointer */
j .L102
.globl caml_ml_array_bound_error
@ -333,7 +335,7 @@ caml_callback3_exn:
caml_ml_array_bound_error:
/* Save return address before decrementing SP, otherwise
the frame descriptor for the call site is not correct */
Storeglobal(%r15, caml_bottom_of_stack)
stg %r15, Caml_state(bottom_of_stack)
lay %r15, -160(%r15) /* Reserve stack space for C call */
Addrglobal(%r7, caml_array_bound_error)
j .L101