aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_remapping_6.f08
blob: 6a4e138f9e5b1bc03ef63d9130177d0d8d14cd1a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
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\\)" }