Skip to content

Commit

Permalink
Put G into FUNCTION, END_FUNCTION and OBJECT
Browse files Browse the repository at this point in the history
Reduce the unnecessary differences between amd64.S and arm64.S runtime
files.
  • Loading branch information
tmcgilchrist committed Nov 26, 2024
1 parent 2790261 commit bb09602
Showing 1 changed file with 64 additions and 64 deletions.
128 changes: 64 additions & 64 deletions runtime/amd64.S
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,9 @@
#define EIGHT_ALIGN 3
#define SIXTEEN_ALIGN 4
#define FUNCTION(name) \
.globl name; \
.globl G(name); \
.align FUNCTION_ALIGN; \
name:
G(name):

#elif defined(SYS_mingw64) || defined(SYS_cygwin)

Expand All @@ -46,10 +46,10 @@
#define EIGHT_ALIGN 8
#define SIXTEEN_ALIGN 16
#define FUNCTION(name) \
TEXT_SECTION(name); \
.globl name; \
TEXT_SECTION(G(name)); \
.globl G(name); \
.align FUNCTION_ALIGN; \
name:
G(name):

#else /* Unix-like operating systems using ELF binaries */

Expand All @@ -66,28 +66,28 @@
#define EIGHT_ALIGN 8
#define SIXTEEN_ALIGN 16
#define FUNCTION(name) \
TEXT_SECTION(name); \
.globl name; \
.type name,@function; \
TEXT_SECTION(G(name)); \
.globl G(name); \
.type G(name),@function; \
.align FUNCTION_ALIGN; \
name:
G(name):

#endif

#define OBJECT(name) \
.globl name; \
.globl G(name); \
.align EIGHT_ALIGN; \
name:
G(name):

#if defined(SYS_linux) || defined(SYS_gnu)
#define ENDFUNCTION(name) \
.size name, . - name
#define ENDOBJECT(name) \
.type name, @object; \
.size name, . - name;
#define END_FUNCTION(name) \
.size G(name), . - G(name)
#define END_OBJECT(name) \
.type G(name), @object; \
.size G(name), . - G(name)
#else
#define ENDFUNCTION(name)
#define ENDOBJECT(name)
#define END_FUNCTION(name)
#define END_OBJECT(name)
#endif

#include "../runtime/caml/asm.h"
Expand Down Expand Up @@ -574,7 +574,7 @@ G(caml_system__code_begin):
#define TSAN_RESTORE_CALLER_REGS
#endif

FUNCTION(G(caml_call_realloc_stack))
FUNCTION(caml_call_realloc_stack)
CFI_STARTPROC
CFI_SIGNAL_FRAME
ENTER_FUNCTION
Expand All @@ -593,9 +593,9 @@ CFI_STARTPROC
add $16, %rsp /* pop argument, retaddr */
jmp GCALL(caml_raise_exn)
CFI_ENDPROC
ENDFUNCTION(G(caml_call_realloc_stack))
END_FUNCTION(caml_call_realloc_stack)

FUNCTION(G(caml_call_gc))
FUNCTION(caml_call_gc)
CFI_STARTPROC
CFI_SIGNAL_FRAME
ENTER_FUNCTION
Expand All @@ -612,9 +612,9 @@ LBL(caml_call_gc):
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_call_gc))
END_FUNCTION(caml_call_gc)

FUNCTION(G(caml_alloc1))
FUNCTION(caml_alloc1)
CFI_STARTPROC
ENTER_FUNCTION
subq $16, %r15
Expand All @@ -623,9 +623,9 @@ CFI_STARTPROC
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_alloc1))
END_FUNCTION(caml_alloc1)

FUNCTION(G(caml_alloc2))
FUNCTION(caml_alloc2)
CFI_STARTPROC
ENTER_FUNCTION
subq $24, %r15
Expand All @@ -634,9 +634,9 @@ CFI_STARTPROC
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_alloc2))
END_FUNCTION(caml_alloc2)

FUNCTION(G(caml_alloc3))
FUNCTION(caml_alloc3)
CFI_STARTPROC
ENTER_FUNCTION
subq $32, %r15
Expand All @@ -645,17 +645,17 @@ CFI_STARTPROC
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_alloc3))
END_FUNCTION(caml_alloc3)

FUNCTION(G(caml_allocN))
FUNCTION(caml_allocN)
CFI_STARTPROC
ENTER_FUNCTION
cmpq Caml_state(young_limit), %r15
jb LBL(caml_call_gc)
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_allocN))
END_FUNCTION(caml_allocN)

/******************************************************************************/
/* Call a C function from OCaml */
Expand Down Expand Up @@ -687,7 +687,7 @@ ENDFUNCTION(G(caml_allocN))
1: movq $-1, Caml_state(young_limit); \
ret

