URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [elemental_optional_args_1.f90] - Rev 302
Compare with Previous | Blame | View Log
! { 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 <jv244@cam.ac.uk>!CALL T1(1,2)CONTAINSSUBROUTINE T1(A1,A2,A3)INTEGER :: A1,A2, A4(2), A5(2)INTEGER, OPTIONAL :: A3(2)interfaceelemental function efoo (B1,B2,B3) result(bar)INTEGER, intent(in) :: B1, B2integer :: barINTEGER, OPTIONAL, intent(in) :: B3end function efooend interface! check an intrinsic functionwrite(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 functionwrite(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 functionwrite(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 subroutinecall foobar (A5,A2,A4)call foobar (A5,A4,A4)END SUBROUTINEelemental function foo (B1,B2,B3) result(bar)INTEGER, intent(in) :: B1, B2integer :: barINTEGER, OPTIONAL, intent(in) :: B3bar = 1end function fooelemental subroutine foobar (B1,B2,B3)INTEGER, intent(OUT) :: B1INTEGER, optional, intent(in) :: B2, B3B1 = 1end subroutine foobarEND
