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/elemental_optional_args_1.f90 | 53 ++++++++++++++++++++++ 1 file changed, 53 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/elemental_optional_args_1.f90 (limited to 'gcc/testsuite/gfortran.dg/elemental_optional_args_1.f90') diff --git a/gcc/testsuite/gfortran.dg/elemental_optional_args_1.f90 b/gcc/testsuite/gfortran.dg/elemental_optional_args_1.f90 new file mode 100644 index 000000000..ea17b5e34 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/elemental_optional_args_1.f90 @@ -0,0 +1,53 @@ +! { dg-do compile } +! { dg-options "-pedantic" } +! Check the fix for PR20893, in which actual arguments could violate: +! "(5) If it is an array, it shall not be supplied as an actual argument to +! an elemental procedure unless an array of the same rank is supplied as an +! actual argument corresponding to a nonoptional dummy argument of that +! elemental procedure." (12.4.1.5) +! +! Contributed by Joost VandeVondele +! + CALL T1(1,2) +CONTAINS + SUBROUTINE T1(A1,A2,A3) + INTEGER :: A1,A2, A4(2), A5(2) + INTEGER, OPTIONAL :: A3(2) + interface + elemental function efoo (B1,B2,B3) result(bar) + INTEGER, intent(in) :: B1, B2 + integer :: bar + INTEGER, OPTIONAL, intent(in) :: B3 + end function efoo + end interface + +! check an intrinsic function + write(6,*) MAX(A1,A2,A3) ! { dg-warning "array and OPTIONAL" } + write(6,*) MAX(A1,A3,A2) + write(6,*) MAX(A1,A4,A3) +! check an internal elemental function + write(6,*) foo(A1,A2,A3) ! { dg-warning "array and OPTIONAL" } + write(6,*) foo(A1,A3,A2) + write(6,*) foo(A1,A4,A3) +! check an external elemental function + write(6,*) efoo(A1,A2,A3) ! { dg-warning "array and OPTIONAL" } + write(6,*) efoo(A1,A3,A2) + write(6,*) efoo(A1,A4,A3) +! check an elemental subroutine + call foobar (A5,A2,A4) + call foobar (A5,A4,A4) + END SUBROUTINE + elemental function foo (B1,B2,B3) result(bar) + INTEGER, intent(in) :: B1, B2 + integer :: bar + INTEGER, OPTIONAL, intent(in) :: B3 + bar = 1 + end function foo + elemental subroutine foobar (B1,B2,B3) + INTEGER, intent(OUT) :: B1 + INTEGER, optional, intent(in) :: B2, B3 + B1 = 1 + end subroutine foobar + +END + -- cgit v1.2.3