File 0885-hipe-Use-portable-comment-syntax-in-assembler-files.patch of Package erlang

From e2b30c1b04f862e0470fec4c4163a45d42a49d0e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 31 Mar 2020 13:13:00 +0200
Subject: [PATCH] hipe: Use portable comment syntax in assembler files

Ancient versions of GAS (such as the one included in `gcc 3.4.3`)
sometimes confused `#`-comments for pre-processor macros, breaking
the build. Using `//` and `/**/` fixes this.

This may seem a bit silly but modern big-endian machines are very
expensive, so most of our big-endian rigs are ancient, and we have
to adapt if want to test HiPE on them.
---
 erts/emulator/hipe/hipe_amd64_asm.m4 |  2 +-
 erts/emulator/hipe/hipe_amd64_glue.S | 54 ++++++++++++++++++------------------
 erts/emulator/hipe/hipe_arm_asm.m4   |  2 +-
 erts/emulator/hipe/hipe_arm_glue.S   | 10 +++----
 erts/emulator/hipe/hipe_ppc_asm.m4   |  2 +-
 erts/emulator/hipe/hipe_ppc_glue.S   | 40 +++++++++++++-------------
 erts/emulator/hipe/hipe_sparc_asm.m4 |  2 +-
 erts/emulator/hipe/hipe_x86_glue.S   | 46 +++++++++++++++---------------
 8 files changed, 79 insertions(+), 79 deletions(-)

diff --git a/erts/emulator/hipe/hipe_amd64_asm.m4 b/erts/emulator/hipe/hipe_amd64_asm.m4
index 409fd0ef89..c0a289c20b 100644
--- a/erts/emulator/hipe/hipe_amd64_asm.m4
+++ b/erts/emulator/hipe/hipe_amd64_asm.m4
@@ -261,7 +261,7 @@ dnl
 dnl This must be called before SWITCH_ERLANG_TO_C{,QUICK}.
 dnl This must not be called if the C BIF's arity > 6.
 dnl
