Increase timeout factor for hppa*-*-* in gcc.dg/long_branch.c
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr96312.f90
blobd6d8e79119fc54ed0efbfcafde72c964c489c0e1
1 ! { dg-do compile }
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>
9 module moda
10 contains
11 PURE SUBROUTINE funca(arr, sz)
12 REAL, ALLOCATABLE, DIMENSION(:, :), INTENT(OUT) :: arr
13 integer, intent(in) :: sz
14 allocate(arr(sz, sz))
15 arr(:, :) = 0.
16 END SUBROUTINE
17 end module
19 module modc
20 use moda, only: funca
21 contains
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)
28 oarr = tmp*1.
29 END SUBROUTINE funcb
30 end module