public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* Fix  PR fortran/44693, take 2
@ 2010-07-06 19:11 Thomas Koenig
  2010-07-06 19:44 ` Tobias Burnus
  0 siblings, 1 reply; 3+ messages in thread
From: Thomas Koenig @ 2010-07-06 19:11 UTC (permalink / raw)
  To: fortran; +Cc: gcc-patches

[-- Attachment #1: Type: text/plain, Size: 793 bytes --]

Hello world,

here is a correct version of a fix for PR 44693.  This contains the
necessary special case for SPREAD (where dim can be one larger than the
rank of the array), an expanded test case and a correction to an old
test case.

I think this is finally correct.

Regression-tested, no new regressions.

OK for trunk?

	Thomas

2010-07-06  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/PR44693
	* check.c (dim_rank_check):  Also check intrinsic functions.
	Adjust permissible rank for functions which reduce the rank of
	their argument.  Spread is an exception, where DIM can
	be one larger than the rank of array.

2010-07-06  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/PR44693
	* gfortran.dg/dim_range_1.f90:  New test.
	* gfortran.dg/minmaxloc_4.f90:  Remove invalid test.


[-- Attachment #2: pr44693-3.diff --]
[-- Type: text/x-patch, Size: 1379 bytes --]

Index: testsuite/gfortran.dg/minmaxloc_4.f90
===================================================================
--- testsuite/gfortran.dg/minmaxloc_4.f90	(Revision 161784)
+++ testsuite/gfortran.dg/minmaxloc_4.f90	(Arbeitskopie)
@@ -3,7 +3,6 @@
 PROGRAM TST
   IMPLICIT NONE
   REAL :: A(1,3)
-  REAL :: B(3,1)
   A(:,1) = 10
   A(:,2) = 20
   A(:,3) = 30
@@ -13,9 +12,4 @@
   if (minloc(sum(a(:,1:3),1),1) .ne. 1) call abort()
   if (maxloc(sum(a(:,1:3),1),1) .ne. 3) call abort()
 
-  B(1,:) = 10
-  B(2,:) = 20
-  B(3,:) = 30
-  if (minloc(sum(b(1:3,:),2),2) .ne. 1) call abort()
-  if (maxloc(sum(b(1:3,:),2),2) .ne. 3) call abort()
 END PROGRAM TST
Index: fortran/check.c
===================================================================
--- fortran/check.c	(Revision 161784)
+++ fortran/check.c	(Arbeitskopie)
@@ -473,12 +473,15 @@
   if (dim == NULL)
     return SUCCESS;
 
-  if (dim->expr_type != EXPR_CONSTANT
-      || (array->expr_type != EXPR_VARIABLE
-	  && array->expr_type != EXPR_ARRAY))
+  if (dim->expr_type != EXPR_CONSTANT)
     return SUCCESS;
 
-  rank = array->rank;
+  if (array->expr_type == EXPR_FUNCTION && array->value.function.isym
+      && array->value.function.isym->id == GFC_ISYM_SPREAD)
+    rank = array->rank + 1;
+  else
+    rank = array->rank;
+
   if (array->expr_type == EXPR_VARIABLE)
     {
       ar = gfc_find_array_ref (array);

[-- Attachment #3: dim_range_1.f90 --]
[-- Type: text/x-fortran, Size: 781 bytes --]

! { dg-do compile }
! PR 44693 - check for invalid dim even in functions.
! Based on a test case by Dominique d'Humieres.
subroutine test1(esss,Ix,Iyz, n)
  real(kind=kind(1.0d0)), dimension(n), intent(out) :: esss
  real(kind=kind(1.0d0)), dimension(n,n,n) :: sp
  real(kind=kind(1.0d0)), dimension(n,n) :: Ix,Iyz
  esss = sum(Ix * Iyz, 0) ! { dg-error "is not a valid dimension index" }
  esss = sum(Ix * Iyz, 1)
  esss = sum(Ix * Iyz, 2)
  esss = sum(Ix * Iyz, 3) ! { dg-error "is not a valid dimension index" }
  sp = spread (ix * iyz, 0, n) ! { dg-error "is not a valid dimension index" }
  sp = spread (ix * iyz, 1, n)
  sp = spread (ix * iyz, 2, n)
  sp = spread (ix * iyz, 3, n)
  sp = spread (ix * iyz, 4, n) ! { dg-error "is not a valid dimension index" }
end subroutine

^ permalink raw reply	[flat|nested] 3+ messages in thread

* Re: Fix  PR fortran/44693, take 2
  2010-07-06 19:11 Fix PR fortran/44693, take 2 Thomas Koenig
@ 2010-07-06 19:44 ` Tobias Burnus
  2010-07-06 19:53   ` Thomas Koenig
  0 siblings, 1 reply; 3+ messages in thread
From: Tobias Burnus @ 2010-07-06 19:44 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: fortran, gcc-patches

Thomas Koenig wrote:
> here is a correct version of a fix for PR 44693.  This contains the
> necessary special case for SPREAD (where dim can be one larger than the
> rank of the array), an expanded test case and a correction to an old
> test case.
>
> I think this is finally correct.
> Regression-tested, no new regressions.
> OK for trunk?
>   

OK. Thanks for the patch - and great that you have spotted (possibly
with the test suite) that SPREAD as only intrinsic can have "1 <= dim <=
n +1".

Tobias

> 2010-07-06  Thomas Koenig  <tkoenig@gcc.gnu.org>
>
> 	PR fortran/PR44693
> 	* check.c (dim_rank_check):  Also check intrinsic functions.
> 	Adjust permissible rank for functions which reduce the rank of
> 	their argument.  Spread is an exception, where DIM can
> 	be one larger than the rank of array.
>
> 2010-07-06  Thomas Koenig  <tkoenig@gcc.gnu.org>
>
> 	PR fortran/PR44693
> 	* gfortran.dg/dim_range_1.f90:  New test.
> 	* gfortran.dg/minmaxloc_4.f90:  Remove invalid test.
>
>   

^ permalink raw reply	[flat|nested] 3+ messages in thread

* Re: Fix  PR fortran/44693, take 2
  2010-07-06 19:44 ` Tobias Burnus
@ 2010-07-06 19:53   ` Thomas Koenig
  0 siblings, 0 replies; 3+ messages in thread
From: Thomas Koenig @ 2010-07-06 19:53 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: fortran, gcc-patches

Hi Tobias,

> > Regression-tested, no new regressions.
> > OK for trunk?
> >   
> 
> OK. Thanks for the patch - and great that you have spotted (possibly
> with the test suite) that SPREAD as only intrinsic can have "1 <= dim
> <=
> n +1".


Thanks for the quick review.  Committed, as rev. 161884.

As a matter of fact, I suddenly remembered not understanding this point
once in the library :-)

	Thomas

^ permalink raw reply	[flat|nested] 3+ messages in thread

end of thread, other threads:[~2010-07-06 19:53 UTC | newest]

Thread overview: 3+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-07-06 19:11 Fix PR fortran/44693, take 2 Thomas Koenig
2010-07-06 19:44 ` Tobias Burnus
2010-07-06 19:53   ` Thomas Koenig

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).