From 0ce78f010d98dc190f21682d4ff56615efd03d23 Mon Sep 17 00:00:00 2001
From: Eric Botcazou <ebotcazou@libertysurf.fr>
Date: Sun, 25 Jan 2004 07:58:33 +0100
Subject: [PATCH] ffi.c (ffi_prep_args_v9): Shift the parameter array when the
 structure return address is passed in %o0.

	* src/sparc/ffi.c (ffi_prep_args_v9): Shift the parameter array
	when the structure return address is passed in %o0.
	(ffi_V9_return_struct): Rename into ffi_v9_layout_struct.
	(ffi_v9_layout_struct): Align the field following a nested structure
	on a word boundary.  Use memmove instead of memcpy.
	(ffi_call): Update call to ffi_V9_return_struct.
	(ffi_prep_closure): Define 'ctx' only for V8.
	(ffi_closure_sparc_inner): Clone into ffi_closure_sparc_inner_v8
	and ffi_closure_sparc_inner_v9.
	(ffi_closure_sparc_inner_v8): Return long doubles by reference.
	Always skip the structure return address.  For structures and long
	doubles, copy the argument directly.
	(ffi_closure_sparc_inner_v9): Skip the structure return address only
	if required.  Shift the maximum floating-point slot accordingly.  For
	big structures, copy the argument directly; otherwise, left-justify the
	argument and call ffi_v9_layout_struct to lay out the structure on
	the stack.
	* src/sparc/v8.S: Undef STACKFRAME before defining it.
	(ffi_closure_v8): Pass the structure return address.  Update call to
	ffi_closure_sparc_inner_v8.  Short-circuit FFI_TYPE_INT handling.
	Skip the 'unimp' insn when returning long doubles and structures.
	* src/sparc/v9.S: Undef STACKFRAME before defining it.
	(ffi_closure_v9): Increase the frame size by 2 words.  Short-circuit
	FFI_TYPE_INT handling.  Load structures both in integers and
	floating-point registers on return.
	* README: Update status of the SPARC port.

From-SVN: r76543
---
 libffi/ChangeLog       |  29 ++++++++
 libffi/README          |  10 +--
 libffi/src/sparc/ffi.c | 164 ++++++++++++++++++++++++++++++-----------
 libffi/src/sparc/v8.S  |  47 +++++++-----
 libffi/src/sparc/v9.S  |  64 +++++++++-------
 5 files changed, 219 insertions(+), 95 deletions(-)

diff --git a/libffi/ChangeLog b/libffi/ChangeLog
index 24ec4f1256d4..c2df6b7a19d0 100644
--- a/libffi/ChangeLog
+++ b/libffi/ChangeLog
@@ -1,3 +1,32 @@
+2004-01-25  Eric Botcazou  <ebotcazou@libertysurf.fr>
+
+	* src/sparc/ffi.c (ffi_prep_args_v9): Shift the parameter array
+	when the structure return address is passed in %o0.
+	(ffi_V9_return_struct): Rename into ffi_v9_layout_struct.
+	(ffi_v9_layout_struct): Align the field following a nested structure
+	on a word boundary.  Use memmove instead of memcpy.
+	(ffi_call): Update call to ffi_V9_return_struct.
+	(ffi_prep_closure): Define 'ctx' only for V8.
+	(ffi_closure_sparc_inner): Clone into ffi_closure_sparc_inner_v8
+	and ffi_closure_sparc_inner_v9.
+	(ffi_closure_sparc_inner_v8): Return long doubles by reference.
+	Always skip the structure return address.  For structures and long
+	doubles, copy the argument directly.
+	(ffi_closure_sparc_inner_v9): Skip the structure return address only
+	if required.  Shift the maximum floating-point slot accordingly.  For
+	big structures, copy the argument directly; otherwise, left-justify the
+	argument and call ffi_v9_layout_struct to lay out the structure on
+	the stack.
+	* src/sparc/v8.S: Undef STACKFRAME before defining it.
+	(ffi_closure_v8): Pass the structure return address.  Update call to
+	ffi_closure_sparc_inner_v8.  Short-circuit FFI_TYPE_INT handling.
+	Skip the 'unimp' insn when returning long doubles and structures.
+	* src/sparc/v9.S: Undef STACKFRAME before defining it.
+	(ffi_closure_v9): Increase the frame size by 2 words.  Short-circuit
+	FFI_TYPE_INT handling.  Load structures both in integers and
+	floating-point registers on return.
+	* README: Update status of the SPARC port.
+
 2004-01-24  Andreas Tobler  <a.tobler@schweiz.ch>
 
 	* testsuite/libffi.call/pyobjc-tc.c (main): Treat result value
