c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / contiguous_3.f90
blobba0ccce8f9ee319767519e973fa24b76fa6d96bb
1 ! { dg-do compile }
2 ! { dg-options "-O0 -fdump-tree-original" }
4 ! PR fortran/40632
6 ! CONTIGUOUS compile-time tests: Check that contigous
7 ! works properly.
9 subroutine test1(a,b)
10 integer, pointer, contiguous :: test1_a(:)
11 integer, target, dimension(3) :: aa
12 test1_a => aa
13 call foo(test1_a)
14 call foo(test1_a(::1))
15 call foo(test1_a(::2))
16 contains
17 subroutine foo(b)
18 integer :: b(*)
19 end subroutine foo
20 end subroutine test1
22 ! For the first two no pack is done; for the third one, an array descriptor
23 ! (cf. below test3) is created for packing.
25 ! { dg-final { scan-tree-dump-times "_internal_pack.*test1_a" 0 "original" } }
26 ! { dg-final { scan-tree-dump-times "_internal_unpack.*test1_a" 0 "original" } }
29 subroutine t2(a1,b1,c2,d2)
30 integer, pointer, contiguous :: a1(:), b1(:)
31 integer, pointer :: c2(:), d2(:)
32 a1 = b1
33 c2 = d2
34 end subroutine t2
36 ! { dg-final { scan-tree-dump-times "= a1->dim.0..stride;" 0 "original" } }
37 ! { dg-final { scan-tree-dump-times "= b1->dim.0..stride;" 0 "original" } }
38 ! { dg-final { scan-tree-dump-times "= c2->dim.0..stride;" 1 "original" } }
39 ! { dg-final { scan-tree-dump-times "= d2->dim.0..stride;" 1 "original" } }
42 subroutine test3()
43 implicit none
44 integer :: test3_a(8),i
45 test3_a = [(i,i=1,8)]
46 call foo(test3_a(::1))
47 call foo(test3_a(::2))
48 call bar(test3_a(::1))
49 call bar(test3_a(::2))
50 contains
51 subroutine foo(x)
52 integer, contiguous :: x(:)
53 print *, x
54 end subroutine
55 subroutine bar(x)
56 integer :: x(:)
57 print *, x
58 end subroutine bar
59 end subroutine test3