aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_remapping_3.f08
blobc498a364507c98bb964b1b161bf994cb18bd0126
1 ! { dg-do compile }
2 ! { dg-options "-std=f2008" }
4 ! PR fortran/29785
5 ! PR fortran/45016
6 ! PR fortran/60091
7 ! Check for pointer remapping compile-time errors.
9 ! Contributed by Daniel Kraft, d@domob.eu.
11 PROGRAM main
12   IMPLICIT NONE
13   INTEGER, TARGET :: arr(12), basem(3, 4)
14   INTEGER, POINTER :: vec(:), mat(:, :)
16   ! Existence of reference elements.
17   vec(:) => arr ! { dg-error "or list of 'lower-bound : upper-bound'" }
18   vec(5:7:1)  => arr ! { dg-error "Stride must not be present" }
19   mat(1:,2:5) => arr ! { dg-error "Rank remapping requires a list of " }
20   mat(1:3,4:) => arr ! { dg-error "Rank remapping requires a list of " }
21   mat(2, 6)   => arr ! { dg-error "Expected bounds specification" }
23   mat(1:,3:)  => arr ! { dg-error "Rank remapping requires a list of " }
25   ! Invalid remapping target; for non-rank one we already check the F2008
26   ! error elsewhere.  Here, test that not-contiguous target is disallowed
27   ! with rank > 1.
28   mat(1:2, 1:3) => arr(1:12:2) ! This is ok, rank one target.
29   vec(1:8) => basem(1:3:2, :) ! { dg-error "rank 1 or simply contiguous" }
31   ! Target is smaller than pointer.
32   vec(1:20) => arr ! { dg-error "smaller than size of the pointer" }
33   vec(1:10) => arr(1:12:2) ! { dg-error "smaller than size of the pointer" }
34   vec(1:20) => basem(:, :) ! { dg-error "smaller than size of the pointer" }
35   mat(1:5, 1:5) => arr ! { dg-error "smaller than size of the pointer" }
36 END PROGRAM main