From 5961d13d279329211e2a2d2c294395d17e4c7fcb Mon Sep 17 00:00:00 2001
From: John David Anglin <danglin@gcc.gnu.org>
Date: Sun, 4 Sep 2016 17:39:05 +0000
Subject: [PATCH] ffi.c (ffi_struct_type): Put type declaration on separate
 line.

	* src/pa/ffi.c (ffi_struct_type): Put type declaration on separate line.
	(ffi_prep_args_pa32): Likewise.
	(ffi_size_stack_pa32): Likewise.
	(ffi_prep_cif_machdep): Likewise.
	(ffi_call): Likewise.  Rename to ffi_call_int.  Add closure argument
	and update call to ffi_call_pa32.
	(ffi_call, ffi_call_go, ffi_prep_go_closure): New.
	(ffi_closure_inner_pa32): Update to handle go closures.
	* src/pa/ffitarget.h (FFI_GO_CLOSURES): Define.
	* src/pa/hpux32.S (ffi_call_pa32): Pass go closure argument in static
	chain register (%ret1).
	(ffi_closure_pa32): Set closure type argument to zero.
	(ffi_go_closure_pa32): New function.  Add unwind data for it.
	* src/pa/linux.S: Likewise.  Use cfi directives for unwind data.
	* testsuite/libffi.go/static-chain.h (STATIC_CHAIN_REG): Define for
	hppa.

From-SVN: r239978
---
 libffi/ChangeLog                          |  19 +++
 libffi/src/pa/ffi.c                       |  83 ++++++++++---
 libffi/src/pa/ffitarget.h                 |   4 +-
 libffi/src/pa/hpux32.S                    |  70 ++++++++++-
 libffi/src/pa/linux.S                     | 135 ++++++++++------------
 libffi/testsuite/libffi.go/static-chain.h |   6 +
 6 files changed, 224 insertions(+), 93 deletions(-)

diff --git a/libffi/ChangeLog b/libffi/ChangeLog
index 8245f5b39f8a..4b16fb0b31fd 100644
--- a/libffi/ChangeLog
+++ b/libffi/ChangeLog
@@ -1,3 +1,22 @@
+2016-09-04  John David Anglin  <danglin@gcc.gnu.org>
+
+	* src/pa/ffi.c (ffi_struct_type): Put type declaration on separate line.
+	(ffi_prep_args_pa32): Likewise.
+	(ffi_size_stack_pa32): Likewise.
+	(ffi_prep_cif_machdep): Likewise.
+	(ffi_call): Likewise.  Rename to ffi_call_int.  Add closure argument
+	and update call to ffi_call_pa32.
+	(ffi_call, ffi_call_go, ffi_prep_go_closure): New.
+	(ffi_closure_inner_pa32): Update to handle go closures.
+	* src/pa/ffitarget.h (FFI_GO_CLOSURES): Define.
+	* src/pa/hpux32.S (ffi_call_pa32): Pass go closure argument in static
+	chain register (%ret1).
+	(ffi_closure_pa32): Set closure type argument to zero.
+	(ffi_go_closure_pa32): New function.  Add unwind data for it.
+	* src/pa/linux.S: Likewise.  Use cfi directives for unwind data.
+	* testsuite/libffi.go/static-chain.h (STATIC_CHAIN_REG): Define for
+	hppa.
+
 2016-05-23  Thomas Schwinge  <thomas@codesourcery.com>
 
 	PR libffi/65567
diff --git a/libffi/src/pa/ffi.c b/libffi/src/pa/ffi.c
index 4ce2bc6f0e4c..0da81849deef 100644
--- a/libffi/src/pa/ffi.c
+++ b/libffi/src/pa/ffi.c
@@ -1,5 +1,6 @@
 /* -----------------------------------------------------------------------
-   ffi.c - (c) 2011 Anthony Green
+   ffi.c - (c) 2016 John David Anglin
+	   (c) 2011 Anthony Green
            (c) 2008 Red Hat, Inc.
 	   (c) 2006 Free Software Foundation, Inc.
            (c) 2003-2004 Randolph Chung <tausq@debian.org>
@@ -51,7 +52,8 @@
 
 #define debug(lvl, x...) do { if (lvl <= DEBUG_LEVEL) { printf(x); } } while (0)
 
-static inline int ffi_struct_type(ffi_type *t)
+static inline int
+ffi_struct_type (ffi_type *t)
 {
   size_t sz = t->size;
 
@@ -139,7 +141,8 @@ static inline int ffi_struct_type(ffi_type *t)
    NOTE: We load floating point args in this function... that means we
    assume gcc will not mess with fp regs in here.  */
 
