From 583a92e874b21a1c7422fadb1153b25a9e647468 Mon Sep 17 00:00:00 2001
From: SUGIOKA Toshinobu <sugioka@itonet.co.jp>
Date: Sat, 23 Jul 2005 07:56:27 +0900
Subject: [PATCH] sysv.S (ffi_call_SYSV): Stop argument popping correctly on
 sh3.

	* src/sh/sysv.S (ffi_call_SYSV): Stop argument popping correctly
	on sh3.
	(ffi_closure_SYSV): Change the stack layout for sh3 struct argument.
	* src/sh/ffi.c (ffi_prep_args): Fix sh3 argument copy, when it is
	partially on register.
	(ffi_closure_helper_SYSV): Likewise.
	(ffi_prep_cif_machdep): Don't set too many cif->flags.

From-SVN: r102298
---
 libffi/ChangeLog     | 10 +++++
 libffi/src/sh/ffi.c  | 20 +++-------
 libffi/src/sh/sysv.S | 88 +++++++++++++++++++++++++++++++-------------
 3 files changed, 78 insertions(+), 40 deletions(-)

diff --git a/libffi/ChangeLog b/libffi/ChangeLog
index bd6a638ac5fd..f61684c056cb 100644
--- a/libffi/ChangeLog
+++ b/libffi/ChangeLog
@@ -1,3 +1,13 @@
+2005-07-22  SUGIOKA Toshinobu  <sugioka@itonet.co.jp>
+
+	* src/sh/sysv.S (ffi_call_SYSV): Stop argument popping correctly
+	on sh3.
+	(ffi_closure_SYSV): Change the stack layout for sh3 struct argument.
+	* src/sh/ffi.c (ffi_prep_args): Fix sh3 argument copy, when it is
+	partially on register.
+	(ffi_closure_helper_SYSV): Likewise.
+	(ffi_prep_cif_machdep): Don't set too many cif->flags.
+
 2005-07-20  Kaz Kojima  <kkojima@gcc.gnu.org>
 
 	* src/sh/ffi.c (ffi_call): Handle small structures correctly.
diff --git a/libffi/src/sh/ffi.c b/libffi/src/sh/ffi.c
index ddf562f048a0..38449e9e6c11 100644
--- a/libffi/src/sh/ffi.c
+++ b/libffi/src/sh/ffi.c
@@ -210,15 +210,11 @@ void ffi_prep_args(char *stack, extended_cif *ecif)
 #if defined(__SH4__)
 	  if (greg + n - 1 >= NGREGARG)
 	    continue;
-	  greg += n;
 #else
 	  if (greg >= NGREGARG)
 	    continue;
-	  else if (greg + n - 1 >= NGREGARG)
-	    greg = NGREGARG;
-	  else
-	    greg += n;
 #endif
+	  greg += n;
 	  memcpy (argp, *p_argv, z);
 	  argp += n * sizeof (int);
 	}
@@ -380,9 +376,8 @@ ffi_status ffi_prep_cif_machdep(ffi_cif *cif)
       if (greg >= NGREGARG)
 	continue;
       else if (greg + n - 1 >= NGREGARG)
-	greg = NGREGARG;
-      else
-	greg += n;
+	n = NGREGARG - greg;
+      greg += n;
       for (m = 0; m < n; m++)
         cif->flags += FFI_TYPE_INT << (2 * j++);
     }
@@ -628,15 +623,11 @@ ffi_closure_helper_SYSV (ffi_closure *closure, void *rvalue,
 #if defined(__SH4__)
 	  if (greg + n - 1 >= NGREGARG)
 	    continue;
-	  greg += n;
 #else
 	  if (greg >= NGREGARG)
 	    continue;
-	  else if (greg + n - 1 >= NGREGARG)
-	    greg = NGREGARG;
-	  else
-	    greg += n;
 #endif
+	  greg += n;
 	  avalue[i] = pgr;
 	  pgr += n;
 	}
