summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/pointer_remapping_6.f08
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/pointer_remapping_6.f08')
-rw-r--r--gcc/testsuite/gfortran.dg/pointer_remapping_6.f0829
1 files changed, 29 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/pointer_remapping_6.f08 b/gcc/testsuite/gfortran.dg/pointer_remapping_6.f08
new file mode 100644
index 000000000..6a4e138f9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pointer_remapping_6.f08
@@ -0,0 +1,29 @@
+! { dg-do run }
+! { dg-options "-std=f2008 -fcheck=bounds" }
+! { dg-shouldfail "Bounds check" }
+
+! PR fortran/29785
+! Check that -fcheck=bounds catches too small target at runtime for
+! pointer rank remapping.
+
+! Contributed by Daniel Kraft, d@domob.eu.
+
+PROGRAM main
+ IMPLICIT NONE
+ INTEGER, POINTER :: ptr(:, :)
+ INTEGER :: n
+
+ n = 10
+ BLOCK
+ INTEGER, TARGET :: arr(2*n)
+
+ ! These are ok.
+ ptr(1:5, 1:2) => arr
+ ptr(1:5, 1:2) => arr(::2)
+ ptr(-5:-1, 11:14) => arr
+
+ ! This is not.
+ ptr(1:3, 1:5) => arr(::2)
+ END BLOCK
+END PROGRAM main
+! { dg-output "At line 26 of .*\nFortran runtime error: Target of rank remapping is too small \\(10 < 15\\)" }