-void ffi_prep_args_pa32(UINT32 *stack, extended_cif *ecif, unsigned bytes)
+void
+ffi_prep_args_pa32 (UINT32 *stack, extended_cif *ecif, unsigned bytes)
 {
   register unsigned int i;
   register ffi_type **p_arg;
@@ -275,7 +278,8 @@ void ffi_prep_args_pa32(UINT32 *stack, extended_cif *ecif, unsigned bytes)
   return;
 }
 
-static void ffi_size_stack_pa32(ffi_cif *cif)
+static void
+ffi_size_stack_pa32 (ffi_cif *cif)
 {
   ffi_type **ptr;
   int i;
@@ -316,7 +320,8 @@ static void ffi_size_stack_pa32(ffi_cif *cif)
 }
 
 /* Perform machine dependent cif processing.  */
-ffi_status ffi_prep_cif_machdep(ffi_cif *cif)
+ffi_status
+ffi_prep_cif_machdep (ffi_cif *cif)
 {
   /* Set the return type flag */
   switch (cif->rtype->type)
@@ -369,11 +374,13 @@ ffi_status ffi_prep_cif_machdep(ffi_cif *cif)
   return FFI_OK;
 }
 
-extern void ffi_call_pa32(void (*)(UINT32 *, extended_cif *, unsigned),
-			  extended_cif *, unsigned, unsigned, unsigned *,
-			  void (*fn)(void));
+extern void ffi_call_pa32 (void (*)(UINT32 *, extended_cif *, unsigned),
+			   extended_cif *, unsigned, unsigned, unsigned *,
+			   void (*fn)(void), void *closure);
 
-void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue)
+static void
+ffi_call_int (ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue,
+	      void *closure)
 {
   extended_cif ecif;
 
@@ -401,8 +408,8 @@ void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue)
     {
     case FFI_PA32:
       debug(3, "Calling ffi_call_pa32: ecif=%p, bytes=%u, flags=%u, rvalue=%p, fn=%p\n", &ecif, cif->bytes, cif->flags, ecif.rvalue, (void *)fn);
-      ffi_call_pa32(ffi_prep_args_pa32, &ecif, cif->bytes,
-		     cif->flags, ecif.rvalue, fn);
+      ffi_call_pa32 (ffi_prep_args_pa32, &ecif, cif->bytes,
+		     cif->flags, ecif.rvalue, fn, closure);
       break;
 
     default:
@@ -411,14 +418,30 @@ void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue)
     }
 }
 
+void
+ffi_call (ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue)
+{
+  ffi_call_int (cif, fn, rvalue, avalue, NULL);
+}
+
+void
+ffi_call_go (ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue,
+	     void *closure)
+{
+  ffi_call_int (cif, fn, rvalue, avalue, closure);
+}
+
 #if FFI_CLOSURES
 /* This is more-or-less an inverse of ffi_call -- we have arguments on
    the stack, and we need to fill them into a cif structure and invoke
    the user function. This really ought to be in asm to make sure
    the compiler doesn't do things we don't expect.  */
-ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack)
+ffi_status
+ffi_closure_inner_pa32 (void *closure, UINT32 *stack, int closure_type)
 {
   ffi_cif *cif;
+  void (*fun)(ffi_cif *,void *,void **,void *); 
+  void *user_data;
   void **avalue;
   void *rvalue;
   UINT32 ret[2]; /* function can return up to 64-bits in registers */
@@ -428,7 +451,19 @@ ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack)
   unsigned int slot = FIRST_ARG_SLOT;
   register UINT32 r28 asm("r28");
 
