tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray / coarray_allocated.f90
bloba423d1f126eaadae9f1cdc55430c989b637fbcde
1 ! { dg-do run }
2 ! { dg-additional-options "-fdump-tree-original" }
3 ! PR fortran/93834 - ICE in trans_caf_is_present
5 program p
6 type t
7 integer, allocatable :: x[:,:,:]
8 end type t
9 integer, allocatable :: a[:]
10 type(t) :: c
11 if (allocated (a)) stop 1
12 if (allocated (c%x)) stop 2
14 ! The coindexed scalar (!) variable is regarded as allocatable but
15 ! we can check the value on any image of the team as they are
16 ! established collectively. As tested by the dump, we do it on
17 ! this_image ().
19 ! For this reason, -fcoarray=single and -fcoarray=lib give the
20 ! same result
21 if (allocated (a[1])) stop 3
22 if (allocated (c%x[1,2,3])) stop 4
24 ! Allocate collectively
25 allocate(a[*])
26 allocate(c%x[4,10,*])
28 if (.not. allocated (a)) stop 5
29 if (.not. allocated (c%x)) stop 6
30 if (.not. allocated (a[1])) stop 7
31 if (.not. allocated (c%x[1,2,3])) stop 8
33 ! Dellocate collectively
34 deallocate(a)
35 deallocate(c%x)
37 if (allocated (a)) stop 9
38 if (allocated (c%x)) stop 10
39 if (allocated (a[1])) stop 11
40 if (allocated (c%x[1,2,3])) stop 12
41 end
43 ! twice == 0 for .not. allocated' (coindexed vs. not)
44 ! four times != for allocated (before alloc after dealloc, coindexed and not)
46 ! There are also == 0 and != 0 for (de)allocate checks with -fcoarray=single but those
47 ! aren't prefixed by '(integer(kind=4) *)'
49 ! { dg-final { scan-tree-dump-times "\\(integer\\(kind=4\\) \\*\\) a.data != 0B" 4 "original" } }
50 ! { dg-final { scan-tree-dump-times "\\(integer\\(kind=4\\) \\*\\) c.x.data != 0B" 4 "original" } }
51 ! { dg-final { scan-tree-dump-times "\\(integer\\(kind=4\\) \\*\\) a.data == 0B" 2 "original" } }
52 ! { dg-final { scan-tree-dump-times "\\(integer\\(kind=4\\) \\*\\) c.x.data == 0B" 2 "original" } }
54 ! Expected: always local access and never a call to _gfortran_caf_get
55 ! { dg-final { scan-tree-dump-not "caf_get" "original" } }