diff --git a/libffi/README b/libffi/README
index 21a7735bf74d..1fc27470d0a3 100644
--- a/libffi/README
+++ b/libffi/README
@@ -46,7 +46,7 @@ Supported Platforms and Prerequisites
 
 Libffi has been ported to:
 
-	SunOS 4.1.3 & Solaris 2.x (Sparc v8)
+	SunOS 4.1.3 & Solaris 2.x (SPARC-V8, SPARC-V9)
 
 	Irix 5.3 & 6.2 (System V/o32 & n32)
 
@@ -306,15 +306,9 @@ Platform Specific Notes
 
 There are no known problems with the x86 port.
 
-	Sun Sparc - SunOS 4.1.3 & Solaris 2.x
+	Sun SPARC - SunOS 4.1.3 & Solaris 2.x
 	-------------------------------------
 
-There's a bug in the structure passing code for sparc processors.
-Struct arguments that are passed in value actually end up being passed
-by reference. This will be fixed Real Soon Now.
-
-"long long" values are not supported yet.
-
 You must use GNU Make to build libffi on Sun platforms.
 
 	MIPS - Irix 5.3 & 6.x
diff --git a/libffi/src/sparc/ffi.c b/libffi/src/sparc/ffi.c
index a08e65ac5717..ad15bee986c8 100644
--- a/libffi/src/sparc/ffi.c
+++ b/libffi/src/sparc/ffi.c
@@ -1,7 +1,7 @@
 /* -----------------------------------------------------------------------
-   ffi.c - Copyright (c) 1996, 2003 Red Hat, Inc.
+   ffi.c - Copyright (c) 1996, 2003, 2004 Red Hat, Inc.
    
-   Sparc Foreign Function Interface 
+   SPARC Foreign Function Interface 
 
    Permission is hereby granted, free of charge, to any person obtaining
    a copy of this software and associated documentation files (the
@@ -28,11 +28,6 @@
 
 #include <stdlib.h>
 
-#ifdef SPARC64
-extern void ffi_closure_v9(void);
-#else
-extern void ffi_closure_v8(void);
-#endif
 
 /* ffi_prep_args is called by the assembly routine once stack space
    has been allocated for the function's arguments */
@@ -154,6 +149,7 @@ int ffi_prep_args_v9(char *stack, extended_cif *ecif)
       ecif->cif->rtype->size > 32)
     {
       *(unsigned long long *) argp = (unsigned long)ecif->rvalue;
+      argp += sizeof(long long);
       tmp = 1;
     }
 
@@ -326,7 +322,7 @@ ffi_status ffi_prep_cif_machdep(ffi_cif *cif)
   return FFI_OK;
 }
 
