aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/assumed_size_refs_2.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/assumed_size_refs_2.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/assumed_size_refs_2.f9044
1 files changed, 44 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/assumed_size_refs_2.f90 b/gcc/testsuite/gfortran.dg/assumed_size_refs_2.f90
new file mode 100644
index 00000000000..8eb708d4989
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/assumed_size_refs_2.f90
@@ -0,0 +1,44 @@
+!==================assumed_size_refs_1.f90==================
+! { dg-do compile }
+! Test the fix for PR20868 & PR20870 in which references to
+! assumed size arrays without an upper bound to the last
+! dimension were generating no error.
+!
+! Contributed by Paul Thomas <pault@gcc.gnu.org>
+!
+program assumed_size_test_2
+ implicit none
+ real a(2, 4)
+
+ a = 1.0
+ call foo (a)
+
+contains
+ subroutine foo(m)
+ real, target :: m(1:2, *)
+ real x(2,2,2)
+ real, pointer :: q(:,:)
+ integer :: i
+ allocate (q(2,2))
+
+ q = cos (1.0 + abs(m)) ! { dg-error "upper bound in the last dimension" }
+
+ x = reshape (m, (/2,2,2/)) ! { dg-error "upper bound in the last dimension" }
+
+! PR20868
+ print *, ubound (m) ! { dg-error "upper bound in the last dimension" }
+ print *, lbound (m)
+
+! PR20870
+ print *, size (m) ! { dg-error "upper bound in the last dimension" }
+
+! Check non-array valued intrinsics
+ print *, ubound (m, 1)
+ print *, ubound (m, 2) ! { dg-error "not a valid dimension index" }
+
+ i = 2
+ print *, size (m, i)
+
+ end subroutine foo
+
+end program assumed_size_test_2