2 ! { dg-options "-O1 -Wall" }
4 ! PR fortran/96312. The line with the call to 'matmul' gave the warning
5 ! ‘tmp.dim[0].lbound’ is used uninitialized in this function
7 ! Contributed by Thomas Koenig <tkoenig@gcc.gnu.org>
11 PURE
SUBROUTINE funca(arr
, sz
)
12 REAL, ALLOCATABLE
, DIMENSION(:, :), INTENT(OUT
) :: arr
13 integer, intent(in
) :: sz
22 PURE
SUBROUTINE funcb(oarr
)
23 REAL, DIMENSION(:), INTENT(OUT
) :: oarr
24 REAL, ALLOCATABLE
, DIMENSION(:, :) :: arr
25 real, allocatable
, dimension(:) :: tmp
26 CALL funca(arr
, ubound(oarr
, 1))
27 tmp
= matmul(transpose(arr
),oarr
)