1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Check for semantic errors in ALLOCATE statements
4 ! TODO: Function Pointer in allocate and derived types!
6 ! Rules I should know when working with coarrays and derived type:
8 ! C736: If EXTENDS appears and the type being defined has a coarray ultimate
9 ! component, its parent type shall have a coarray ultimate component.
11 ! C746: (R737) If a coarray-spec appears, it shall be a deferred-coshape-spec-list
12 ! and the component shall have the ALLOCATABLE attribute.
14 ! C747: If a coarray-spec appears, the component shall not be of type C_PTR or
15 ! C_FUNPTR from the intrinsic module ISO_C_BINDING (18.2), or of type TEAM_TYPE from the
16 ! intrinsic module ISO_FORTRAN_ENV (16.10.2).
18 ! C748: A data component whose type has a coarray ultimate component shall be a
19 ! nonpointer nonallocatable scalar and shall not be a coarray.
21 ! 7.5.4.3 Coarray components
22 ! 7.5.6 Final subroutines: C786
25 ! C825 An entity whose type has a coarray ultimate component shall be a
26 ! nonpointer nonallocatable scalar, shall not be a coarray, and shall not be a function result.
28 ! C826 A coarray or an object with a coarray ultimate component shall be an
29 ! associate name, a dummy argument, or have the ALLOCATABLE or SAVE attribute.
32 ! Type-spec shall not specify a type that has a coarray ultimate component.
36 real, allocatable
:: x
[:]
41 !ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'y%x')
42 type(B
), pointer :: forward
51 !ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'x')
52 type(A
), pointer :: potential
57 class(*), allocatable
:: var
58 ! unlimited polymorphic is the ONLY way to get an allocatable/pointer 'var' that can be
59 ! allocated with a type-spec T that has coarray ultimate component without
60 ! violating other rules than C937.
62 ! C934 => var must be type compatible with T.
63 ! => var type is T, a type P extended by T, or unlimited polymorphic
64 ! C825 => var cannot be of type T.
65 ! C736 => all parent types P of T must have a coarray ultimate component
66 ! => var cannot be of type P (C825)
67 ! => if var can be defined, it can only be unlimited polymorphic
69 ! Also, as per C826 or C852, var can only be an allocatable, not a pointer
71 ! OK, x is not an ultimate component
74 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
76 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
78 !ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
82 !TODO: type extending team_type !? subcomponents !?
84 subroutine C938_C947(var2
, ptr
, ptr2
, fptr
, my_team
, srca
)
85 ! If an allocate-object is a coarray, type-spec shall not specify type C_PTR or
86 ! C_FUNPTR from the intrinsic module ISO_C_BINDING, or type TEAM_TYPE from the intrinsic module
97 ! Again, I do not see any other way to violate this rule and not others without
98 ! having var being an unlimited polymorphic.
99 ! Suppose var of type P and T, the type in type-spec
100 ! Per C934, P must be compatible with T. P cannot be a forbidden type per C824.
101 ! Per C728 and 7.5.7.1, P cannot extend a c_ptr or _c_funptr. hence, P has to be
102 ! unlimited polymorphic or a type that extends TEAM_TYPE.
103 class(*), allocatable
:: var
[:], var2(:)[:]
104 class(*), allocatable
:: varok
, varok2(:)
106 Type(C_PTR
) :: ptr
, ptr2(2:10)
108 Type(TEAM_TYPE
) my_team
109 Type(A(4, 10)) :: srca
112 allocate(real:: var
[5:*])
113 allocate(A(4, 10):: var
[5:*])
114 allocate(TEAM_TYPE
:: varok
, varok2(2))
115 allocate(C_PTR
:: varok
, varok2(2))
116 allocate(C_FUNPTR
:: varok
, varok2(2))
118 !ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
119 allocate(TEAM_TYPE
:: var
[5:*])
120 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
121 allocate(C_PTR
:: varok
, var
[5:*])
122 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
123 allocate(C_FUNPTR
:: var
[5:*])
124 !ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
125 allocate(TEAM_TYPE
:: var2(2)[5:*])
126 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
127 allocate(C_PTR
:: var2(2)[5:*])
128 !ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
129 allocate(C_FUNPTR
:: varok2(2), var2(2)[5:*])
132 ! C947: The declared type of source-expr shall not be C_PTR or C_FUNPTR from the
133 ! intrinsic module ISO_C_BINDING, or TEAM_TYPE from the intrinsic module
134 ! ISO_FORTRAN_ENV, if an allocateobject is a coarray.
137 allocate(var
[5:*], SOURCE
=cos(0.5_4
))
138 allocate(var
[5:*], MOLD
=srca
)
139 allocate(varok
, varok2(2), SOURCE
=ptr
)
140 allocate(varok2
, MOLD
=ptr2
)
141 allocate(varok
, varok2(2), SOURCE
=my_team
)
142 allocate(varok
, varok2(2), MOLD
=fptr
)
144 !ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
145 allocate(var
[5:*], SOURCE
=my_team
)
146 !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
147 allocate(var
[5:*], SOURCE
=ptr
)
148 !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
149 allocate(varok
, var
[5:*], MOLD
=ptr2(2))
150 !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
151 allocate(var
[5:*], MOLD
=fptr
)
152 !ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
153 allocate(var2(2)[5:*], MOLD
=my_team
)
154 !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
155 allocate(var2(2)[5:*], MOLD
=ptr
)
156 !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
157 allocate(var2(2)[5:*], SOURCE
=ptr2
)
158 !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
159 allocate(varok2(2), var2(2)[5:*], SOURCE
=fptr
)