diff mbox

[fortran] PR 38536

Message ID 4D29C8FA.5000400@netcologne.de
State New
Headers show

Commit Message

Thomas Koenig Jan. 9, 2011, 2:40 p.m. UTC
Hello world,

this fixes a rejects-valid bug, what's left of PR 38536 (Mikael fixed
the previous ICE).

OK for trunk?

	Thomas

2011-01-09  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/38536
	* resolve.c (is_scalar_expr_ptr):  For a substring reference,
	use gfc_dep_compare_expr to compare start and end expession.
	Add FIXME for using gfc_deb_compare_expr elsewhere.

2011-01-09  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/38536
	* gfortran.dg/iso_c_binding_c_loc_char_1.f03:  New test.
! { dg-do compile }
! PR 38536 - don't reject substring of length one
! Original test case by Scot Breitenfeld
SUBROUTINE test(buf, buf2, buf3, n)
  USE, INTRINSIC :: ISO_C_BINDING
  IMPLICIT NONE
  CHARACTER(LEN=*), INTENT(INOUT), TARGET :: buf
  INTEGER, INTENT(in) :: n
  CHARACTER(LEN=*), INTENT(INOUT), DIMENSION(1:2), TARGET :: buf2
  CHARACTER(LEN=3), TARGET :: buf3
  TYPE(C_PTR) :: f_ptr

  f_ptr = C_LOC(buf(1:1))      ! Used to fail
                               ! Error: CHARACTER argument 'buf' to 'c_loc'
                               ! at (1) must have a length of 1
  f_ptr = C_LOC(buf2(1)(1:1))  ! PASSES

  f_ptr = C_LOC(buf(n:n))

  f_ptr = C_LOC(buf3(3:))
END SUBROUTINE test

Comments

Thomas Koenig Jan. 9, 2011, 2:46 p.m. UTC | #1
Am 09.01.2011 15:40, schrieb Thomas Koenig:
> Hello world,
> 
> this fixes a rejects-valid bug, what's left of PR 38536 (Mikael fixed
> the previous ICE).
> 
> OK for trunk?

I forgot to mention: Regression-tested.

	Thomas
Tobias Burnus Jan. 9, 2011, 3:25 p.m. UTC | #2
Thomas Koenig wrote:
> this fixes a rejects-valid bug, what's left of PR 38536 (Mikael fixed
> the previous ICE).
>
> OK for trunk?

OK - thanks for the patch.

Tobias

PS: I think two bugs are still left to be fixed (cf. my comment in the PR).

> 2011-01-09  Thomas Koenig<tkoenig@gcc.gnu.org>
>
> 	PR fortran/38536
> 	* resolve.c (is_scalar_expr_ptr):  For a substring reference,
> 	use gfc_dep_compare_expr to compare start and end expession.
> 	Add FIXME for using gfc_deb_compare_expr elsewhere.
>
> 2011-01-09  Thomas Koenig<tkoenig@gcc.gnu.org>
>
> 	PR fortran/38536
> 	* gfortran.dg/iso_c_binding_c_loc_char_1.f03:  New test.
Thomas Koenig Jan. 9, 2011, 3:39 p.m. UTC | #3
Am 09.01.2011 16:25, schrieb Tobias Burnus:
> Thomas Koenig wrote:
>> this fixes a rejects-valid bug, what's left of PR 38536 (Mikael fixed
>> the previous ICE).
>>
>> OK for trunk?
> 
> OK - thanks for the patch.

Sende          fortran/ChangeLog
Sende          fortran/resolve.c
Sende          testsuite/ChangeLog
Hinzufügen     testsuite/gfortran.dg/iso_c_binding_c_loc_char_1.f03
Übertrage Daten ....
Revision 168614 übertragen.

Thanks for the review!

> Tobias
> 
> PS: I think two bugs are still left to be fixed (cf. my comment in the PR).

A pity - I would have liked to close it ;-)

	Thomas
diff mbox

Patch

Index: resolve.c
===================================================================
--- resolve.c	(Revision 168596)
+++ resolve.c	(Arbeitskopie)
@@ -2547,21 +2547,11 @@  is_scalar_expr_ptr (gfc_expr *expr)
       switch (ref->type)
         {
         case REF_SUBSTRING:
-          if (ref->u.ss.length != NULL 
-              && ref->u.ss.length->length != NULL
-              && ref->u.ss.start
-              && ref->u.ss.start->expr_type == EXPR_CONSTANT 
-              && ref->u.ss.end
-              && ref->u.ss.end->expr_type == EXPR_CONSTANT)
-            {
-              start = (int) mpz_get_si (ref->u.ss.start->value.integer);
-              end = (int) mpz_get_si (ref->u.ss.end->value.integer);
-              if (end - start + 1 != 1)
-                retval = FAILURE;
-            }
-          else
-            retval = FAILURE;
+          if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
+	      || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
+	    retval = FAILURE;
           break;
+
         case REF_ARRAY:
           if (ref->u.ar.type == AR_ELEMENT)
             retval = SUCCESS;
@@ -2590,7 +2580,8 @@  is_scalar_expr_ptr (gfc_expr *expr)
 		    {
 		      /* We have constant lower and upper bounds.  If the
 			 difference between is 1, it can be considered a
-			 scalar.  */
+			 scalar.  
+			 FIXME: Use gfc_dep_compare_expr instead.  */
 		      start = (int) mpz_get_si
 				(ref->u.ar.as->lower[0]->value.integer);
 		      end = (int) mpz_get_si