-  cif = closure->cif;
+  /* A non-zero closure type indicates a go closure.  */
+  if (closure_type)
+    {
+      cif = ((ffi_go_closure *)closure)->cif;
+      fun = ((ffi_go_closure *)closure)->fun;
+      user_data = closure;
+    }
+  else
+    {
+      cif = ((ffi_closure *)closure)->cif;
+      fun = ((ffi_closure *)closure)->fun;
+      user_data = ((ffi_closure *)closure)->user_data;
+    }
 
   /* If returning via structure, callee will write to our pointer.  */
   if (cif->flags == FFI_TYPE_STRUCT)
@@ -436,7 +471,7 @@ ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack)
   else
     rvalue = &ret[0];
 
-  avalue = (void **)alloca(cif->nargs * FFI_SIZEOF_ARG);
+  avalue = (void **) alloca (cif->nargs * FFI_SIZEOF_ARG);
   avn = cif->nargs;
   p_arg = cif->arg_types;
 
@@ -529,7 +564,7 @@ ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack)
     }
 
   /* Invoke the closure.  */
-  (closure->fun) (cif, rvalue, avalue, closure->user_data);
+  fun (cif, rvalue, avalue, user_data);
 
   debug(3, "after calling function, ret[0] = %08x, ret[1] = %08x\n", ret[0],
 	ret[1]);
@@ -621,6 +656,7 @@ ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack)
    cif specifies the argument and result types for fun.
    The cif must already be prep'ed.  */
 
+extern void ffi_go_closure_pa32(void);
 extern void ffi_closure_pa32(void);
 
 ffi_status
@@ -716,4 +752,21 @@ ffi_prep_closure_loc (ffi_closure* closure,
 
   return FFI_OK;
 }
+
+#ifdef FFI_GO_CLOSURES
+ffi_status
+ffi_prep_go_closure (ffi_go_closure *closure,
+		     ffi_cif *cif,
+		     void (*fun)(ffi_cif *, void *, void **, void *))
+{
+  if (cif->abi != FFI_PA32)
+    return FFI_BAD_ABI;
+
+  closure->tramp = &ffi_go_closure_pa32;
+  closure->cif = cif;
+  closure->fun = fun;
+
+  return FFI_OK;
+}
+#endif /* FFI_GO_CLOSURES */
 #endif
diff --git a/libffi/src/pa/ffitarget.h b/libffi/src/pa/ffitarget.h
index fff4c6b382e5..024ac81a8073 100644
--- a/libffi/src/pa/ffitarget.h
+++ b/libffi/src/pa/ffitarget.h
@@ -1,5 +1,6 @@
 /* -----------------------------------------------------------------*-C-*-
-   ffitarget.h - Copyright (c) 2012  Anthony Green
+   ffitarget.h - Copyright (c) 2016  John David Anglin
+		 Copyright (c) 2012  Anthony Green
                  Copyright (c) 1996-2003  Red Hat, Inc.
    Target configuration macros for hppa.
 
@@ -67,6 +68,7 @@ typedef enum ffi_abi {
 /* ---- Definitions for closures ----------------------------------------- */
 
 #define FFI_CLOSURES 1
+#define FFI_GO_CLOSURES 1
 #define FFI_NATIVE_RAW_API 0
 
 #ifdef PA_LINUX
diff --git a/libffi/src/pa/hpux32.S b/libffi/src/pa/hpux32.S
index 40528bad7511..4a47da3791a9 100644
--- a/libffi/src/pa/hpux32.S
+++ b/libffi/src/pa/hpux32.S
@@ -1,6 +1,7 @@
 /* -----------------------------------------------------------------------
    hpux32.S - Copyright (c) 2006 Free Software Foundation, Inc.
 	                (c) 2008 Red Hat, Inc.
+			(c) 2016 John David Anglin
    based on src/pa/linux.S
 
    HP-UX PA Foreign Function Interface
@@ -41,7 +42,8 @@
 			       unsigned bytes,
 			       unsigned flags,
 			       unsigned *rvalue,
-			       void (*fn)(void));
+			       void (*fn)(void),
+			       ffi_go_closure *closure);
 	 */
 
 	.export	ffi_call_pa32,ENTRY,PRIV_LEV=3
