PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_size_refs_2.f90
blob8eb708d4989804406a8be36ad298081ac8af4358
1 !==================assumed_size_refs_1.f90==================
2 ! { dg-do compile }
3 ! Test the fix for PR20868 & PR20870 in which references to
4 ! assumed size arrays without an upper bound to the last
5 ! dimension were generating no error.
7 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
9 program assumed_size_test_2
10 implicit none
11 real a(2, 4)
13 a = 1.0
14 call foo (a)
16 contains
17 subroutine foo(m)
18 real, target :: m(1:2, *)
19 real x(2,2,2)
20 real, pointer :: q(:,:)
21 integer :: i
22 allocate (q(2,2))
24 q = cos (1.0 + abs(m)) ! { dg-error "upper bound in the last dimension" }
26 x = reshape (m, (/2,2,2/)) ! { dg-error "upper bound in the last dimension" }
28 ! PR20868
29 print *, ubound (m) ! { dg-error "upper bound in the last dimension" }
30 print *, lbound (m)
32 ! PR20870
33 print *, size (m) ! { dg-error "upper bound in the last dimension" }
35 ! Check non-array valued intrinsics
36 print *, ubound (m, 1)
37 print *, ubound (m, 2) ! { dg-error "not a valid dimension index" }
39 i = 2
40 print *, size (m, i)
42 end subroutine foo
44 end program assumed_size_test_2