FUNCTION(G(caml_c_call))
FUNCTION(caml_c_call)
CFI_STARTPROC
CFI_SIGNAL_FRAME
ENTER_FUNCTION
Expand Down Expand Up @@ -722,9 +722,9 @@ LBL(caml_c_call):
/* Return to OCaml caller */
RET_FROM_C_CALL
CFI_ENDPROC
ENDFUNCTION(G(caml_c_call))
END_FUNCTION(caml_c_call)

FUNCTION(G(caml_c_call_stack_args))
FUNCTION(caml_c_call_stack_args)
CFI_STARTPROC
CFI_SIGNAL_FRAME
ENTER_FUNCTION
Expand Down Expand Up @@ -770,13 +770,13 @@ LBL(106):
LEAVE_FUNCTION
RET_FROM_C_CALL
CFI_ENDPROC
ENDFUNCTION(G(caml_c_call_stack_args))
END_FUNCTION(caml_c_call_stack_args)

/******************************************************************************/
/* Start the OCaml program */
/******************************************************************************/

FUNCTION(G(caml_start_program))
FUNCTION(caml_start_program)
CFI_STARTPROC
CFI_SIGNAL_FRAME
/* Save callee-save registers */
Expand Down Expand Up @@ -884,15 +884,15 @@ LBL(109):
movq %rsp, %r10
jmp 1b
CFI_ENDPROC
ENDFUNCTION(G(caml_start_program))
END_FUNCTION(caml_start_program)

/******************************************************************************/
/* Exceptions */
/******************************************************************************/

/* Raise an exception from OCaml */

FUNCTION(G(caml_raise_exn))
FUNCTION(caml_raise_exn)
CFI_STARTPROC
ENTER_FUNCTION
LBL(caml_raise_exn):
Expand All @@ -915,15 +915,15 @@ LBL(117):
RESTORE_EXN_HANDLER_OCAML
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_raise_exn))
END_FUNCTION(caml_raise_exn)

#if defined(WITH_THREAD_SANITIZER)
/* When TSan support is enabled, this routine should be called just before
raising an exception. It calls __tsan_func_exit for every OCaml frame about
to be exited due to the exception.
Takes no arguments, clobbers C_ARG_1, C_ARG_2, C_ARG_3 and potentially all
caller-saved registers of the C calling convention. */
FUNCTION(G(caml_tsan_exit_on_raise_asm))
FUNCTION(caml_tsan_exit_on_raise_asm)
CFI_STARTPROC
ENTER_FUNCTION
movq STACK_RETADDR(%rsp), C_ARG_1 /* arg 1: pc of raise */
Expand All @@ -935,22 +935,22 @@ CFI_STARTPROC
LEAVE_FUNCTION
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_tsan_exit_on_raise_asm))
END_FUNCTION(caml_tsan_exit_on_raise_asm)
#endif

FUNCTION(G(caml_reraise_exn))
FUNCTION(caml_reraise_exn)
CFI_STARTPROC
ENTER_FUNCTION
testq $1, Caml_state(backtrace_active)
jne LBL(117)
RESTORE_EXN_HANDLER_OCAML
ret
CFI_ENDPROC
ENDFUNCTION(G(caml_reraise_exn))
END_FUNCTION(caml_reraise_exn)

/* Raise an exception from C */

FUNCTION(G(caml_raise_exception))
FUNCTION(caml_raise_exception)
CFI_STARTPROC
ENTER_FUNCTION
movq C_ARG_1, %r14 /* Caml_state */
Expand All @@ -974,13 +974,13 @@ CFI_STARTPROC
#endif
jmp LBL(caml_raise_exn)
CFI_ENDPROC
ENDFUNCTION(G(caml_raise_exception))
END_FUNCTION(caml_raise_exception)

/******************************************************************************/
/* Callback from C to OCaml */
/******************************************************************************/

FUNCTION(G(caml_callback_asm))
FUNCTION(caml_callback_asm)
CFI_STARTPROC
#if defined(WITH_THREAD_SANITIZER)
/* Save non-callee-saved registers C_ARG_1, C_ARG_2, C_ARG_3 before C call
Expand All @@ -1005,9 +1005,9 @@ CFI_STARTPROC
movq $0, %rsi /* dummy */
jmp LBL(caml_start_program)
CFI_ENDPROC
ENDFUNCTION(G(caml_callback_asm))
END_FUNCTION(caml_callback_asm)

FUNCTION(G(caml_callback2_asm))
FUNCTION(caml_callback2_asm)
CFI_STARTPROC
#if defined(WITH_THREAD_SANITIZER)
/* Save non-callee-saved registers C_ARG_1, C_ARG_2, C_ARG_3 before C call
Expand All @@ -1032,9 +1032,9 @@ CFI_STARTPROC
movq $0, %rsi /* dummy */
jmp LBL(caml_start_program)
CFI_ENDPROC
ENDFUNCTION(G(caml_callback2_asm))
END_FUNCTION(caml_callback2_asm)

