OSDN Git Service

Merge branch 'trunk' of git://gcc.gnu.org/git/gcc into rework
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / pr46665.f90
1 ! { dg-do run }
2 ! { dg-options "-fipa-pta -fno-tree-ccp -fno-tree-forwprop -g" }
3
4 program main
5   implicit none
6   call test ((/ 3, 4, 5 /), f ((/ 3, 4, 5 /)))
7 contains
8   subroutine test (expected, x)
9     integer, dimension (:,:,:) :: x
10     integer, dimension (3) :: expected
11     integer :: i, i1, i2, i3
12     do i = 1, 3
13       if (size (x, i) .ne. expected (i)) call abort
14     end do
15     do i1 = 1, expected (1)
16       do i2 = 1, expected (2)
17         do i3 = 1, expected (3)
18           if (x (i1, i2, i3) .ne. i1 + i2 * 10 + i3 * 100) call abort
19         end do
20       end do
21     end do
22   end subroutine test
23
24   function f (x)
25     integer, dimension (3) :: x
26     integer, dimension (x(1), x(2), x(3)) :: f
27     integer :: i1, i2, i3
28     do i1 = 1, x(1)
29       do i2 = 1, x(2)
30         do i3 = 1, x(3)
31           f (i1, i2, i3) = i1 + i2 * 10 + i3 * 100
32         end do
33       end do
34     end do
35   end function f
36 end program main