Remove old autovect-branch by moving to "dead" directory.
[official-gcc.git] / old-autovect-branch / gcc / testsuite / gfortran.fortran-torture / execute / bounds.f90
blob894cd5d56b26fe32413091443d9b57a41b2fdd3d
1 ! Program to test the upper and lower bound intrinsics
2 program testbounds
3 implicit none
4 real, dimension(:, :), allocatable :: a
5 integer, dimension(5) :: j
6 integer i
8 ! Check compile time simplification
9 if (lbound(j,1).ne.1 .or. ubound(j,1).ne.5) call abort ()
11 allocate (a(3:8, 6:7))
13 ! With one parameter
14 j = 0;
15 j(3:4) = ubound(a)
16 if (j(3) .ne. 8) call abort
17 if (j(4) .ne. 7) call abort
19 ! With two parameters, assigning to an array
20 j = lbound(a, 1)
21 if ((j(1) .ne. 3) .or. (j(5) .ne. 3)) call abort
23 ! With a variable second parameter
24 i = 2
25 i = lbound(a, i)
26 if (i .ne. 6) call abort
28 call test(a)
29 contains
30 subroutine test (a)
31 real, dimension (1:, 1:) :: a
32 integer i
34 i = 2
35 if ((ubound(a, 1) .ne. 6) .or. (ubound(a, i) .ne. 2)) call abort
36 end subroutine
37 end program