FUNCTION(G(caml_callback3_asm))
FUNCTION(caml_callback3_asm)
CFI_STARTPROC
#if defined(WITH_THREAD_SANITIZER)
/* Save non-callee-saved registers C_ARG_1, C_ARG_2, C_ARG_3 before C call
Expand All @@ -1059,7 +1059,7 @@ CFI_STARTPROC
LEA_VAR(caml_apply3, %r12) /* code pointer */
jmp LBL(caml_start_program)
CFI_ENDPROC
ENDFUNCTION(G(caml_callback3_asm))
END_FUNCTION(caml_callback3_asm)

/******************************************************************************/
/* Fibers */
Expand All @@ -1071,7 +1071,7 @@ ENDFUNCTION(G(caml_callback3_asm))
*/
/******************************************************************************/

FUNCTION(G(caml_perform))
FUNCTION(caml_perform)
CFI_STARTPROC
/* %rax: effect to perform
%rbx: freshly allocated continuation */
Expand Down Expand Up @@ -1150,9 +1150,9 @@ LBL(112):
LEA_VAR(caml_raise_unhandled_effect, %rax)
jmp LBL(caml_c_call)
CFI_ENDPROC
ENDFUNCTION(G(caml_perform))
END_FUNCTION(caml_perform)

FUNCTION(G(caml_reperform))
FUNCTION(caml_reperform)
CFI_STARTPROC
/* %rax: effect to reperform
%rbx: continuation
Expand All @@ -1166,9 +1166,9 @@ CFI_STARTPROC
UPDATE_BASE_POINTER(%r10)
jmp LBL(do_perform)
CFI_ENDPROC
ENDFUNCTION(G(caml_reperform))
END_FUNCTION(caml_reperform)

FUNCTION(G(caml_resume))
FUNCTION(caml_resume)
CFI_STARTPROC
/* %rax -> fiber, %rbx -> fun, %rdi -> arg, %rsi -> last_fiber */
leaq -1(%rax), %r10 /* %r10 (new stack) = Ptr_val(%rax) */
Expand Down Expand Up @@ -1215,11 +1215,11 @@ CFI_STARTPROC
LEA_VAR(caml_raise_continuation_already_resumed, %rax)
jmp LBL(caml_c_call)
CFI_ENDPROC
ENDFUNCTION(G(caml_resume))
END_FUNCTION(caml_resume)

/* Run a function on a new stack,
then invoke either the value or exception handler */
FUNCTION(G(caml_runstack))
FUNCTION(caml_runstack)
CFI_STARTPROC
CFI_SIGNAL_FRAME
ENTER_FUNCTION
Expand Down Expand Up @@ -1299,19 +1299,19 @@ LBL(fiber_exn_handler):
movq Handler_exception(%r11), %rbx
jmp 1b
CFI_ENDPROC
ENDFUNCTION(G(caml_runstack))
END_FUNCTION(caml_runstack)

FUNCTION(G(caml_ml_array_bound_error))
FUNCTION(caml_ml_array_bound_error)
CFI_STARTPROC
ENTER_FUNCTION
/* No registers require saving before C call to TSan */
TSAN_ENTER_FUNCTION(0)
LEA_VAR(caml_array_bound_error_asm, %rax)
jmp LBL(caml_c_call)
CFI_ENDPROC
ENDFUNCTION(G(caml_ml_array_bound_error))
END_FUNCTION(caml_ml_array_bound_error)

FUNCTION(G(caml_assert_stack_invariants))
FUNCTION(caml_assert_stack_invariants)
CFI_STARTPROC
movq Caml_state(current_stack), %r11
movq %rsp, %r10
Expand All @@ -1322,14 +1322,14 @@ CFI_STARTPROC
int3
1: ret
CFI_ENDPROC
ENDFUNCTION(G(caml_assert_stack_invariants))
END_FUNCTION(caml_assert_stack_invariants)

TEXT_SECTION(caml_system__code_end)
.globl G(caml_system__code_end)
G(caml_system__code_end):

.data
OBJECT(G(caml_system.frametable))
OBJECT(caml_system.frametable)
.quad 2 /* two descriptors */
.quad LBL(108) /* return address into callback */
.value -1 /* negative frame size => use callback link */
Expand All @@ -1338,7 +1338,7 @@ OBJECT(G(caml_system.frametable))
.quad LBL(frame_runstack) /* return address into fiber_val_handler */
.value -1 /* negative frame size => use callback link */
.value 0 /* no roots here */
ENDOBJECT(G(caml_system.frametable))
END_OBJECT(caml_system.frametable)

#if defined(SYS_macosx)
.literal16
Expand Down

0 comments on commit bb09602

Please sign in to comment.