c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_remapping_6.f08
blob6a4e138f9e5b1bc03ef63d9130177d0d8d14cd1a
1 ! { dg-do run }
2 ! { dg-options "-std=f2008 -fcheck=bounds" }
3 ! { dg-shouldfail "Bounds check" }
5 ! PR fortran/29785
6 ! Check that -fcheck=bounds catches too small target at runtime for
7 ! pointer rank remapping.
9 ! Contributed by Daniel Kraft, d@domob.eu.
11 PROGRAM main
12   IMPLICIT NONE
13   INTEGER, POINTER :: ptr(:, :)
14   INTEGER :: n
16   n = 10
17   BLOCK
18     INTEGER, TARGET :: arr(2*n)
20     ! These are ok.
21     ptr(1:5, 1:2) => arr
22     ptr(1:5, 1:2) => arr(::2)
23     ptr(-5:-1, 11:14) => arr
25     ! This is not.
26     ptr(1:3, 1:5) => arr(::2)
27   END BLOCK
28 END PROGRAM main
29 ! { dg-output "At line 26 of .*\nFortran runtime error: Target of rank remapping is too small \\(10 < 15\\)" }