2 ! { dg-options "-fcheck=pointer" }
4 ! { dg-shouldfail "pointer check" }
5 ! { dg-output ".*At line 104 of file .*Fortran runtime error: Pointer actual argument 'a' is not associated.*" }
9 ! The following cases are all valid, but were failing
10 ! for one or the other reason.
12 ! Contributed by Janus Weil and Tobias Burnus.
18 subroutine test(str
,uec
)
20 character*(*), intent(in
), optional
:: str
21 integer, intent(in
), optional
:: uec
27 Module procedure matrixMult_C2
32 complex, dimension(0:3,0:3) :: m1
,m2
33 print *,Trace(MatrixMult(m1
,m2
))
35 complex function trace(a
)
37 complex, intent(in
), dimension(0:3,0:3) :: a
39 function matrixMult_C2(a
,b
) result(matrix
)
41 complex, dimension(0:3,0:3) :: matrix
,a
,b
42 end function matrixMult_C2
45 SUBROUTINE plotdop(amat
)
47 REAL, INTENT (IN
) :: amat(3,3)
51 pt
= MATMUL(amat
,(/i1
,i1
,i1
/))
52 END SUBROUTINE plotdop
54 FUNCTION evaluateFirst(s
,n
)result(number
)
56 CHARACTER(len
=*), INTENT(inout
) :: s
62 SUBROUTINE rw_inp(scpos
)
67 FUNCTION evaluateFirst(s
,n
)result(number
)
69 CHARACTER(len
=*), INTENT(inout
) :: s
75 CHARACTER(len
=100) :: line
76 scpos
= evaluatefirst(line
)
95 integer, pointer,optional
:: a
101 integer, pointer,optional
:: a
103 ! call sub2(a) ! << Invalid - working correctly, but not allowed in F2003
104 call sub3(a
) ! << INVALID
107 integer, optional
,pointer :: b
110 integer, optional
:: b