@@ -104,6 +106,7 @@ L$CFI13
 	   we need to give it a place to put the result.  */
 	ldw	-52(%r3), %ret0		; %ret0 <- rvalue
 	ldw	-56(%r3), %r22		; %r22 <- function to call
+	ldw	-60(%r3), %ret1		; %ret1 <- closure
 	bl	$$dyncall, %r31		; Call the user function
 	copy	%r31, %rp
 
@@ -285,7 +288,9 @@ L$CFI22
 	stw	%arg2, -44(%r3)
 	stw	%arg3, -48(%r3)
 
+	/* Closure type 0.  */
 	copy	%r21, %arg0
+	copy	%r0, %arg2
 	bl	ffi_closure_inner_pa32, %r2
 	copy    %r3, %arg1
 	ldwm	-64(%sp), %r3
@@ -297,6 +302,47 @@ L$CFI22
 	.procend
 L$FE2:
 
+	/* void ffi_go_closure_pa32(void);
+	   Called with closure argument in %ret1 */
+
+	.SPACE $TEXT$
+	.SUBSPA $CODE$
+	.export ffi_go_closure_pa32,ENTRY,PRIV_LEV=3,RTNVAL=GR
+	.import ffi_closure_inner_pa32,CODE
+	.align 4
+L$FB3
+ffi_go_closure_pa32
+	.proc
+	.callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=3
+	.entry
+
+	stw	%rp, -20(%sp)
+	copy	%r3, %r1
+L$CFI31
+	copy	%sp, %r3
+L$CFI32
+	stwm	%r1, 64(%sp)
+
+	/* Put arguments onto the stack and call ffi_closure_inner.  */
+	stw	%arg0, -36(%r3)
+	stw	%arg1, -40(%r3)
+	stw	%arg2, -44(%r3)
+	stw	%arg3, -48(%r3)
+
+	/* Closure type 1.  */
+	copy	%ret1, %arg0
+	ldi	1, %arg2
+	bl	ffi_closure_inner_pa32, %r2
+	copy    %r3, %arg1
+	ldwm	-64(%sp), %r3
+	ldw	-20(%sp), %rp
+	ldw	-36(%sp), %ret0
+	bv	%r0(%rp)
+	ldw	-40(%sp), %ret1
+	.exit
+	.procend
+L$FE3:
+
 	.SPACE $PRIVATE$
 	.SUBSPA $DATA$
 
@@ -366,3 +412,25 @@ L$ASFDE2:
 
 	.align 4
 L$EFDE2:
+
+L$SFDE3:
+	.word   L$EFDE3-L$ASFDE3        ;# FDE Length
+L$ASFDE3:
+	.word   L$ASFDE3-L$frame1       ;# FDE CIE offset
+	.word   L$FB3   ;# FDE initial location
+	.word   L$FE3-L$FB3     ;# FDE address range
+	.byte   0x4     ;# DW_CFA_advance_loc4
+	.word   L$CFI31-L$FB3
+	.byte   0x83    ;# DW_CFA_offset, column 0x3
+	.uleb128 0x0
+	.byte   0x11    ;# DW_CFA_offset_extended_sf
+	.uleb128 0x2
+	.sleb128 -5
+
+	.byte   0x4     ;# DW_CFA_advance_loc4
+	.word   L$CFI32-L$CFI31
+	.byte   0xd     ;# DW_CFA_def_cfa_register = r3
+	.uleb128 0x3
+
+	.align 4
+L$EFDE3:
diff --git a/libffi/src/pa/linux.S b/libffi/src/pa/linux.S
index f11ae768074d..602690432c04 100644
--- a/libffi/src/pa/linux.S
+++ b/libffi/src/pa/linux.S
@@ -1,6 +1,7 @@
 /* -----------------------------------------------------------------------
    linux.S - (c) 2003-2004 Randolph Chung <tausq@debian.org>
 	     (c) 2008 Red Hat, Inc.
+	     (c) 2016 John David Anglin
 
    HPPA Foreign Function Interface
 
@@ -37,24 +38,26 @@
 			       unsigned bytes,
 			       unsigned flags,
 			       unsigned *rvalue,
-			       void (*fn)(void));
+			       void (*fn)(void),
+			       ffi_go_closure *closure);
 	 */
 
 	.export ffi_call_pa32,code
 	.import ffi_prep_args_pa32,code
 
 	.type ffi_call_pa32, @function
