aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite
diff options
context:
space:
mode:
authorPaul Thomas <pault@gcc.gnu.org>2007-01-27 18:23:14 +0000
committerPaul Thomas <pault@gcc.gnu.org>2007-01-27 18:23:14 +0000
commita00b8d1a38973eb176d7932bb2bd6cf7e59c5495 (patch)
tree5980c7b71db5312698ab4c49a4066d1da8d30e6b /gcc/testsuite
parentea6244280b016b12843432c1381a2a9064f60d00 (diff)
downloadgcc-a00b8d1a38973eb176d7932bb2bd6cf7e59c5495.zip
gcc-a00b8d1a38973eb176d7932bb2bd6cf7e59c5495.tar.gz
gcc-a00b8d1a38973eb176d7932bb2bd6cf7e59c5495.tar.bz2
re PR fortran/30407 ([4.1 only] Elemental functions in WHERE assignments wrongly rejected)
2007-01-27 Paul Thomas <pault@gcc.gnu.org> PR fortran/30407 * trans-expr.c (gfc_conv_operator_assign): New function. * trans.h : Add prototype for gfc_conv_operator_assign. * trans-stmt.c (gfc_trans_where_assign): Add a gfc_symbol for a potential operator assignment subroutine. If it is non-NULL call gfc_conv_operator_assign instead of the first assignment. ( gfc_trans_where_2): In the case of an operator assignment, extract the argument expressions from the code for the subroutine call and pass the symbol to gfc_trans_where_assign. resolve.c (resolve_where, gfc_resolve_where_code_in_forall, gfc_resolve_forall_body): Resolve the subroutine call for operator assignments. 2007-01-27 Paul Thomas <pault@gcc.gnu.org> PR fortran/30407 * gfortran.dg/where_operator_assign_1.f90: New test. * gfortran.dg/where_operator_assign_2.f90: New test. * gfortran.dg/where_operator_assign_3.f90: New test. From-SVN: r121235
Diffstat (limited to 'gcc/testsuite')
-rw-r--r--gcc/testsuite/ChangeLog7
-rw-r--r--gcc/testsuite/gfortran.dg/where_operator_assign_1.f90108
-rw-r--r--gcc/testsuite/gfortran.dg/where_operator_assign_2.f90106
-rw-r--r--gcc/testsuite/gfortran.dg/where_operator_assign_3.f9081
4 files changed, 302 insertions, 0 deletions
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 426d683..dd50222 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2007-01-27 Paul Thomas <pault@gcc.gnu.org>
+
+ PR fortran/30407
+ * gfortran.dg/where_operator_assign_1.f90: New test.
+ * gfortran.dg/where_operator_assign_2.f90: New test.
+ * gfortran.dg/where_operator_assign_3.f90: New test.
+
2007-01-26 Joseph Myers <joseph@codesourcery.com>
* lib/target-supports.exp
diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90
new file mode 100644
index 0000000..c2b4abf
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90
@@ -0,0 +1,108 @@
+! { dg-do compile }
+! Tests the fix for PR30407, in which operator assignments did not work
+! in WHERE blocks or simple WHERE statements. This is the test provided
+! by the reporter.
+!
+! Contributed by Dominique d'Humieres <dominiq@lps.ens.fr>
+!==============================================================================
+
+MODULE kind_mod
+
+ IMPLICIT NONE
+
+ PRIVATE
+
+ INTEGER, PUBLIC, PARAMETER :: I4=SELECTED_INT_KIND(9)
+ INTEGER, PUBLIC, PARAMETER :: TF=KIND(.TRUE._I4)
+
+END MODULE kind_mod
+
+!==============================================================================
+
+MODULE pointer_mod
+
+ USE kind_mod, ONLY : I4
+
+ IMPLICIT NONE
+
+ PRIVATE
+
+ TYPE, PUBLIC :: pvt
+ INTEGER(I4), POINTER, DIMENSION(:) :: vect
+ END TYPE pvt
+
+ INTERFACE ASSIGNMENT(=)
+ MODULE PROCEDURE p_to_p
+ END INTERFACE
+
+ PUBLIC :: ASSIGNMENT(=)
+
+CONTAINS
+
+ !---------------------------------------------------------------------------
+
+ PURE ELEMENTAL SUBROUTINE p_to_p(a1, a2)
+ IMPLICIT NONE
+ TYPE(pvt), INTENT(OUT) :: a1
+ TYPE(pvt), INTENT(IN) :: a2
+ a1%vect = a2%vect
+ END SUBROUTINE p_to_p
+
+ !---------------------------------------------------------------------------
+
+END MODULE pointer_mod
+
+!==============================================================================
+
+PROGRAM test_prog
+
+ USE pointer_mod, ONLY : pvt, ASSIGNMENT(=)
+
+ USE kind_mod, ONLY : I4, TF
+
+ IMPLICIT NONE
+
+ INTEGER(I4), DIMENSION(12_I4), TARGET :: ia
+ LOGICAL(TF), DIMENSION(2_I4,3_I4) :: la
+ TYPE(pvt), DIMENSION(6_I4) :: pv
+ INTEGER(I4) :: i
+
+ ! Initialisation...
+ la(:,1_I4:3_I4:2_I4)=.TRUE._TF
+ la(:,2_I4)=.FALSE._TF
+
+ DO i=1_I4,6_I4
+ pv(i)%vect => ia((2_I4*i-1_I4):(2_I4*i))
+ END DO
+
+ ia=0_I4
+
+ DO i=1_I4,3_I4
+ WHERE(la((/1_I4,2_I4/),i))
+ pv((2_I4*i-1_I4):(2_I4*i))= iaef((/(2_I4*i-1_I4),(2_I4*i)/))
+ ELSEWHERE
+ pv((2_I4*i-1_I4):(2_I4*i))= iaef((/0_I4,0_I4/))
+ END WHERE
+ END DO
+
+ if (any (ia .ne. (/1,-1,2,-2,0,0,0,0,5,-5,6,-6/))) call abort ()
+
+CONTAINS
+
+ TYPE(pvt) ELEMENTAL FUNCTION iaef(index) RESULT(ans)
+
+ USE kind_mod, ONLY : I4
+ USE pointer_mod, ONLY : pvt, ASSIGNMENT(=)
+
+ IMPLICIT NONE
+
+ INTEGER(I4), INTENT(IN) :: index
+
+ ALLOCATE(ans%vect(2_I4))
+ ans%vect=(/index,-index/)
+
+ END FUNCTION iaef
+
+END PROGRAM test_prog
+
+! { dg-final { cleanup-modules "kind_mod pointer_mod" } }
diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90
new file mode 100644
index 0000000..420103f
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90
@@ -0,0 +1,106 @@
+! { dg-do compile }
+! Tests the fix for PR30407, in which operator assignments did not work
+! in WHERE blocks or simple WHERE statements.
+!
+! Contributed by Paul Thomas <pault@gcc.gnu.org>
+!******************************************************************************
+module global
+ type :: a
+ integer :: b
+ integer :: c
+ end type a
+ interface assignment(=)
+ module procedure a_to_a
+ end interface
+ interface operator(.ne.)
+ module procedure a_ne_a
+ end interface
+
+ type(a) :: x(4), y(4), z(4), u(4, 4)
+ logical :: l1(4), t = .true., f= .false.
+contains
+!******************************************************************************
+ elemental subroutine a_to_a (m, n)
+ type(a), intent(in) :: n
+ type(a), intent(out) :: m
+ m%b = n%b + 1
+ m%c = n%c
+ end subroutine a_to_a
+!******************************************************************************
+ elemental logical function a_ne_a (m, n)
+ type(a), intent(in) :: n
+ type(a), intent(in) :: m
+ a_ne_a = (m%b .ne. n%b) .or. (m%c .ne. n%c)
+ end function a_ne_a
+!******************************************************************************
+ elemental function foo (m)
+ type(a) :: foo
+ type(a), intent(in) :: m
+ foo%b = 0
+ foo%c = m%c
+ end function foo
+end module global
+!******************************************************************************
+program test
+ use global
+ x = (/a (0, 1),a (0, 2),a (0, 3),a (0, 4)/)
+ y = x
+ z = x
+ l1 = (/t, f, f, t/)
+
+ call test_where_1
+ if (any (y .ne. (/a (2, 1),a (2, 2),a (2, 3),a (2, 4)/))) call abort ()
+
+ call test_where_2
+ if (any (y .ne. (/a (1, 0),a (2, 2),a (2, 3),a (1, 0)/))) call abort ()
+ if (any (z .ne. (/a (3, 4),a (1, 0),a (1, 0),a (3, 1)/))) call abort ()
+
+ call test_where_3
+ if (any (y .ne. (/a (1, 0),a (1, 2),a (1, 3),a (1, 0)/))) call abort ()
+
+ y = x
+ call test_where_forall_1
+ if (any (u(4, :) .ne. (/a (1, 4),a (2, 2),a (2, 3),a (1, 4)/))) call abort ()
+
+ l1 = (/t, f, t, f/)
+ call test_where_4
+ if (any (x .ne. (/a (1, 1),a (2, 1),a (1, 3),a (2, 3)/))) call abort ()
+
+contains
+!******************************************************************************
+ subroutine test_where_1 ! Test a simple WHERE
+ where (l1) y = x
+ end subroutine test_where_1
+!******************************************************************************
+ subroutine test_where_2 ! Test a WHERE blocks
+ where (l1)
+ y = a (0, 0)
+ z = z(4:1:-1)
+ elsewhere
+ y = x
+ z = a (0, 0)
+ end where
+ end subroutine test_where_2
+!******************************************************************************
+ subroutine test_where_3 ! Test a simple WHERE with a function assignment
+ where (.not. l1) y = foo (x)
+ end subroutine test_where_3
+!******************************************************************************
+ subroutine test_where_forall_1 ! Test a WHERE in a FORALL block
+ forall (i = 1:4)
+ where (.not. l1)
+ u(i, :) = x
+ elsewhere
+ u(i, :) = a(0, i)
+ endwhere
+ end forall
+ end subroutine test_where_forall_1
+!******************************************************************************
+ subroutine test_where_4 ! Test a WHERE assignment with dependencies
+ where (l1(1:3))
+ x(2:4) = x(1:3)
+ endwhere
+ end subroutine test_where_4
+end program test
+! { dg-final { cleanup-modules "global" } }
+
diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90
new file mode 100644
index 0000000..eddbdfc
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90
@@ -0,0 +1,81 @@
+! { dg-do compile }
+! Tests the fix for PR30407, in which operator assignments did not work
+! in WHERE blocks or simple WHERE statements. This tests that the character
+! lengths are transmitted OK.
+!
+! Contributed by Paul Thomas <pault@gcc.gnu.org>
+!******************************************************************************
+module global
+ type :: a
+ integer :: b
+ character(8):: c
+ end type a
+ interface assignment(=)
+ module procedure a_to_a, c_to_a, a_to_c
+ end interface
+ interface operator(.ne.)
+ module procedure a_ne_a
+ end interface
+
+ type(a) :: x(4), y(4)
+ logical :: l1(4), t = .true., f= .false.
+contains
+!******************************************************************************
+ elemental subroutine a_to_a (m, n)
+ type(a), intent(in) :: n
+ type(a), intent(out) :: m
+ m%b = len ( trim(n%c))
+ m%c = n%c
+ end subroutine a_to_a
+ elemental subroutine c_to_a (m, n)
+ character(8), intent(in) :: n
+ type(a), intent(out) :: m
+ m%b = m%b + 1
+ m%c = n
+ end subroutine c_to_a
+ elemental subroutine a_to_c (m, n)
+ type(a), intent(in) :: n
+ character(8), intent(out) :: m
+ m = n%c
+ end subroutine a_to_c
+!******************************************************************************
+ elemental logical function a_ne_a (m, n)
+ type(a), intent(in) :: n
+ type(a), intent(in) :: m
+ a_ne_a = (m%b .ne. n%b) .or. (m%c .ne. n%c)
+ end function a_ne_a
+!******************************************************************************
+ elemental function foo (m)
+ type(a) :: foo
+ type(a), intent(in) :: m
+ foo%b = 0
+ foo%c = m%c
+ end function foo
+end module global
+!******************************************************************************
+program test
+ use global
+ x = (/a (0, "one"),a (0, "two"),a (0, "three"),a (0, "four")/)
+ y = x
+ l1 = (/t,f,f,t/)
+
+ call test_where_char1
+ call test_where_char2
+ if (any(y .ne. &
+ (/a(4, "null"), a(8, "non-null"), a(8, "non-null"), a(4, "null")/))) call abort ()
+contains
+ subroutine test_where_char1 ! Test a WHERE blocks
+ where (l1)
+ y = a (0, "null")
+ elsewhere
+ y = x
+ end where
+ end subroutine test_where_char1
+ subroutine test_where_char2 ! Test a WHERE blocks
+ where (y%c .ne. "null")
+ y = a (99, "non-null")
+ endwhere
+ end subroutine test_where_char2
+end program test
+! { dg-final { cleanup-modules "global" } }
+