AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_remapping_10.f90
blob14938670829cacc49c67ab2cc6c8c77ffa45af12
1 ! { dg-do run }
2 ! { dg-options "-fcheck=all" }
4 ! PR fortran/71194
6 ! Contributed by T Kondic
8 program ice
9 implicit none
10 integer, parameter :: pa=10, pb=20
11 complex, target :: a(pa*pb)
12 real, pointer:: ptr(:,:) =>null()
13 integer :: i, j, cnt
14 logical :: negative
16 do i = 1, size(a)
17 a(i) = cmplx(i,-i)
18 end do
20 ! Was ICEing before with bounds checks
21 ptr(1:pa*2,1:pb) => conv2real(a)
23 negative = .false.
24 cnt = 1
25 do i = 1, ubound(ptr,dim=2)
26 do j = 1, ubound(ptr,dim=1)
27 if (negative) then
28 if (-cnt /= ptr(j, i)) STOP 1
29 cnt = cnt + 1
30 negative = .false.
31 else
32 if (cnt /= ptr(j, i)) STOP 2
33 negative = .true.
34 end if
35 end do
36 end do
38 contains
39 function conv2real(carr)
40 use, intrinsic :: iso_c_binding
41 ! returns real pointer to a complex array
42 complex, contiguous, intent(inout), target :: carr(:)
43 real,contiguous,pointer :: conv2real(:)
44 call c_f_pointer(c_loc(carr),conv2real,[size(carr)*2])
45 end function conv2real
46 end program