[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / allocate11.f90
blobb07b7a18ff4c6979b27121a5f41a9c865bd6ca0f
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! Check for semantic errors in ALLOCATE statements
5 ! TODO: Function Pointer in allocate and derived types!
7 ! Rules I should know when working with coarrays and derived type:
9 ! C736: If EXTENDS appears and the type being defined has a coarray ultimate
10 ! component, its parent type shall have a coarray ultimate component.
12 ! C746: (R737) If a coarray-spec appears, it shall be a deferred-coshape-spec-list
13 ! and the component shall have the ALLOCATABLE attribute.
15 ! C747: If a coarray-spec appears, the component shall not be of type C_PTR or
16 ! C_FUNPTR from the intrinsic module ISO_C_BINDING (18.2), or of type TEAM_TYPE from the
17 ! intrinsic module ISO_FORTRAN_ENV (16.10.2).
19 ! C748: A data component whose type has a coarray ultimate component shall be a
20 ! nonpointer nonallocatable scalar and shall not be a coarray.
22 ! 7.5.4.3 Coarray components
23 ! 7.5.6 Final subroutines: C786
26 ! C825 An entity whose type has a coarray ultimate component shall be a
27 ! nonpointer nonallocatable scalar, shall not be a coarray, and shall not be a function result.
29 ! C826 A coarray or an object with a coarray ultimate component shall be an
30 ! associate name, a dummy argument, or have the ALLOCATABLE or SAVE attribute.
32 subroutine C937(var)
33 ! Type-spec shall not specify a type that has a coarray ultimate component.
36 type A
37 real, allocatable :: x[:]
38 end type
40 type B
41 type(A) y
42 !ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'y%x')
43 type(B), pointer :: forward
44 real :: u
45 end type
47 type C
48 type(B) z
49 end type
51 type D
52 !ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'x')
53 type(A), pointer :: potential
54 end type
58 class(*), allocatable :: var
59 ! unlimited polymorphic is the ONLY way to get an allocatable/pointer 'var' that can be
60 ! allocated with a type-spec T that has coarray ultimate component without
61 ! violating other rules than C937.
62 ! Rationale:
63 ! C934 => var must be type compatible with T.
64 ! => var type is T, a type P extended by T, or unlimited polymorphic
65 ! C825 => var cannot be of type T.
66 ! C736 => all parent types P of T must have a coarray ultimate component
67 ! => var cannot be of type P (C825)
68 ! => if var can be defined, it can only be unlimited polymorphic
70 ! Also, as per C826 or C852, var can only be an allocatable, not a pointer
72 ! OK, x is not an ultimate component
73 allocate(D:: var)
75 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
76 allocate(A:: var)
77 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
78 allocate(B:: var)
79 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
80 allocate(C:: var)
81 end subroutine
83 !TODO: type extending team_type !? subcomponents !?
85 subroutine C938_C947(var2, ptr, ptr2, fptr, my_team, srca)
86 ! If an allocate-object is a coarray, type-spec shall not specify type C_PTR or
87 ! C_FUNPTR from the intrinsic module ISO_C_BINDING, or type TEAM_TYPE from the intrinsic module
88 ! ISO_FORTRAN_ENV.
89 use ISO_FORTRAN_ENV
90 use ISO_C_BINDING
92 type A(k, l)
93 integer, kind :: k
94 integer, len :: l
95 real(kind=k) x(l,l)
96 end type
98 ! Again, I do not see any other way to violate this rule and not others without
99 ! having var being an unlimited polymorphic.
100 ! Suppose var of type P and T, the type in type-spec
101 ! Per C934, P must be compatible with T. P cannot be a forbidden type per C824.
102 ! Per C728 and 7.5.7.1, P cannot extend a c_ptr or _c_funptr. hence, P has to be
103 ! unlimited polymorphic or a type that extends TEAM_TYPE.
104 class(*), allocatable :: var[:], var2(:)[:]
105 class(*), allocatable :: varok, varok2(:)
107 Type(C_PTR) :: ptr, ptr2(2:10)
108 Type(C_FUNPTR) fptr
109 Type(TEAM_TYPE) my_team
110 Type(A(4, 10)) :: srca
112 ! Valid constructs
113 allocate(real:: var[5:*])
114 allocate(A(4, 10):: var[5:*])
115 allocate(TEAM_TYPE:: varok, varok2(2))
116 allocate(C_PTR:: varok, varok2(2))
117 allocate(C_FUNPTR:: varok, varok2(2))
119 !ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
120 allocate(TEAM_TYPE:: var[5:*])
121 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
122 allocate(C_PTR:: varok, var[5:*])
123 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
124 allocate(C_FUNPTR:: var[5:*])
125 !ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
126 allocate(TEAM_TYPE:: var2(2)[5:*])
127 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
128 allocate(C_PTR:: var2(2)[5:*])
129 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
130 allocate(C_FUNPTR:: varok2(2), var2(2)[5:*])
133 ! C947: The declared type of source-expr shall not be C_PTR or C_FUNPTR from the
134 ! intrinsic module ISO_C_BINDING, or TEAM_TYPE from the intrinsic module
135 ! ISO_FORTRAN_ENV, if an allocateobject is a coarray.
137 ! ! Valid constructs
138 allocate(var[5:*], SOURCE=cos(0.5_4))
139 allocate(var[5:*], MOLD=srca)
140 allocate(varok, varok2(2), SOURCE=ptr)
141 allocate(varok2, MOLD=ptr2)
142 allocate(varok, varok2(2), SOURCE=my_team)
143 allocate(varok, varok2(2), MOLD=fptr)
145 !ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
146 allocate(var[5:*], SOURCE=my_team)
147 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
148 allocate(var[5:*], SOURCE=ptr)
149 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
150 allocate(varok, var[5:*], MOLD=ptr2(1))
151 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
152 allocate(var[5:*], MOLD=fptr)
153 !ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
154 allocate(var2(2)[5:*], MOLD=my_team)
155 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
156 allocate(var2(2)[5:*], MOLD=ptr)
157 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
158 allocate(var2(2)[5:*], SOURCE=ptr2)
159 !ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
160 allocate(varok2(2), var2(2)[5:*], SOURCE=fptr)
162 end subroutine