-.LFB1:
+	.cfi_startproc
 ffi_call_pa32:
 	.proc
 	.callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=4
 	.entry
 	stw %rp, -20(%sp)
 	copy %r3, %r1
-.LCFI11:
+        .cfi_offset 2, -20
+        .cfi_register 3, 1
 
 	copy %sp, %r3
-.LCFI12:
+	.cfi_def_cfa_register 3
 
 	/* Setup the stack for calling prep_args...
 	   We want the stack to look like this:
@@ -70,8 +73,8 @@ ffi_call_pa32:
 	 */
 
 	stwm %r1, 64(%sp)
+	.cfi_offset 3, 0
 	stw %r4, 12(%r3)
-.LCFI13:
 	copy %sp, %r4
 
 	addl %arg2, %r4, %arg0      /* arg stack */
@@ -98,6 +101,7 @@ ffi_call_pa32:
 	   we need to give it a place to put the result.  */
 	ldw -52(%r3), %ret0                     /* %ret0 <- rvalue */
 	ldw -56(%r3), %r22                      /* %r22 <- function to call */
+	ldw -60(%r3), %ret1                     /* %ret1 <- closure */
 	bl $$dyncall, %r31                      /* Call the user function */
 	copy %r31, %rp
 
@@ -249,27 +253,27 @@ ffi_call_pa32:
 	nop
 	.exit
 	.procend
-.LFE1:
+	.cfi_endproc
 
 	/* void ffi_closure_pa32(void);
-	   Called with closure argument in %r21 */
+	   Called with ffi_closure argument in %r21.  */
 	.export ffi_closure_pa32,code
 	.import ffi_closure_inner_pa32,code
-
 	.type ffi_closure_pa32, @function
-.LFB2:
+	.cfi_startproc
 ffi_closure_pa32:
 	.proc
 	.callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=3
 	.entry
 
 	stw %rp, -20(%sp)
-.LCFI20:
 	copy %r3, %r1
-.LCFI21:
+	.cfi_offset 2, -20
+	.cfi_register 3, 1
 	copy %sp, %r3
-.LCFI22:
+	.cfi_def_cfa_register 3
 	stwm %r1, 64(%sp)
+	.cfi_offset 3, 0
 
 	/* Put arguments onto the stack and call ffi_closure_inner.  */
 	stw %arg0, -36(%r3)
@@ -277,7 +281,9 @@ ffi_closure_pa32:
 	stw %arg2, -44(%r3)
 	stw %arg3, -48(%r3)
 
+	/* Closure type 0.  */
 	copy %r21, %arg0
+	copy %r0, %arg2
 	bl ffi_closure_inner_pa32, %r2
 	copy %r3, %arg1
 
@@ -289,69 +295,46 @@ ffi_closure_pa32:
 
 	.exit
 	.procend
-.LFE2:
-
-	.section        ".eh_frame",EH_FRAME_FLAGS,@progbits
-.Lframe1:
-	.word   .LECIE1-.LSCIE1 ;# Length of Common Information Entry
-.LSCIE1:
-	.word   0x0     ;# CIE Identifier Tag
-	.byte   0x1     ;# CIE Version
-	.ascii "\0"     ;# CIE Augmentation
-	.uleb128 0x1    ;# CIE Code Alignment Factor
-	.sleb128 4      ;# CIE Data Alignment Factor
-	.byte   0x2     ;# CIE RA Column
-	.byte   0xc     ;# DW_CFA_def_cfa
-	.uleb128 0x1e
-	.uleb128 0x0
-	.align 4
-.LECIE1:
-.LSFDE1:
-	.word   .LEFDE1-.LASFDE1        ;# FDE Length
-.LASFDE1:
-	.word   .LASFDE1-.Lframe1       ;# FDE CIE offset
-	.word   .LFB1   ;# FDE initial location
-	.word   .LFE1-.LFB1     ;# FDE address range
-
-	.byte   0x4     ;# DW_CFA_advance_loc4
-	.word   .LCFI11-.LFB1
-	.byte	0x83	;# DW_CFA_offset, column 0x3
-	.uleb128 0x0
-	.byte   0x11    ;# DW_CFA_offset_extended_sf; save r2 at [r30-20]
-	.uleb128 0x2
-	.sleb128 -5
-
-	.byte   0x4     ;# DW_CFA_advance_loc4
-	.word   .LCFI12-.LCFI11
-	.byte   0xd     ;# DW_CFA_def_cfa_register = r3
-	.uleb128 0x3
-
-	.byte   0x4     ;# DW_CFA_advance_loc4
-	.word   .LCFI13-.LCFI12
-	.byte	0x84	;# DW_CFA_offset, column 0x4
-	.uleb128 0x3
+	.cfi_endproc
 
