aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/vector_subscript_5.f90
blob: 88eb358e6bf10f5a7aef4eb018233322732b1e3f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
! { dg-do run }
!
! Test the fix for PR37749 in which the expression in line 13 would cause an ICE
! because the upper value of the loop range was not set.
!
! Contributed by Jakub Jelinek <jakub@gcc.gnu.org>
!
subroutine subr (m, n, a, b, c, d, p)
  implicit none
  integer m, n
  real a(m,n), b(m,n), c(n,n), d(m,n)
  integer p(n)
  d = a(:,p) - matmul(b, c)
end subroutine

  implicit none
  integer i
  real a(3,2), b(3,2), c(2,2), d(3,2)
  integer p(2)
  a = reshape ((/(i, i = 1, 6)/), (/3, 2/))
  b = 1
  c = 2
  p = 2
  call subr (3, 2, a, b, c, d, p)
  if (any (d .ne. reshape ((/(mod (i + 2, 3), i = 1, 6)/), (/3, 2/)))) call abort
end