-define(NBIF_MOVE_REG,`ifelse($1,$2,`# movq	$2, $1',`movq	$2, $1')')dnl
+define(NBIF_MOVE_REG,`ifelse($1,$2,`// movq	$2, $1',`movq	$2, $1')')dnl
 define(NBIF_REG_ARG,`NBIF_MOVE_REG($1,ARG$2)')dnl
 define(NBIF_STK_LOAD,`movq	$2(NSP), $1')dnl
 define(NBIF_STK_ARG,`NBIF_STK_LOAD($1,eval(8*($2-$3)))')dnl
diff --git a/erts/emulator/hipe/hipe_amd64_glue.S b/erts/emulator/hipe/hipe_amd64_glue.S
index f3404888d5..c717ae8192 100644
--- a/erts/emulator/hipe/hipe_amd64_glue.S
+++ b/erts/emulator/hipe/hipe_amd64_glue.S
@@ -76,7 +76,7 @@ CSYM(x86_call_to_native):
  * This is where native code returns to emulated code.
  */
 ASYM(nbif_return):
-	movq	%rax, P_ARG0(P)			# save retval
+	movq	%rax, P_ARG0(P)			/* save retval */
 	movl	$HIPE_MODE_SWITCH_RES_RETURN, %eax
 /* FALLTHROUGH to .flush_exit
  *
@@ -96,12 +96,12 @@ ASYM(nbif_return):
 	SWITCH_ERLANG_TO_C_QUICK
 	SET_GC_SAFE
 	/* restore C callee-save registers, drop frame, return */
-	movq	(%rsp), %rbp	# kills P
+	movq	(%rsp), %rbp	/* kills P */
 	movq	8(%rsp), %rbx
 	movq	16(%rsp), %r12
 	movq	24(%rsp), %r13
 	movq	32(%rsp), %r14
-	movq	40(%rsp), %r15	# kills HP
+	movq	40(%rsp), %r15	/* kills HP */
 	addq	$(7*8), %rsp
 	ret
 
@@ -260,10 +260,10 @@ ASYM(nbif_suspend_msg):
 ASYM(nbif_suspend_msg_timeout):
 	movq	P_FLAGS(P), %rax
 	/* this relies on F_TIMO (1<<2) fitting in a byte */
-	testb	$F_TIMO, %al			# F_TIMO set?
-	jz	.no_timeout			# if not set, suspend
+	testb	$F_TIMO, %al			/* F_TIMO set? */
+	jz	.no_timeout			/* if not set, suspend */
 	/* timeout has occurred */
-	xorl	%eax, %eax			# return 0 to signal timeout
+	xorl	%eax, %eax			/* return 0 to signal timeout */
 	NSP_RET0
 .no_timeout:
 	movl	$HIPE_MODE_SWITCH_RES_WAIT_TIMEOUT, %eax
@@ -308,7 +308,7 @@ CSYM(x86_tailcall_to_native):
 CSYM(x86_throw_to_native):
 	ENTER_FROM_C
 	/* invoke the handler */
-	jmp	*P_NCALLEE(P)		# set by hipe_find_handler()
+	jmp	*P_NCALLEE(P)		/* set by hipe_find_handler() */
 
 /*
  * This is the default exception handler for native code.
@@ -346,15 +346,15 @@ nbif_4_gc_after_bif:
 	/*FALLTHROUGH*/
 	.align	4
 .gc_after_bif:
-	movl	%edx, P_NARITY(P)	# Note: narity is a 32-bit field
+	movl	%edx, P_NARITY(P)	/* Note: narity is a 32-bit field */
 	subq	$(16-8), %rsp
 	movq	P, %rdi
 	movq	%rax, %rsi
-	xorl	%edx, %edx		# Pass NULL in regs
-	xorl	%ecx, %ecx		# Pass 0 in arity
+	xorl	%edx, %edx		/* Pass NULL in regs */
+	xorl	%ecx, %ecx		/* Pass 0 in arity */
 	call	CSYM(erts_gc_after_bif_call)
 	addq	$(16-8), %rsp
-	movl	$0, P_NARITY(P)		# Note: narity is a 32-bit field
+	movl	$0, P_NARITY(P)		/* Note: narity is a 32-bit field */
 	ret
 
 /*
@@ -396,15 +396,15 @@ nbif_4_simple_exception:
 	 * The stack/heap registers were just read from P.
 	 * - %eax should contain the current call's arity
 	 */
-	movl	%eax, P_NARITY(P)	# Note: narity is a 32-bit field
+	movl	%eax, P_NARITY(P)	/* Note: narity is a 32-bit field */
 	/* find and prepare to invoke the handler */
-	SWITCH_ERLANG_TO_C_QUICK	# The cached state is clean and need not be saved.
+	SWITCH_ERLANG_TO_C_QUICK	/* The cached state is clean and need not be saved. */
 	SET_GC_SAFE
 	movq	P, %rdi
-	call	CSYM(hipe_handle_exception)	# Note: hipe_handle_exception() conses
-	SWITCH_C_TO_ERLANG		# %rsp updated by hipe_find_handler()
+	call	CSYM(hipe_handle_exception)	/* Note: hipe_handle_exception() conses */
+	SWITCH_C_TO_ERLANG		/* %rsp updated by hipe_find_handler() */
 	/* now invoke the handler */
-	jmp	*P_NCALLEE(P)		# set by hipe_find_handler()
+	jmp	*P_NCALLEE(P)		/* set by hipe_find_handler() */
 
 	/*
 	 * A BIF failed with freason TRAP:
@@ -412,7 +412,7 @@ nbif_4_simple_exception:
 	 * - the native heap/stack/reds registers are saved in P
 	 */
 .handle_trap:
-	movl	%eax, P_NARITY(P)	# Note: narity is a 32-bit field
+	movl	%eax, P_NARITY(P)	/* Note: narity is a 32-bit field */
 	movl	$HIPE_MODE_SWITCH_RES_TRAP, %eax
 	jmp	.nosave_exit
 
@@ -422,17 +422,17 @@ nbif_4_simple_exception:
  */
 	GLOBAL(ASYM(nbif_stack_trap_ra))
 	.align	4
-ASYM(nbif_stack_trap_ra):			# a return address, not a function
-	# This only handles a single return value.
-	# If we have more, we need to save them in the PCB.
-	movq	%rax, TEMP_RV		# save retval
+ASYM(nbif_stack_trap_ra):			/* a return address, not a function */
+	/* This only handles a single return value. */
+	/* If we have more, we need to save them in the PCB. */
+	movq	%rax, TEMP_RV		/* save retval */
 	SWITCH_ERLANG_TO_C_QUICK
 	movq	P, %rdi
-	call	CSYM(hipe_handle_stack_trap)	# must not cons; preserves TEMP_RV
-	movq	%rax, %rdx		# original RA
+	call	CSYM(hipe_handle_stack_trap)	/* must not cons; preserves TEMP_RV */
+	movq	%rax, %rdx		/* original RA */
 	SWITCH_C_TO_ERLANG_QUICK
-	movq	TEMP_RV, %rax		# restore retval
-	jmp	*%rdx			# resume at original RA
+	movq	TEMP_RV, %rax		/* restore retval */
+	jmp	*%rdx			/* resume at original RA */
 
 /*
  * nbif_inc_stack_0
@@ -443,8 +443,8 @@ ASYM(nbif_inc_stack_0):
 	SWITCH_ERLANG_TO_C_QUICK
 	STORE_ARG_REGS
 	movq	P, %rdi
-	# hipe_inc_nstack reads and writes NSP and NSP_LIMIT,
-	# but does not access HP or FCALLS (or the non-amd64 NRA).
+	/* hipe_inc_nstack reads and writes NSP and NSP_LIMIT, */
+	/* but does not access HP or FCALLS (or the non-amd64 NRA). */
 	call	CSYM(hipe_inc_nstack)
 	LOAD_ARG_REGS
 	SWITCH_C_TO_ERLANG_QUICK
diff --git a/erts/emulator/hipe/hipe_arm_asm.m4 b/erts/emulator/hipe/hipe_arm_asm.m4
index 68a6faa70b..fe78c2b777 100644
--- a/erts/emulator/hipe/hipe_arm_asm.m4
+++ b/erts/emulator/hipe/hipe_arm_asm.m4
@@ -175,7 +175,7 @@ dnl It will be a memory load via NSP when ARGNO >= NR_ARG_REGS.
 dnl It will be a register move when 0 <= ARGNO < NR_ARG_REGS; if
 dnl the source and destination are the same, the move is suppressed.
 dnl
-define(NBIF_MOVE_REG,`ifelse($1,$2,`# mov	$1, $2',`mov	$1, $2')')dnl
+define(NBIF_MOVE_REG,`ifelse($1,$2,`// mov	$1, $2',`mov	$1, $2')')dnl
 define(NBIF_REG_ARG,`NBIF_MOVE_REG($1,ARG$2)')dnl
 define(NBIF_STK_LOAD,`ldr	$1, [NSP, #$2]')dnl
 define(NBIF_STK_ARG,`NBIF_STK_LOAD($1,eval(4*(($2-$3)-1)))')dnl
diff --git a/erts/emulator/hipe/hipe_arm_glue.S b/erts/emulator/hipe/hipe_arm_glue.S
index 5b7f8ad52d..5071b10287 100644
--- a/erts/emulator/hipe/hipe_arm_glue.S
+++ b/erts/emulator/hipe/hipe_arm_glue.S
@@ -436,8 +436,8 @@ nbif_4_simple_exception:
 	.global	nbif_stack_trap_ra
 	.type	nbif_stack_trap_ra, %function
 nbif_stack_trap_ra:		/* a return address, not a function */
-	# This only handles a single return value.
-	# If we have more, we need to save them in the PCB.
+	/* This only handles a single return value. */
+	/* If we have more, we need to save them in the PCB. */
 	mov	TEMP_ARG0, r0		/* save retval */
 	str	NSP, [P, #P_NSP]
 	mov	r0, P
@@ -457,12 +457,12 @@ hipe_arm_inc_stack:
 	mov	TEMP_ARG0, lr
 	str	NSP, [P, #P_NSP]
 	mov	r0, P
-	# hipe_inc_nstack reads and writes NSP and NSP_LIMIT,
-	# but does not access LR/RA, HP, or FCALLS.
+	/* hipe_inc_nstack reads and writes NSP and NSP_LIMIT, */
+	/* but does not access LR/RA, HP, or FCALLS. */
 	bl	hipe_inc_nstack
 	ldr	NSP, [P, #P_NSP]
 	LOAD_ARG_REGS
-	# this relies on LOAD_ARG_REGS not clobbering TEMP_ARG0
+	/* this relies on LOAD_ARG_REGS not clobbering TEMP_ARG0 */
 	mov	pc, TEMP_ARG0
 
 #if defined(__linux__) && defined(__ELF__)
diff --git a/erts/emulator/hipe/hipe_ppc_asm.m4 b/erts/emulator/hipe/hipe_ppc_asm.m4
index be25d65725..f4c90bcbab 100644
--- a/erts/emulator/hipe/hipe_ppc_asm.m4
+++ b/erts/emulator/hipe/hipe_ppc_asm.m4
@@ -270,7 +270,7 @@ dnl It will be a memory load via NSP when ARGNO >= NR_ARG_REGS.
 dnl It will be a register move when 0 <= ARGNO < NR_ARG_REGS; if
 dnl the source and destination are the same, the move is suppressed.
 dnl
-define(NBIF_MOVE_REG,`ifelse($1,$2,`# mr $1, $2',`mr	$1, $2')')dnl
+define(NBIF_MOVE_REG,`ifelse($1,$2,`// mr $1, $2',`mr	$1, $2')')dnl
 define(NBIF_REG_ARG,`NBIF_MOVE_REG($1,ARG$2)')dnl
 define(NBIF_STK_LOAD,`LOAD	$1, $2(NSP)')dnl
 define(NBIF_STK_ARG,`NBIF_STK_LOAD($1,eval(WSIZE*(($2-$3)-1)))')dnl
diff --git a/erts/emulator/hipe/hipe_ppc_glue.S b/erts/emulator/hipe/hipe_ppc_glue.S
index 44351dc06c..15e734c414 100644
--- a/erts/emulator/hipe/hipe_ppc_glue.S
+++ b/erts/emulator/hipe/hipe_ppc_glue.S
@@ -39,14 +39,14 @@
  * Usage: mflr r0 SEMI bl .enter
  */
 .enter:
-	# Our PPC64 ELF ABI frame must include:
-	# - 48 (6*8) bytes for AIX-like linkage area
-	# - 64 (8*8) bytes for AIX-like parameter area for
-	#   recursive C calls with up to 8 parameter words
-	# - padding to make the frame a multiple of 16 bytes
-	# - 144 (18*8) bytes for saving r14-r31
-	# The final size is 256 bytes.
-	# stdu is required for atomic alloc+init
+	/* Our PPC64 ELF ABI frame must include: */
+	/* - 48 (6*8) bytes for AIX-like linkage area */
+	/* - 64 (8*8) bytes for AIX-like parameter area for */
+	/*   recursive C calls with up to 8 parameter words */
+	/* - padding to make the frame a multiple of 16 bytes */
+	/* - 144 (18*8) bytes for saving r14-r31 */
+	/* The final size is 256 bytes. */
+	/* stdu is required for atomic alloc+init */
 	stdu	r1,-256(r1)	/* 0(r1) contains r1+256 */
 	std	r14, 112(r1)
 	std	r15, 120(r1)
@@ -122,14 +122,14 @@
  * Usage: mflr r0 SEMI bl .enter
  */
 .enter:
-	# A unified Linux/OSX C frame must include:
-	# - 24 bytes for AIX/OSX-like linkage area
-	# - 28 bytes for AIX/OSX-like parameter area for
-	#   recursive C calls with up to 7 parameter words
-	# - 76 bytes for saving r14-r31 and LR
-	# - padding to make it a multiple of 16 bytes
-	# The final size is 128 bytes.
-	# stwu is required for atomic alloc+init
+	/* A unified Linux/OSX C frame must include: */
+	/* - 24 bytes for AIX/OSX-like linkage area */
+	/* - 28 bytes for AIX/OSX-like parameter area for */
+	/*   recursive C calls with up to 7 parameter words */
+	/* - 76 bytes for saving r14-r31 and LR */
+	/* - padding to make it a multiple of 16 bytes */
+	/* The final size is 128 bytes. */
+	/* stwu is required for atomic alloc+init */
 	stwu	r1,-128(r1)	/* 0(r1) contains r1+128 */
 	stw	r14, 52(r1)
 	stw	r15, 56(r1)
@@ -577,8 +577,8 @@ CSYM(nbif_4_simple_exception):
  */
 	GLOBAL(ASYM(nbif_stack_trap_ra))
 ASYM(nbif_stack_trap_ra):		/* a return address, not a function */
-	# This only handles a single return value.
-	# If we have more, we need to save them in the PCB.
+	/* This only handles a single return value. */
+	/* If we have more, we need to save them in the PCB. */
 	mr	TEMP_ARG0, r3		/* save retval */
 	STORE	NSP, P_NSP(P)
 	mr	r3, P
@@ -597,8 +597,8 @@ ASYM(hipe_ppc_inc_stack):
 	mflr	TEMP_ARG0
 	STORE	NSP, P_NSP(P)
 	mr	r3, P
-	# hipe_inc_nstack reads and writes NSP and NSP_LIMIT,
-	# but does not access LR/RA, HP, or FCALLS.
+	/* hipe_inc_nstack reads and writes NSP and NSP_LIMIT, */
+	/* but does not access LR/RA, HP, or FCALLS. */
 	bl	CSYM(hipe_inc_nstack)
 	mtlr	TEMP_ARG0
 	LOAD	NSP, P_NSP(P)
diff --git a/erts/emulator/hipe/hipe_sparc_asm.m4 b/erts/emulator/hipe/hipe_sparc_asm.m4
index 8a9a516eab..2fcdf997b3 100644
--- a/erts/emulator/hipe/hipe_sparc_asm.m4
+++ b/erts/emulator/hipe/hipe_sparc_asm.m4
@@ -166,7 +166,7 @@ dnl It will be a memory load via NSP when ARGNO >= NR_ARG_REGS.
 dnl It will be a register move when 0 <= ARGNO < NR_ARG_REGS; if
 dnl the source and destination are the same, the move is suppressed.
 dnl
-define(NBIF_MOVE_REG,`ifelse($1,$2,`! mov	$2, $1',`mov	$2, $1')')dnl
+define(NBIF_MOVE_REG,`ifelse($1,$2,`// mov	$2, $1',`mov	$2, $1')')dnl
 define(NBIF_REG_ARG,`NBIF_MOVE_REG($1,ARG$2)')dnl
 define(NBIF_STK_LOAD,`ld	[NSP+$2], $1')dnl
 define(NBIF_STK_ARG,`NBIF_STK_LOAD($1,eval(4*(($2-$3)-1)))')dnl
diff --git a/erts/emulator/hipe/hipe_x86_glue.S b/erts/emulator/hipe/hipe_x86_glue.S
index 8d6e377730..51bbb8098f 100644
--- a/erts/emulator/hipe/hipe_x86_glue.S
+++ b/erts/emulator/hipe/hipe_x86_glue.S
@@ -73,7 +73,7 @@ CSYM(x86_call_to_native):
  * This is where native code returns to emulated code.
  */
 ASYM(nbif_return):
-	movl	%eax, P_ARG0(P)			# save retval
+	movl	%eax, P_ARG0(P)			/* save retval */
 	movl	$HIPE_MODE_SWITCH_RES_RETURN, %eax
 /* FALLTHROUGH to .flush_exit
  *
@@ -93,9 +93,9 @@ ASYM(nbif_return):
 	SWITCH_ERLANG_TO_C_QUICK
 	/* restore C callee-save registers, drop frame, return */
 	movl	28(%esp), %edi
-	movl	32(%esp), %esi	# kills HP, if HP_IN_ESI is true
+	movl	32(%esp), %esi	/* kills HP, if HP_IN_ESI is true */
 	movl	36(%esp), %ebx
-	movl	40(%esp), %ebp	# kills P
+	movl	40(%esp), %ebp	/* kills P */
 	addl	$44, %esp
 	ret
 
@@ -237,10 +237,10 @@ ASYM(nbif_suspend_msg):
 ASYM(nbif_suspend_msg_timeout):
 	movl	P_FLAGS(P), %eax
 	/* this relies on F_TIMO (1<<2) fitting in a byte */
-	testb	$F_TIMO, %al			# F_TIMO set?
-	jz	.no_timeout			# if not set, suspend
+	testb	$F_TIMO, %al			/* F_TIMO set? */
+	jz	.no_timeout			/* if not set, suspend */
 	/* timeout has occurred */
-	xorl	%eax, %eax			# return 0 to signal timeout
+	xorl	%eax, %eax			/* return 0 to signal timeout */
 	NSP_RET0
 .no_timeout:
 	movl	$HIPE_MODE_SWITCH_RES_WAIT_TIMEOUT, %eax
@@ -285,7 +285,7 @@ CSYM(x86_tailcall_to_native):
 CSYM(x86_throw_to_native):
 	ENTER_FROM_C
 	/* invoke the handler */
-	jmp	*P_NCALLEE(P)		# set by hipe_find_handler()
+	jmp	*P_NCALLEE(P)		/* set by hipe_find_handler() */
 
 /*
  * This is the default exception handler for native code.
@@ -327,8 +327,8 @@ nbif_4_gc_after_bif:
 	subl	$(32-4), %esp
 	movl	P, (%esp)
 	movl	%eax, 4(%esp)
-	movl	$0, 8(%esp)		# Pass NULL in regs
-	movl	$0, 12(%esp)		# Pass 0 in arity
+	movl	$0, 8(%esp)		/* Pass NULL in regs */
+	movl	$0, 12(%esp)		/* Pass 0 in arity */
 	call	CSYM(erts_gc_after_bif_call)
 	addl	$(32-4), %esp
 	movl	$0, P_NARITY(P)
@@ -375,12 +375,12 @@ nbif_4_simple_exception:
 	 */
 	movl	%eax, P_NARITY(P)
 	/* find and prepare to invoke the handler */
-	SWITCH_ERLANG_TO_C_QUICK	# The cached state is clean and need not be saved.
+	SWITCH_ERLANG_TO_C_QUICK	/* The cached state is clean and need not be saved. */
 	movl	P, (%esp)
-	call	CSYM(hipe_handle_exception)	# Note: hipe_handle_exception() conses
-	SWITCH_C_TO_ERLANG		# %esp updated by hipe_find_handler()
+	call	CSYM(hipe_handle_exception)	/* Note: hipe_handle_exception() conses */
+	SWITCH_C_TO_ERLANG		/* %esp updated by hipe_find_handler() */
 	/* now invoke the handler */
-	jmp	*P_NCALLEE(P)		# set by hipe_find_handler()
+	jmp	*P_NCALLEE(P)		/* set by hipe_find_handler() */
 
 	/*
 	 * A BIF failed with freason TRAP:
@@ -398,17 +398,17 @@ nbif_4_simple_exception:
  */
 	GLOBAL(ASYM(nbif_stack_trap_ra))
 	.align	4
-ASYM(nbif_stack_trap_ra):		# a return address, not a function
-	# This only handles a single return value.
-	# If we have more, we need to save them in the PCB.
-	movl	%eax, TEMP_RV		# save retval
+ASYM(nbif_stack_trap_ra):		/* a return address, not a function */
+	/* This only handles a single return value. */
+	/* If we have more, we need to save them in the PCB. */
+	movl	%eax, TEMP_RV		/* save retval */
 	SWITCH_ERLANG_TO_C_QUICK
 	movl	P, (%esp)
-	call	CSYM(hipe_handle_stack_trap)	# must not cons; preserves TEMP_RV
-	movl	%eax, %edx		# original RA
+	call	CSYM(hipe_handle_stack_trap)	/* must not cons; preserves TEMP_RV */
+	movl	%eax, %edx		/* original RA */
 	SWITCH_C_TO_ERLANG_QUICK
-	movl	TEMP_RV, %eax		# restore retval
-	jmp	*%edx			# resume at original RA
+	movl	TEMP_RV, %eax		/* restore retval */
+	jmp	*%edx			/* resume at original RA */
 
 /*
  * nbif_inc_stack_0
@@ -419,8 +419,8 @@ ASYM(nbif_inc_stack_0):
 	SWITCH_ERLANG_TO_C_QUICK
 	STORE_CALLER_SAVE
 	movl	P, (%esp)
-	# hipe_inc_nstack reads and writes NSP and NSP_LIMIT,
-	# but does not access HP or FCALLS (or the non-x86 NRA).
+	/* hipe_inc_nstack reads and writes NSP and NSP_LIMIT, */
+	/* but does not access HP or FCALLS (or the non-x86 NRA). */
 	call	CSYM(hipe_inc_nstack)
 	LOAD_CALLER_SAVE
 	SWITCH_C_TO_ERLANG_QUICK
-- 
2.16.4

openSUSE Build Service is sponsored by