-	.align 4
-.LEFDE1:
-
-.LSFDE2:
-	.word   .LEFDE2-.LASFDE2        ;# FDE Length
-.LASFDE2:
-	.word   .LASFDE2-.Lframe1       ;# FDE CIE offset
-	.word   .LFB2   ;# FDE initial location
-	.word   .LFE2-.LFB2     ;# FDE address range
-	.byte   0x4     ;# DW_CFA_advance_loc4
-	.word   .LCFI21-.LFB2
-	.byte   0x83    ;# DW_CFA_offset, column 0x3
-	.uleb128 0x0
-	.byte   0x11    ;# DW_CFA_offset_extended_sf
-	.uleb128 0x2
-	.sleb128 -5
-
-	.byte   0x4     ;# DW_CFA_advance_loc4
-	.word   .LCFI22-.LCFI21
-	.byte   0xd     ;# DW_CFA_def_cfa_register = r3
-	.uleb128 0x3
+	/* void ffi_go_closure_pa32(void);
+	   Called with ffi_go_closure argument in %ret1.  */
+	.export ffi_go_closure_pa32,code
+	.import ffi_closure_inner_pa32,code
+	.type ffi_go_closure_pa32, @function
+	.cfi_startproc
+ffi_go_closure_pa32:
+	.proc
+	.callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=3
+	.entry
 
-	.align 4
-.LEFDE2:
+	stw %rp, -20(%sp)
+	copy %r3, %r1
+	.cfi_offset 2, -20
+	.cfi_register 3, 1
+	copy %sp, %r3
+	.cfi_def_cfa_register 3
+	stwm %r1, 64(%sp)
+	.cfi_offset 3, 0
+
+	/* Put arguments onto the stack and call ffi_closure_inner.  */
+	stw %arg0, -36(%r3)
+	stw %arg1, -40(%r3)
+	stw %arg2, -44(%r3)
+	stw %arg3, -48(%r3)
+
+	/* Closure type 1.  */
+	copy %ret1, %arg0
+	ldi 1, %arg2
+	bl ffi_closure_inner_pa32, %r2
+	copy %r3, %arg1
+
+	ldwm -64(%sp), %r3
+	ldw -20(%sp), %rp
+	ldw -36(%sp), %ret0
+	bv %r0(%r2)
+	ldw -40(%sp), %ret1
+
+	.exit
+	.procend
+	.cfi_endproc
diff --git a/libffi/testsuite/libffi.go/static-chain.h b/libffi/testsuite/libffi.go/static-chain.h
index 3675b40a54c8..e120eea5e75b 100644
--- a/libffi/testsuite/libffi.go/static-chain.h
+++ b/libffi/testsuite/libffi.go/static-chain.h
@@ -4,6 +4,12 @@
 # define STATIC_CHAIN_REG  "$1"
 #elif defined(__arm__)
 # define STATIC_CHAIN_REG  "ip"
+#elif defined(__hppa__)
+# if defined(__LP64)
+#   define define STATIC_CHAIN_REG  "%r31"
+# else
+#   define define STATIC_CHAIN_REG  "%r29"   /* %ret1 */
+# endif
 #elif defined(__sparc__)
 # if defined(__arch64__) || defined(__sparcv9)
 #  define STATIC_CHAIN_REG "g5"
-- 
GitLab