4 ! Test the handling of optional, polymorphic and non-polymorphic arguments
5 ! to elemental procedures.
7 ! Original testcase by Tobias Burnus <burnus@net-b.de>
15 integer, allocatable :: a
16 integer, allocatable :: a2(:)
17 integer, pointer :: p => null()
18 integer, pointer :: p2(:) => null()
21 type(t), allocatable :: ta, taa(:)
22 type(t), pointer :: tp, tpa(:)
23 class(t), allocatable :: ca, caa(:)
24 class(t), pointer :: cp, cpa(:)
35 ! =============== sub1 ==================
36 ! SCALAR COMPONENTS: Non alloc/assoc
41 call sub1 (s, x%a, .false.)
42 call sub1 (v, x%a, .false.)
45 if (any (v /= [9, 33])) STOP 2
47 call sub1 (s, x%p, .false.)
48 call sub1 (v, x%p, .false.)
51 if (any (v /= [9, 33])) STOP 4
54 ! SCALAR COMPONENTS: alloc/assoc
59 call sub1 (s, x%a, .true.)
60 call sub1 (v, x%a, .true.)
63 if (any (v /= [4*2, 4*2])) STOP 6
65 call sub1 (s, x%p, .true.)
66 call sub1 (v, x%p, .true.)
69 if (any (v /= [5*2, 5*2])) STOP 8
72 ! ARRAY COMPONENTS: Non alloc/assoc
76 call sub1 (v, x%a2, .false.)
78 if (any (v /= [9, 33])) STOP 9
80 call sub1 (v, x%p2, .false.)
82 if (any (v /= [9, 33])) STOP 10
85 ! ARRAY COMPONENTS: alloc/assoc
87 allocate (x%a2(2), x%p2(2))
91 call sub1 (v, x%a2, .true.)
93 if (any (v /= [84*2, 82*2])) STOP 11
95 call sub1 (v, x%p2, .true.)
97 if (any (v /= [35*2, 58*2])) STOP 12
100 ! =============== sub_t ==================
101 ! SCALAR DT: Non alloc/assoc
106 call sub_t (s, ta, .false.)
107 call sub_t (v, ta, .false.)
110 if (any (v /= [9, 33])) STOP 14
112 call sub_t (s, tp, .false.)
113 call sub_t (v, tp, .false.)
116 if (any (v /= [9, 33])) STOP 16
118 call sub_t (s, ca, .false.)
119 call sub_t (v, ca, .false.)
122 if (any (v /= [9, 33])) STOP 18
124 call sub_t (s, cp, .false.)
125 call sub_t (v, cp, .false.)
128 if (any (v /= [9, 33])) STOP 20
130 ! SCALAR COMPONENTS: alloc/assoc
132 allocate (ta, tp, ca, cp)
138 call sub_t (s, ta, .true.)
139 call sub_t (v, ta, .true.)
141 if (s /= 4*2) STOP 21
142 if (any (v /= [4*2, 4*2])) STOP 22
144 call sub_t (s, tp, .true.)
145 call sub_t (v, tp, .true.)
147 if (s /= 5*2) STOP 23
148 if (any (v /= [5*2, 5*2])) STOP 24
150 call sub_t (s, ca, .true.)
151 call sub_t (v, ca, .true.)
153 if (s /= 6*2) STOP 25
154 if (any (v /= [6*2, 6*2])) STOP 26
156 call sub_t (s, cp, .true.)
157 call sub_t (v, cp, .true.)
159 if (s /= 7*2) STOP 27
160 if (any (v /= [7*2, 7*2])) STOP 28
162 ! ARRAY COMPONENTS: Non alloc/assoc
166 call sub_t (v, taa, .false.)
168 if (any (v /= [9, 33])) STOP 29
170 call sub_t (v, tpa, .false.)
172 if (any (v /= [9, 33])) STOP 30
174 call sub_t (v, caa, .false.)
176 if (any (v /= [9, 33])) STOP 31
178 call sub_t (v, cpa, .false.)
180 if (any (v /= [9, 33])) STOP 32
182 deallocate(ta, tp, ca, cp)
185 ! ARRAY COMPONENTS: alloc/assoc
187 allocate (taa(2), tpa(2))
188 taa(1:2)%a = [44, 444]
189 tpa(1:2)%a = [55, 555]
190 allocate (caa(2), source=[t(66), t(666)])
191 allocate (cpa(2), source=[t(77), t(777)])
195 if (any (caa(:)%a /= [66, 666])) STOP 33
200 if (any (cpa(:)%a /= [77, 777])) STOP 34
203 call sub_t (v, taa, .true.)
205 if (any (v /= [44*2, 444*2])) STOP 35
207 call sub_t (v, tpa, .true.)
209 if (any (v /= [55*2, 555*2])) STOP 36
212 call sub_t (v, caa, .true.)
214 if (any (v /= [66*2, 666*2])) STOP 37
216 call sub_t (v, cpa, .true.)
218 if (any (v /= [77*2, 777*2])) STOP 38
220 deallocate (taa, tpa, caa, cpa)
225 elemental subroutine sub1 (x, y, alloc)
226 integer, intent(inout) :: x
227 integer, intent(in), optional :: y
228 logical, intent(in) :: alloc
229 if (alloc .neqv. present (y)) &
235 elemental subroutine sub_t(x, y, alloc)
236 integer, intent(inout) :: x
237 type(t), intent(in), optional :: y
238 logical, intent(in) :: alloc
239 if (alloc .neqv. present (y)) &