PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / maxloc_bounds_4.f90
blobb1c7ca752d04ff167b679f3d4b6b5394466035af
1 ! { dg-do run }
2 ! { dg-options "-fbounds-check" }
3 ! { dg-shouldfail "Incorrect extent in return value of MAXLOC intrinsic: is 3, should be 2" }
4 module tst
5 contains
6 subroutine foo(res)
7 integer(kind=4), allocatable :: f(:,:)
8 integer, dimension(:) :: res
9 allocate (f(2,5))
10 f = 3
11 res = maxloc(f)
12 end subroutine foo
14 end module tst
15 program main
16 use tst
17 implicit none
18 integer :: res(3)
19 call foo(res)
20 end program main
21 ! { dg-output "Fortran runtime error: Incorrect extent in return value of MAXLOC intrinsic: is 3, should be 2" }