From 554fd8c5195424bdbcabf5de30fdc183aba391bd Mon Sep 17 00:00:00 2001 From: upstream source tree Date: Sun, 15 Mar 2015 20:14:05 -0400 Subject: obtained gcc-4.6.4.tar.bz2 from upstream website; verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository. --- .../gfortran.dg/where_operator_assign_1.f90 | 108 +++++++++++++++++++++ 1 file changed, 108 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 (limited to 'gcc/testsuite/gfortran.dg/where_operator_assign_1.f90') 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 000000000..c2b4abf85 --- /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 +!============================================================================== + +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" } } -- cgit v1.2.3