fix pr/45972
[official-gcc.git] / gcc / testsuite / gfortran.dg / vector_subscript_6.f90
blob51613d11368c1173c798fbdeca78d13279742fe0
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 subroutine test0(esss,Ix, e_x)
5 real(kind=kind(1.0d0)), dimension(:), intent(out) :: esss
6 real(kind=kind(1.0d0)), dimension(:), intent(in) :: Ix
7 integer(kind=kind(1)), dimension(:), intent(in) :: e_x
8 esss = Ix(e_x)
9 end subroutine
11 subroutine test1(esss,Ix, e_x)
12 real(kind=kind(1.0d0)), dimension(:), intent(out) :: esss
13 real(kind=kind(1.0d0)), dimension(:), intent(in) :: Ix
14 integer(kind=4), dimension(:), intent(in) :: e_x
15 esss = Ix(e_x)
16 end subroutine
18 subroutine test2(esss,Ix, e_x)
19 real(kind=kind(1.0d0)), dimension(:), intent(out) :: esss
20 real(kind=kind(1.0d0)), dimension(:), intent(in) :: Ix
21 integer(kind=8), dimension(:), intent(in) :: e_x
22 esss = Ix(e_x)
23 end subroutine
25 subroutine test3(esss,Ix,Iyz, e_x, ii_ivec)
26 real(kind=kind(1.0d0)), dimension(:), intent(out) :: esss
27 real(kind=kind(1.0d0)), dimension(:), intent(in) :: Ix,Iyz
28 integer(kind=kind(1)), dimension(:), intent(in) :: e_x,ii_ivec
29 esss = esss + Ix(e_x) * Iyz(ii_ivec)
30 end subroutine
32 ! { dg-final { scan-tree-dump-not "malloc" "original" } }
33 ! { dg-final { cleanup-tree-dump "original" } }