-int ffi_V9_return_struct(ffi_type *arg, int off, char *ret, char *intg, char *flt)
+int ffi_v9_layout_struct(ffi_type *arg, int off, char *ret, char *intg, char *flt)
 {
   ffi_type **ptr = &arg->elements[0];
 
@@ -338,18 +334,19 @@ int ffi_V9_return_struct(ffi_type *arg, int off, char *ret, char *intg, char *fl
       switch ((*ptr)->type)
 	{
 	case FFI_TYPE_STRUCT:
-	  off = ffi_V9_return_struct(*ptr, off, ret, intg, flt);
+	  off = ffi_v9_layout_struct(*ptr, off, ret, intg, flt);
+	  off = ALIGN(off, FFI_SIZEOF_ARG);
 	  break;
 	case FFI_TYPE_FLOAT:
 	case FFI_TYPE_DOUBLE:
 #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
 	case FFI_TYPE_LONGDOUBLE:
 #endif
-	  memcpy(ret + off, flt + off, (*ptr)->size);
+	  memmove(ret + off, flt + off, (*ptr)->size);
 	  off += (*ptr)->size;
 	  break;
 	default:
-	  memcpy(ret + off, intg + off, (*ptr)->size);
+	  memmove(ret + off, intg + off, (*ptr)->size);
 	  off += (*ptr)->size;
 	  break;
 	}
@@ -358,10 +355,14 @@ int ffi_V9_return_struct(ffi_type *arg, int off, char *ret, char *intg, char *fl
   return off;
 }
 
-extern int ffi_call_V8(void *, extended_cif *, unsigned, 
+
+#ifdef SPARC64
+extern int ffi_call_v9(void *, extended_cif *, unsigned, 
 		       unsigned, unsigned *, void (*fn)());
-extern int ffi_call_V9(void *, extended_cif *, unsigned, 
+#else
+extern int ffi_call_v8(void *, extended_cif *, unsigned, 
 		       unsigned, unsigned *, void (*fn)());
+#endif
 
 void ffi_call(ffi_cif *cif, void (*fn)(), void *rvalue, void **avalue)
 {
@@ -394,16 +395,16 @@ void ffi_call(ffi_cif *cif, void (*fn)(), void *rvalue, void **avalue)
       /* We don't yet support calling 32bit code from 64bit */
       FFI_ASSERT(0);
 #else
-      ffi_call_V8(ffi_prep_args_v8, &ecif, cif->bytes, 
+      ffi_call_v8(ffi_prep_args_v8, &ecif, cif->bytes, 
 		  cif->flags, rvalue, fn);
 #endif
       break;
     case FFI_V9:
 #ifdef SPARC64
-      ffi_call_V9(ffi_prep_args_v9, &ecif, cif->bytes,
+      ffi_call_v9(ffi_prep_args_v9, &ecif, cif->bytes,
 		  cif->flags, rval, fn);
       if (rvalue && rval && cif->rtype->type == FFI_TYPE_STRUCT)
-	ffi_V9_return_struct(cif->rtype, 0, (char *)rvalue, (char *)rval, ((char *)rval)+32);
+	ffi_v9_layout_struct(cif->rtype, 0, (char *)rvalue, (char *)rval, ((char *)rval)+32);
 #else
       /* And vice versa */
       FFI_ASSERT(0);
@@ -416,6 +417,13 @@ void ffi_call(ffi_cif *cif, void (*fn)(), void *rvalue, void **avalue)
 
 }
 
+
+#ifdef SPARC64
+extern void ffi_closure_v9(void);
+#else
+extern void ffi_closure_v8(void);
+#endif
+
 ffi_status
 ffi_prep_closure (ffi_closure* closure,
 		  ffi_cif* cif,
@@ -424,8 +432,6 @@ ffi_prep_closure (ffi_closure* closure,
 {
   unsigned int *tramp = (unsigned int *) &closure->tramp[0];
   unsigned long fn;
-  unsigned long ctx = (unsigned long) closure;
-
 #ifdef SPARC64
   /* Trampoline address is equal to the closure address.  We take advantage
      of that to reduce the trampoline size by 8 bytes. */
@@ -437,6 +443,7 @@ ffi_prep_closure (ffi_closure* closure,
   tramp[3] = 0x01000000;	/* nop			*/
   *((unsigned long *) &tramp[4]) = fn;
 #else
+  unsigned long ctx = (unsigned long) closure;
   FFI_ASSERT (cif->abi == FFI_V8);
   fn = (unsigned long) ffi_closure_v8;
   tramp[0] = 0x03000000 | fn >> 10;	/* sethi %hi(fn), %g1	*/
@@ -462,49 +469,122 @@ ffi_prep_closure (ffi_closure* closure,
 }
 
 int
-ffi_closure_sparc_inner(ffi_closure *closure,
-  void *rvalue, unsigned long *gpr, double *fpr)
+ffi_closure_sparc_inner_v8(ffi_closure *closure,
+  void *rvalue, unsigned long *gpr)
 {
   ffi_cif *cif;
-  void **avalue;
   ffi_type **arg_types;
-  int i, avn, argn;
+  void **avalue;
+  int i, argn;
 
   cif = closure->cif;
+  arg_types = cif->arg_types;
   avalue = alloca(cif->nargs * sizeof(void *));
 
-  argn = 0;
+  /* Copy the caller's structure return address so that the closure
+     returns the data directly to the caller.  */
+  if (cif->flags == FFI_TYPE_STRUCT
+#if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE  
+      || cif->flags == FFI_TYPE_LONGDOUBLE
+#endif
+     )
+    rvalue = (void *) gpr[0];
+
+  /* Always skip the structure return address.  */
+  argn = 1;
+
+  /* Grab the addresses of the arguments from the stack frame.  */
+  for (i = 0; i < cif->nargs; i++)
+    {
+      if (arg_types[i]->type == FFI_TYPE_STRUCT
+#if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
+	  || arg_types[i]->type == FFI_TYPE_LONGDOUBLE
+#endif
+         )
+	{
+	  /* Straight copy of invisible reference.  */
+	  avalue[i] = (void *)gpr[argn++];
+	}
+      else
+	{
+	  /* Always right-justify.  */
+	  argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG;
+	  avalue[i] = ((char *) &gpr[argn]) - arg_types[i]->size;
+	}
+    }
 
-  /* Copy the caller's structure return address to that the closure
+  /* Invoke the closure.  */
+  (closure->fun) (cif, rvalue, avalue, closure->user_data);
+
+  /* Tell ffi_closure_sparc how to perform return type promotions.  */
+  return cif->rtype->type;
+}
+
+int
+ffi_closure_sparc_inner_v9(ffi_closure *closure,
+  void *rvalue, unsigned long *gpr, double *fpr)
+{
+  ffi_cif *cif;
+  ffi_type **arg_types;
+  void **avalue;
+  int i, argn, fp_slot_max;
+
+  cif = closure->cif;
+  arg_types = cif->arg_types;
+  avalue = alloca(cif->nargs * sizeof(void *));
+
+  /* Copy the caller's structure return address so that the closure
      returns the data directly to the caller.  */
-  if (cif->flags == FFI_TYPE_STRUCT)
+  if (cif->flags == FFI_TYPE_VOID
+      && cif->rtype->type == FFI_TYPE_STRUCT)
     {
       rvalue = (void *) gpr[0];
+      /* Skip the structure return address.  */
       argn = 1;
     }
+  else
+    argn = 0;
+
+  fp_slot_max = 16 - argn;
 
-  i = 0;
-  avn = cif->nargs;
-  arg_types = cif->arg_types;
-  
   /* Grab the addresses of the arguments from the stack frame.  */
-  while (i < avn)
+  for (i = 0; i < cif->nargs; i++)
     {
-      /* Assume big-endian.  FIXME */
-      argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG;
+      if (arg_types[i]->type == FFI_TYPE_STRUCT)
+	{
+	  if (arg_types[i]->size > 16)
+	    {
+	      /* Straight copy of invisible reference.  */
+	      avalue[i] = (void *)gpr[argn++];
+	    }
+	  else
+	    {
+	      /* Left-justify.  */
+	      ffi_v9_layout_struct(arg_types[i],
+				   0,
+				   (char *) &gpr[argn],
+				   (char *) &gpr[argn],
+				   (char *) &fpr[argn]);
+	      avalue[i] = &gpr[argn];
+	      argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG;
+	    }
+	}
+      else
+	{
+	  /* Right-justify.  */
+	  argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG;
 
-#ifdef SPARC64
-      if (i < 16 && (arg_types[i]->type == FFI_TYPE_FLOAT
-		 || arg_types[i]->type == FFI_TYPE_DOUBLE
+	  if (i < fp_slot_max
+	      && (arg_types[i]->type == FFI_TYPE_FLOAT
+		  || arg_types[i]->type == FFI_TYPE_DOUBLE
 #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
-		 || arg_types[i]->type == FFI_TYPE_LONGDOUBLE
+		  || arg_types[i]->type == FFI_TYPE_LONGDOUBLE
 #endif
-		))
-        avalue[i] = ((char *) &fpr[argn]) - arg_types[i]->size;
-      else
-#endif
-        avalue[i] = ((char *) &gpr[argn]) - arg_types[i]->size;
-      i++;
+		  ))
+	    avalue[i] = ((char *) &fpr[argn]) - arg_types[i]->size;
+	  else
+	    avalue[i] = ((char *) &gpr[argn]) - arg_types[i]->size;
+	}
     }
 
   /* Invoke the closure.  */
diff --git a/libffi/src/sparc/v8.S b/libffi/src/sparc/v8.S
index 880aae1f69e0..aaa7be7b4c8e 100644
--- a/libffi/src/sparc/v8.S
+++ b/libffi/src/sparc/v8.S
@@ -1,7 +1,7 @@
 /* -----------------------------------------------------------------------
-   v8.S - Copyright (c) 1996, 1997, 2003 Red Hat, Inc.
+   v8.S - Copyright (c) 1996, 1997, 2003, 2004 Red Hat, Inc.
    
-   Sparc Foreign Function Interface 
+   SPARC Foreign Function Interface 
 
    Permission is hereby granted, free of charge, to any person obtaining
    a copy of this software and associated documentation files (the
@@ -32,11 +32,11 @@
 
 .text
         .align 8
-.globl ffi_call_V8
-.globl _ffi_call_V8
+.globl ffi_call_v8
+.globl _ffi_call_v8
 
-ffi_call_V8:
-_ffi_call_V8:
+ffi_call_v8:
+_ffi_call_v8:
 .LLFB1:
 	save	%sp, -STACKFRAME, %sp
 .LLCFI0:
@@ -92,10 +92,11 @@ longlong:
 	restore
 .LLFE1:
 
-.ffi_call_V8_end:
-	.size	ffi_call_V8,.ffi_call_V8_end-ffi_call_V8
+.ffi_call_v8_end:
+	.size	ffi_call_v8,.ffi_call_v8_end-ffi_call_v8
 
 
+#undef STACKFRAME
 #define	STACKFRAME	104	/* 16*4 register window +
 				   1*4 struct return +	
 				   6*4 args backing store +
@@ -128,14 +129,17 @@ ffi_closure_v8:
 	! Call ffi_closure_sparc_inner to do the bulk of the work.
 	mov	%g2, %o0
 	add	%fp, -8, %o1
-	add	%fp,  68, %o2
-	call	ffi_closure_sparc_inner
-	 mov	0, %o3
+	call	ffi_closure_sparc_inner_v8
+	 add	%fp,  64, %o2
 
 	! Load up the return value in the proper type.
+	! See ffi_prep_cif_machdep for the list of cases.
 	cmp	%o0, FFI_TYPE_VOID
 	be	done1
 
+	cmp	%o0, FFI_TYPE_INT
+	be	integer
+
 	cmp	%o0, FFI_TYPE_FLOAT
 	be,a	done1
 	 ld	[%fp-8], %f0
@@ -144,19 +148,26 @@ ffi_closure_v8:
 	be,a	done1
 	 ldd	[%fp-8], %f0
 
-	cmp	%o0, FFI_TYPE_SINT64
-	be,a	integer
-	 ld	[%fp-4], %i1
+#if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
+	cmp	%o0, FFI_TYPE_LONGDOUBLE
+	be	done2
+#endif
+
+	cmp	%o0, FFI_TYPE_STRUCT
+	be	done2
 
-	cmp	%o0, FFI_TYPE_UINT64
-	be,a	integer
-	 ld	[%fp-4], %i1
+	! FFI_TYPE_SINT64
+	ld	[%fp-4], %i1
 
 integer:
 	ld	[%fp-8], %i0
 
 done1:
-	ret
+	jmp	%i7+8
+	 restore
+done2:
+	! Skip 'unimp'.
+	jmp	%i7+12
 	 restore
 .LLFE2:
 
diff --git a/libffi/src/sparc/v9.S b/libffi/src/sparc/v9.S
index 03b487bb54d9..d640e0232d5c 100644
--- a/libffi/src/sparc/v9.S
+++ b/libffi/src/sparc/v9.S
@@ -1,7 +1,7 @@
 /* -----------------------------------------------------------------------
-   v9.S - Copyright (c) 2000, 2003 Red Hat, Inc.
+   v9.S - Copyright (c) 2000, 2003, 2004 Red Hat, Inc.
    
-   Sparc 64bit Foreign Function Interface 
+   SPARC 64-bit Foreign Function Interface 
 
    Permission is hereby granted, free of charge, to any person obtaining
    a copy of this software and associated documentation files (the
@@ -37,11 +37,11 @@
 
 .text
         .align 8
-.globl ffi_call_V9
-.globl _ffi_call_V9
+.globl ffi_call_v9
+.globl _ffi_call_v9
 
-ffi_call_V9:
-_ffi_call_V9:
+ffi_call_v9:
+_ffi_call_v9:
 .LLFB1:
 	save	%sp, -STACKFRAME, %sp
 .LLCFI0:
@@ -87,7 +87,7 @@ _ffi_call_V9:
 
 	cmp	%i3, FFI_TYPE_INT
 	be,a,pt	%icc, done
-	 stx	%o0, [%i4]	! (delay)
+	 stx	%o0, [%i4+0]	! (delay)
 
 	cmp	%i3, FFI_TYPE_FLOAT
 	be,a,pn	%icc, done
@@ -123,13 +123,14 @@ dostruct:
 	 restore
 .LLFE1:
 
-.ffi_call_V9_end:
-	.size	ffi_call_V9,.ffi_call_V9_end-ffi_call_V9
+.ffi_call_v9_end:
+	.size	ffi_call_v9,.ffi_call_v9_end-ffi_call_v9
 
 
-#define	STACKFRAME	 320	/* 16*8 register window +
+#undef STACKFRAME
+#define	STACKFRAME	 336	/* 16*8 register window +
 				   6*8 args backing store +
-				   18*8 locals */
+				   20*8 locals */
 #define	FP		%fp+STACK_BIAS
 
 /* ffi_closure_v9(...)
@@ -173,46 +174,55 @@ ffi_closure_v9:
 
 	! Call ffi_closure_sparc_inner to do the bulk of the work.
 	mov	%g1, %o0
-	add	%fp, STACK_BIAS-144, %o1
+	add	%fp, STACK_BIAS-160, %o1
 	add	%fp, STACK_BIAS+128, %o2
-	call	ffi_closure_sparc_inner
-	add	%fp, STACK_BIAS-128, %o3
+	call	ffi_closure_sparc_inner_v9
+	 add	%fp, STACK_BIAS-128, %o3
 
 	! Load up the return value in the proper type.
+	! See ffi_prep_cif_machdep for the list of cases.
 	cmp	%o0, FFI_TYPE_VOID
 	be,pn	%icc, done1
 
+	cmp	%o0, FFI_TYPE_INT
+	be,pn	%icc, integer
+
 	cmp	%o0, FFI_TYPE_FLOAT
 	be,a,pn	%icc, done1
-	 ld	[FP-144], %f0
+	 ld	[FP-160], %f0
 
 	cmp	%o0, FFI_TYPE_DOUBLE
 	be,a,pn	%icc, done1
-	 ldd	[FP-144], %f0
+	 ldd	[FP-160], %f0
 
+#if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
 	cmp	%o0, FFI_TYPE_LONGDOUBLE
 	be,a,pn	%icc, longdouble1
-	 ldd	[FP-144], %f0
+	 ldd	[FP-160], %f0
+#endif
 
-	cmp	%o0, FFI_TYPE_STRUCT
-	be,pn	%icc, struct1
+	! FFI_TYPE_STRUCT
+	ldx	[FP-152], %i1
+	ldx	[FP-144], %i2
+	ldx	[FP-136], %i3
+	ldd	[FP-160], %f0
+	ldd	[FP-152], %f2
+	ldd	[FP-144], %f4
+	ldd	[FP-136], %f6
 
-	! FFI_TYPE_UINT64 | FFI_TYPE_SINT64 | FFI_TYPE_POINTER
-	ldx	[FP-144], %i0
+integer:
+	ldx	[FP-160], %i0
 
 done1:
 	ret
 	 restore
 
-struct1:
-	ldx	[FP-136], %i2
-	ret
-	 restore
-
+#if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE
 longdouble1:
-	ldd	[FP-136], %f2
+	ldd	[FP-152], %f2
 	ret
 	 restore
+#endif
 .LLFE2:
 
 .ffi_closure_v9_end:
-- 
GitLab