@@ -720,7 +711,8 @@ ffi_closure_helper_SYSV (ffi_closure *closure, void *rvalue,
 #if (! defined(__SH4__))
 	  else if (greg < NGREGARG)
 	    {
-	      greg = NGREGARG;
+	      greg += n;
+	      pst += greg - NGREGARG;
 	      continue;
 	    }
 #endif
diff --git a/libffi/src/sh/sysv.S b/libffi/src/sh/sysv.S
index 887137db3ce7..c9002a75027c 100644
--- a/libffi/src/sh/sysv.S
+++ b/libffi/src/sh/sysv.S
@@ -401,6 +401,9 @@ L_pop_d:
 	 mov.l	@r15+,r7
 
 L_pass_i:
+	cmp/eq	#FFI_TYPE_INT,r0
+	bf	L_call_it
+
 	mov	#8,r0
 	cmp/hs	r0,r2
 	bt/s	2f
@@ -492,39 +495,42 @@ L_epilogue:
 
 ENTRY(ffi_closure_SYSV)
 .LFB2:
-	mov.l	r14,@-r15
+	mov.l	r7,@-r15
 .LCFI7:
+	mov.l	r6,@-r15
+.LCFI8:
+	mov.l	r5,@-r15
+.LCFI9:
+	mov.l	r4,@-r15
+.LCFIA:
+	mov.l	r14,@-r15
+.LCFIB:
 	sts.l	pr,@-r15
 
 	/* Stack layout:	
-	   ...
-	   32 bytes (floating register parameters, SH-4 only)
+	   xx bytes (on stack parameters)
 	   16 bytes (register parameters)
+	    4 bytes (saved frame pointer)
+	    4 bytes (saved return address)
+	   32 bytes (floating register parameters, SH-4 only)
 	    8 bytes (result)
 	    4 bytes (pad)
 	    4 bytes (5th arg)
 	   <- new stack pointer
 	*/
-.LCFI8:
+.LCFIC:
 #if defined(__SH4__)
-	add	#-64,r15
+	add	#-48,r15
 #else
-	add	#-32,r15
+	add	#-16,r15
 #endif
-.LCFI9:
+.LCFID:
 	mov	r15,r14
-.LCFIA:
-	mov	r14,r1
-	add	#32,r1
-	mov.l	r7,@-r1
-	mov.l	r6,@-r1
-	mov.l	r5,@-r1
-	mov.l	r4,@-r1
-	mov	r1,r6
+.LCFIE:
 
 #if defined(__SH4__)
 	mov	r14,r1
-	add	#64,r1
+	add	#48,r1
 #ifdef __LITTLE_ENDIAN__
 	fmov.s	fr10,@-r1
 	fmov.s	fr11,@-r1
@@ -545,6 +551,11 @@ ENTRY(ffi_closure_SYSV)
 	fmov.s	fr4,@-r1
 #endif
 	mov	r1,r7
+	mov	r14,r6
+	add	#56,r6
+#else
+	mov	r14,r6
+	add	#24,r6
 #endif
 
 	bt/s	10f
@@ -678,13 +689,14 @@ L_case_uh:
 
 L_case_v:
 #if defined(__SH4__)
-	add	#64,r15
+	add	#48,r15
 #else
-	add	#32,r15
+	add	#16,r15
 #endif
 	lds.l	@r15+,pr
+	mov.l	@r15+,r14
 	rts
-	 mov.l	@r15+,r14
+	 add	#16,r15
 .LFE2:
 .ffi_closure_SYSV_end:
         .size    CNAME(ffi_closure_SYSV),.ffi_closure_SYSV_end-CNAME(ffi_closure_SYSV)
@@ -788,21 +800,45 @@ __FRAME_BEGIN__:
 	.byte	0x4	/* DW_CFA_advance_loc4 */
 	.4byte	.LCFI8-.LCFI7
 	.byte	0xe	/* DW_CFA_def_cfa_offset */
-	.byte	0x8	/* uleb128 0x8 */
+	.byte	0x8	/* uleb128 0x4 */
 	.byte	0x4	/* DW_CFA_advance_loc4 */
 	.4byte	.LCFI9-.LCFI8
 	.byte	0xe	/* DW_CFA_def_cfa_offset */
+	.byte	0xc	/* uleb128 0x4 */
+	.byte	0x4	/* DW_CFA_advance_loc4 */
+	.4byte	.LCFIA-.LCFI9
+	.byte	0xe	/* DW_CFA_def_cfa_offset */
+	.byte	0x10	/* uleb128 0x4 */
+	.byte	0x4	/* DW_CFA_advance_loc4 */
+	.4byte	.LCFIB-.LCFIA
+	.byte	0xe	/* DW_CFA_def_cfa_offset */
+	.byte	0x14	/* uleb128 0x4 */
+	.byte	0x4	/* DW_CFA_advance_loc4 */
+	.4byte	.LCFIC-.LCFIB
+	.byte	0xe	/* DW_CFA_def_cfa_offset */
+	.byte	0x18	/* uleb128 0x4 */
+	.byte	0x4	/* DW_CFA_advance_loc4 */
+	.4byte	.LCFID-.LCFIC
+	.byte	0xe	/* DW_CFA_def_cfa_offset */
 #if defined(__SH4__)
-	.byte	8+64	/* uleb128 8+64 */
+	.byte	24+48	/* uleb128 24+48 */
 #else
-	.byte	8+32	/* uleb128 8+32 */
+	.byte	24+16	/* uleb128 24+16 */
 #endif
 	.byte	0x91	/* DW_CFA_offset, column 0x11 */
-        .byte	0x2
-        .byte	0x8e	/* DW_CFA_offset, column 0xe */
-        .byte	0x1
+	.byte	0x6	/* uleb128 0x6 */
+	.byte	0x8e	/* DW_CFA_offset, column 0xe */
+	.byte	0x5	/* uleb128 0x5 */
+	.byte	0x8b	/* DW_CFA_offset, column 0xb */
+	.byte	0x4	/* uleb128 0x4 */
+	.byte	0x8a	/* DW_CFA_offset, column 0xa */
+	.byte	0x3	/* uleb128 0x3 */
+	.byte	0x89	/* DW_CFA_offset, column 0x9 */
+	.byte	0x2	/* uleb128 0x2 */
+	.byte	0x88	/* DW_CFA_offset, column 0x8 */
+	.byte	0x1	/* uleb128 0x1 */
 	.byte	0x4	/* DW_CFA_advance_loc4 */
-	.4byte	.LCFIA-.LCFI9
+	.4byte	.LCFIE-.LCFID
 	.byte	0xd	/* DW_CFA_def_cfa_register */
 	.byte	0xe	/* uleb128 0xe */
 	.align	2
-- 
GitLab