[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr104908.f90
blobc3a30b0003c53d3ee30dc40c0fd05eb5cdc8e6a3
1 ! { dg-do compile }
2 ! { dg-additional-options "-fcheck=bounds -fdump-tree-original" }
4 ! PR fortran/104908 - incorrect out-of-bounds runtime error
6 program test
7 implicit none
8 type vec
9 integer :: x(3) = [2,4,6]
10 end type vec
11 type(vec) :: w(2)
12 call sub(w)
13 contains
14 subroutine sub (v)
15 class(vec), intent(in) :: v(:)
16 integer :: k, q(3)
17 q = [ (v(1)%x(k), k = 1, 3) ] ! <-- was failing here after r11-1235
18 print *, q
19 end
20 end
22 subroutine sub2 (zz)
23 implicit none
24 type vec
25 integer :: x(2,1)
26 end type vec
27 class(vec), intent(in) :: zz(:) ! used to ICE after r11-1235
28 integer :: k
29 k = zz(1)%x(2,1)
30 end
32 ! { dg-final { scan-tree-dump-times " above upper bound " 4 "original" } }