[mlir][NFC] Avoid using braced initializer lists to call a constructor. (#123714)
[llvm-project.git] / flang / test / Lower / Intrinsics / reduce.f90
blob8d7ec89d27474ccf1d1b3502ebad512c945b5ece
1 ! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
3 module reduce_mod
5 type :: t1
6 integer :: a
7 end type
9 abstract interface
10 pure function red_int1_interface(a, b)
11 integer(1), intent(in) :: a, b
12 integer(1) :: red_int1_interface
13 end function
14 pure function red_int1_interface_value(a, b)
15 integer(1), value, intent(in) :: a, b
16 integer(1) :: red_int1_interface_value
17 end function
18 end interface
20 contains
22 pure function red_int1(a,b)
23 integer(1), intent(in) :: a, b
24 integer(1) :: red_int1
25 red_int1 = a + b
26 end function
28 pure function red_int1_value(a,b)
29 integer(1), value, intent(in) :: a, b
30 integer(1) :: red_int1_value
31 red_int1_value = a + b
32 end function
34 subroutine integer1(a, id, d1, d2)
35 integer(1), intent(in) :: a(:)
36 integer(1) :: res, id
37 procedure(red_int1_interface), pointer :: fptr
38 procedure(red_int1_interface_value), pointer :: fptr_value
39 procedure(red_int1_interface) :: d1
40 procedure(red_int1_interface_value) :: d2
42 res = reduce(a, red_int1)
44 res = reduce(a, red_int1, identity=id)
46 res = reduce(a, red_int1, identity=id, ordered = .true.)
48 res = reduce(a, red_int1, [.true., .true., .false.])
50 res = reduce(a, red_int1_value)
52 fptr => red_int1
53 res = reduce(a, fptr)
55 fptr_value => red_int1_value
56 res = reduce(a, fptr_value)
58 !res = reduce(a, d1)
59 !res = reduce(a, d2)
60 end subroutine
62 ! CHECK-LABEL: func.func @_QMreduce_modPinteger1(
63 ! CHECK-SAME: %[[ARG0:.*]]: !fir.box<!fir.array<?xi8>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<i8> {fir.bindc_name = "id"}
64 ! CHECK: %[[A:.*]]:2 = hlfir.declare %[[ARG0]] dummy_scope %{{.*}} {fortran_attrs = #fir.var_attrs<intent_in>, uniq_name = "_QMreduce_modFinteger1Ea"} : (!fir.box<!fir.array<?xi8>>, !fir.dscope) -> (!fir.box<!fir.array<?xi8>>, !fir.box<!fir.array<?xi8>>)
65 ! CHECK: %[[ID:.*]]:2 = hlfir.declare %[[ARG1]] dummy_scope %{{.*}} {uniq_name = "_QMreduce_modFinteger1Eid"} : (!fir.ref<i8>, !fir.dscope) -> (!fir.ref<i8>, !fir.ref<i8>)
66 ! CHECK: %[[ALLOC_RES:.*]] = fir.alloca i8 {bindc_name = "res", uniq_name = "_QMreduce_modFinteger1Eres"}
67 ! CHECK: %[[RES:.*]]:2 = hlfir.declare %[[ALLOC_RES]] {uniq_name = "_QMreduce_modFinteger1Eres"} : (!fir.ref<i8>) -> (!fir.ref<i8>, !fir.ref<i8>)
68 ! CHECK: %[[ADDR_OP:.*]] = fir.address_of(@_QMreduce_modPred_int1) : (!fir.ref<i8>, !fir.ref<i8>) -> i8
69 ! CHECK: %[[BOX_PROC:.*]] = fir.emboxproc %[[ADDR_OP]] : ((!fir.ref<i8>, !fir.ref<i8>) -> i8) -> !fir.boxproc<() -> ()>
70 ! CHECK: %[[MASK:.*]] = fir.absent !fir.box<i1>
71 ! CHECK: %[[IDENTITY:.*]] = fir.absent !fir.ref<i8>
72 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX_PROC]] : (!fir.boxproc<() -> ()>) -> ((!fir.ref<i8>, !fir.ref<i8>) -> !fir.ref<i8>)
73 ! CHECK: %[[A_NONE:.*]] = fir.convert %[[A]]#1 : (!fir.box<!fir.array<?xi8>>) -> !fir.box<none>
74 ! CHECK: %[[MASK_NONE:.*]] = fir.convert %[[MASK]] : (!fir.box<i1>) -> !fir.box<none>
75 ! CHECK: %[[REDUCE_RES:.*]] = fir.call @_FortranAReduceInteger1Ref(%[[A_NONE]], %[[BOX_ADDR]], %{{.*}}, %{{.*}}, %c1{{.*}}, %[[MASK_NONE]], %[[IDENTITY]], %false) fastmath<contract> : (!fir.box<none>, (!fir.ref<i8>, !fir.ref<i8>) -> !fir.ref<i8>, !fir.ref<i8>, i32, i32, !fir.box<none>, !fir.ref<i8>, i1) -> i8
76 ! CHECK: hlfir.assign %[[REDUCE_RES]] to %[[RES]]#0 : i8, !fir.ref<i8>
77 ! CHECK: %[[ADDR_OP:.*]] = fir.address_of(@_QMreduce_modPred_int1) : (!fir.ref<i8>, !fir.ref<i8>) -> i8
78 ! CHECK: %[[BOX_PROC:.*]] = fir.emboxproc %[[ADDR_OP]] : ((!fir.ref<i8>, !fir.ref<i8>) -> i8) -> !fir.boxproc<() -> ()>
79 ! CHECK: %[[MASK:.*]] = fir.absent !fir.box<i1>
80 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX_PROC]] : (!fir.boxproc<() -> ()>) -> ((!fir.ref<i8>, !fir.ref<i8>) -> !fir.ref<i8>)
81 ! CHECK: %[[A_NONE:.*]] = fir.convert %[[A]]#1 : (!fir.box<!fir.array<?xi8>>) -> !fir.box<none>
82 ! CHECK: %[[MASK_NONE:.*]] = fir.convert %[[MASK]] : (!fir.box<i1>) -> !fir.box<none>
83 ! CHECK: %{{.*}} = fir.call @_FortranAReduceInteger1Ref(%[[A_NONE]], %[[BOX_ADDR]], %{{.*}}, %{{.*}}, %c1{{.*}}, %[[MASK_NONE]], %[[ID]]#1, %false{{.*}}) fastmath<contract> : (!fir.box<none>, (!fir.ref<i8>, !fir.ref<i8>) -> !fir.ref<i8>, !fir.ref<i8>, i32, i32, !fir.box<none>, !fir.ref<i8>, i1) -> i8
84 ! CHECK: fir.call @_FortranAReduceInteger1Ref(%{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}#1, %true)
85 ! CHECK: %[[MASK:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QQro.3xl4.0"} : (!fir.ref<!fir.array<3x!fir.logical<4>>>, !fir.shape<1>) -> (!fir.ref<!fir.array<3x!fir.logical<4>>>, !fir.ref<!fir.array<3x!fir.logical<4>>>)
86 ! CHECK: %[[SHAPE_C3:.*]] = fir.shape %c3{{.*}} : (index) -> !fir.shape<1>
87 ! CHECK: %[[BOXED_MASK:.*]] = fir.embox %[[MASK]]#1(%[[SHAPE_C3]]) : (!fir.ref<!fir.array<3x!fir.logical<4>>>, !fir.shape<1>) -> !fir.box<!fir.array<3x!fir.logical<4>>>
88 ! CHECK: %[[CONV_MASK:.*]] = fir.convert %[[BOXED_MASK]] : (!fir.box<!fir.array<3x!fir.logical<4>>>) -> !fir.box<none>
89 ! CHECK: fir.call @_FortranAReduceInteger1Ref(%{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %[[CONV_MASK]], %{{.*}}, %false{{.*}})
90 ! CHECK: fir.call @_FortranAReduceInteger1Value
91 ! CHECK: fir.call @_FortranAReduceInteger1Ref
92 ! CHECK: fir.call @_FortranAReduceInteger1Value
93 ! TODO fir.call @_FortranAReduceInteger1Ref
94 ! TODO fir.call @_FortranAReduceInteger1Value
96 pure function red_int2(a,b)
97 integer(2), intent(in) :: a, b
98 integer(2) :: red_int2
99 red_int2 = a + b
100 end function
102 pure function red_int2_value(a,b)
103 integer(2), value, intent(in) :: a, b
104 integer(2) :: red_int2_value
105 red_int2_value = a + b
106 end function
108 subroutine integer2(a)
109 integer(2), intent(in) :: a(:)
110 integer(2) :: res
111 res = reduce(a, red_int2)
112 res = reduce(a, red_int2_value)
113 end subroutine
115 ! CHECK: fir.call @_FortranAReduceInteger2Ref
116 ! CHECK: fir.call @_FortranAReduceInteger2Value
118 pure function red_int4(a,b)
119 integer(4), intent(in) :: a, b
120 integer(4) :: red_int4
121 red_int4 = a + b
122 end function
124 pure function red_int4_value(a,b)
125 integer(4), value, intent(in) :: a, b
126 integer(4) :: red_int4_value
127 red_int4_value = a + b
128 end function
130 subroutine integer4(a)
131 integer(4), intent(in) :: a(:)
132 integer(4) :: res
133 res = reduce(a, red_int4)
134 res = reduce(a, red_int4_value)
135 end subroutine
137 ! CHECK: fir.call @_FortranAReduceInteger4Ref
138 ! CHECK: fir.call @_FortranAReduceInteger4Value
140 pure function red_int8(a,b)
141 integer(8), intent(in) :: a, b
142 integer(8) :: red_int8
143 red_int8 = a + b
144 end function
146 pure function red_int8_value(a,b)
147 integer(8), value, intent(in) :: a, b
148 integer(8) :: red_int8_value
149 red_int8_value = a + b
150 end function
152 subroutine integer8(a)
153 integer(8), intent(in) :: a(:)
154 integer(8) :: res
155 res = reduce(a, red_int8)
156 res = reduce(a, red_int8_value)
157 end subroutine
159 ! CHECK: fir.call @_FortranAReduceInteger8Ref
160 ! CHECK: fir.call @_FortranAReduceInteger8Value
162 pure function red_int16(a,b)
163 integer(16), intent(in) :: a, b
164 integer(16) :: red_int16
165 red_int16 = a + b
166 end function
168 pure function red_int16_value(a,b)
169 integer(16), value, intent(in) :: a, b
170 integer(16) :: red_int16_value
171 red_int16_value = a + b
172 end function
174 subroutine integer16(a)
175 integer(16), intent(in) :: a(:)
176 integer(16) :: res
177 res = reduce(a, red_int16)
178 res = reduce(a, red_int16_value)
179 end subroutine
181 ! CHECK: fir.call @_FortranAReduceInteger16Ref
182 ! CHECK: fir.call @_FortranAReduceInteger16Value
184 pure function red_real2(a,b)
185 real(2), intent(in) :: a, b
186 real(2) :: red_real2
187 red_real2 = a + b
188 end function
190 pure function red_real2_value(a,b)
191 real(2), value, intent(in) :: a, b
192 real(2) :: red_real2_value
193 red_real2_value = a + b
194 end function
196 subroutine real2(a)
197 real(2), intent(in) :: a(:)
198 real(2) :: res
199 res = reduce(a, red_real2)
200 res = reduce(a, red_real2_value)
201 end subroutine
203 ! CHECK: fir.call @_FortranAReduceReal2Ref
204 ! CHECK: fir.call @_FortranAReduceReal2Value
206 pure function red_real3(a,b)
207 real(3), intent(in) :: a, b
208 real(3) :: red_real3
209 red_real3 = a + b
210 end function
212 pure function red_real3_value(a,b)
213 real(3), value, intent(in) :: a, b
214 real(3) :: red_real3_value
215 red_real3_value = a + b
216 end function
218 subroutine real3(a)
219 real(3), intent(in) :: a(:)
220 real(3) :: res
221 res = reduce(a, red_real3)
222 res = reduce(a, red_real3_value)
223 end subroutine
225 ! CHECK: fir.call @_FortranAReduceReal3Ref
226 ! CHECK: fir.call @_FortranAReduceReal3Value
228 pure function red_real4(a,b)
229 real(4), intent(in) :: a, b
230 real(4) :: red_real4
231 red_real4 = a + b
232 end function
234 pure function red_real4_value(a,b)
235 real(4), value, intent(in) :: a, b
236 real(4) :: red_real4_value
237 red_real4_value = a + b
238 end function
240 subroutine real4(a)
241 real(4), intent(in) :: a(:)
242 real(4) :: res
243 res = reduce(a, red_real4)
244 res = reduce(a, red_real4_value)
245 end subroutine
247 ! CHECK: fir.call @_FortranAReduceReal4Ref
248 ! CHECK: fir.call @_FortranAReduceReal4Value
250 pure function red_real8(a,b)
251 real(8), intent(in) :: a, b
252 real(8) :: red_real8
253 red_real8 = a + b
254 end function
256 pure function red_real8_value(a,b)
257 real(8), value, intent(in) :: a, b
258 real(8) :: red_real8_value
259 red_real8_value = a + b
260 end function
262 subroutine real8(a)
263 real(8), intent(in) :: a(:)
264 real(8) :: res
265 res = reduce(a, red_real8)
266 res = reduce(a, red_real8_value)
267 end subroutine
269 ! CHECK: fir.call @_FortranAReduceReal8Ref
270 ! CHECK: fir.call @_FortranAReduceReal8Value
272 pure function red_real10(a,b)
273 real(10), intent(in) :: a, b
274 real(10) :: red_real10
275 red_real10 = a + b
276 end function
278 pure function red_real10_value(a,b)
279 real(10), value, intent(in) :: a, b
280 real(10) :: red_real10_value
281 red_real10_value = a + b
282 end function
284 subroutine real10(a)
285 real(10), intent(in) :: a(:)
286 real(10) :: res
287 res = reduce(a, red_real10)
288 res = reduce(a, red_real10_value)
289 end subroutine
291 ! CHECK: fir.call @_FortranAReduceReal10Ref
292 ! CHECK: fir.call @_FortranAReduceReal10Value
294 pure function red_real16(a,b)
295 real(16), intent(in) :: a, b
296 real(16) :: red_real16
297 red_real16 = a + b
298 end function
300 pure function red_real16_value(a,b)
301 real(16), value, intent(in) :: a, b
302 real(16) :: red_real16_value
303 red_real16_value = a + b
304 end function
306 subroutine real16(a)
307 real(16), intent(in) :: a(:)
308 real(16) :: res
309 res = reduce(a, red_real16)
310 res = reduce(a, red_real16_value)
311 end subroutine
313 ! CHECK: fir.call @_FortranAReduceReal16Ref
314 ! CHECK: fir.call @_FortranAReduceReal16Value
316 pure function red_complex2(a,b)
317 complex(2), intent(in) :: a, b
318 complex(2) :: red_complex2
319 red_complex2 = a + b
320 end function
322 pure function red_complex2_value(a,b)
323 complex(2), value, intent(in) :: a, b
324 complex(2) :: red_complex2_value
325 red_complex2_value = a + b
326 end function
328 subroutine complex2(a)
329 complex(2), intent(in) :: a(:)
330 complex(2) :: res
331 res = reduce(a, red_complex2)
332 res = reduce(a, red_complex2_value)
333 end subroutine
335 ! CHECK: fir.call @_FortranACppReduceComplex2Ref
336 ! CHECK: fir.call @_FortranACppReduceComplex2Value
338 pure function red_complex3(a,b)
339 complex(3), intent(in) :: a, b
340 complex(3) :: red_complex3
341 red_complex3 = a + b
342 end function
344 pure function red_complex3_value(a,b)
345 complex(3), value, intent(in) :: a, b
346 complex(3) :: red_complex3_value
347 red_complex3_value = a + b
348 end function
350 subroutine complex3(a)
351 complex(3), intent(in) :: a(:)
352 complex(3) :: res
353 res = reduce(a, red_complex3)
354 res = reduce(a, red_complex3_value)
355 end subroutine
357 ! CHECK: fir.call @_FortranACppReduceComplex3Ref
358 ! CHECK: fir.call @_FortranACppReduceComplex3Value
360 pure function red_complex4(a,b)
361 complex(4), intent(in) :: a, b
362 complex(4) :: red_complex4
363 red_complex4 = a + b
364 end function
366 pure function red_complex4_value(a,b)
367 complex(4), value, intent(in) :: a, b
368 complex(4) :: red_complex4_value
369 red_complex4_value = a + b
370 end function
372 subroutine complex4(a)
373 complex(4), intent(in) :: a(:)
374 complex(4) :: res
375 res = reduce(a, red_complex4)
376 res = reduce(a, red_complex4_value)
377 end subroutine
379 ! CHECK: fir.call @_FortranACppReduceComplex4Ref
380 ! CHECK: fir.call @_FortranACppReduceComplex4Value
382 pure function red_complex8(a,b)
383 complex(8), intent(in) :: a, b
384 complex(8) :: red_complex8
385 red_complex8 = a + b
386 end function
388 pure function red_complex8_value(a,b)
389 complex(8), value, intent(in) :: a, b
390 complex(8) :: red_complex8_value
391 red_complex8_value = a + b
392 end function
394 subroutine complex8(a)
395 complex(8), intent(in) :: a(:)
396 complex(8) :: res
397 res = reduce(a, red_complex8)
398 res = reduce(a, red_complex8_value)
399 end subroutine
401 ! CHECK: fir.call @_FortranACppReduceComplex8Ref
402 ! CHECK: fir.call @_FortranACppReduceComplex8Value
404 pure function red_complex10(a,b)
405 complex(10), intent(in) :: a, b
406 complex(10) :: red_complex10
407 red_complex10 = a + b
408 end function
410 pure function red_complex10_value(a,b)
411 complex(10), value, intent(in) :: a, b
412 complex(10) :: red_complex10_value
413 red_complex10_value = a + b
414 end function
416 subroutine complex10(a)
417 complex(10), intent(in) :: a(:)
418 complex(10) :: res
419 res = reduce(a, red_complex10)
420 res = reduce(a, red_complex10_value)
421 end subroutine
423 ! CHECK: fir.call @_FortranACppReduceComplex10Ref
424 ! CHECK: fir.call @_FortranACppReduceComplex10Value
426 pure function red_complex16(a,b)
427 complex(16), intent(in) :: a, b
428 complex(16) :: red_complex16
429 red_complex16 = a + b
430 end function
432 pure function red_complex16_value(a,b)
433 complex(16), value, intent(in) :: a, b
434 complex(16) :: red_complex16_value
435 red_complex16_value = a + b
436 end function
438 subroutine complex16(a)
439 complex(16), intent(in) :: a(:)
440 complex(16) :: res
441 res = reduce(a, red_complex16)
442 res = reduce(a, red_complex16_value)
443 end subroutine
445 ! CHECK: fir.call @_FortranACppReduceComplex16Ref
446 ! CHECK: fir.call @_FortranACppReduceComplex16Value
448 pure function red_log1(a,b)
449 logical(1), intent(in) :: a, b
450 logical(1) :: red_log1
451 red_log1 = a .and. b
452 end function
454 pure function red_log1_value(a,b)
455 logical(1), value, intent(in) :: a, b
456 logical(1) :: red_log1_value
457 red_log1_value = a .and. b
458 end function
460 subroutine log1(a)
461 logical(1), intent(in) :: a(:)
462 logical(1) :: res
463 res = reduce(a, red_log1)
464 res = reduce(a, red_log1_value)
465 end subroutine
467 ! CHECK: fir.call @_FortranAReduceLogical1Ref
468 ! CHECK: fir.call @_FortranAReduceLogical1Value
470 pure function red_log2(a,b)
471 logical(2), intent(in) :: a, b
472 logical(2) :: red_log2
473 red_log2 = a .and. b
474 end function
476 pure function red_log2_value(a,b)
477 logical(2), value, intent(in) :: a, b
478 logical(2) :: red_log2_value
479 red_log2_value = a .and. b
480 end function
482 subroutine log2(a)
483 logical(2), intent(in) :: a(:)
484 logical(2) :: res
485 res = reduce(a, red_log2)
486 res = reduce(a, red_log2_value)
487 end subroutine
489 ! CHECK: fir.call @_FortranAReduceLogical2Ref
490 ! CHECK: fir.call @_FortranAReduceLogical2Value
492 pure function red_log4(a,b)
493 logical(4), intent(in) :: a, b
494 logical(4) :: red_log4
495 red_log4 = a .and. b
496 end function
498 pure function red_log4_value(a,b)
499 logical(4), value, intent(in) :: a, b
500 logical(4) :: red_log4_value
501 red_log4_value = a .and. b
502 end function
504 subroutine log4(a)
505 logical(4), intent(in) :: a(:)
506 logical(4) :: res
507 res = reduce(a, red_log4)
508 res = reduce(a, red_log4_value)
509 end subroutine
511 ! CHECK: fir.call @_FortranAReduceLogical4Ref
512 ! CHECK: fir.call @_FortranAReduceLogical4Value
514 pure function red_log8(a,b)
515 logical(8), intent(in) :: a, b
516 logical(8) :: red_log8
517 red_log8 = a .and. b
518 end function
520 pure function red_log8_value(a,b)
521 logical(8), value, intent(in) :: a, b
522 logical(8) :: red_log8_value
523 red_log8_value = a .and. b
524 end function
526 subroutine log8(a)
527 logical(8), intent(in) :: a(:)
528 logical(8) :: res
529 res = reduce(a, red_log8)
530 res = reduce(a, red_log8_value)
531 end subroutine
533 ! CHECK: fir.call @_FortranAReduceLogical8Ref
534 ! CHECK: fir.call @_FortranAReduceLogical8Value
536 pure function red_char1(a,b)
537 character(1), intent(in) :: a, b
538 character(1) :: red_char1
539 red_char1 = a // b
540 end function
542 subroutine char1(a)
543 character(1), intent(in) :: a(:)
544 character(1) :: res
545 res = reduce(a, red_char1)
546 end subroutine
548 ! CHECK: %[[CHRTMP:.*]] = fir.alloca !fir.char<1> {bindc_name = ".chrtmp"}
549 ! CHECK: %[[RESULT:.*]] = fir.convert %[[CHRTMP]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
550 ! CHECK: fir.call @_FortranAReduceChar1(%[[RESULT]], {{.*}})
552 pure function red_char2(a,b)
553 character(kind=2, len=10), intent(in) :: a, b
554 character(kind=2, len=10) :: red_char2
555 red_char2 = a // b
556 end function
558 subroutine char2(a)
559 character(kind=2, len=10), intent(in) :: a(:)
560 character(kind=2, len=10) :: res
561 res = reduce(a, red_char2)
562 end subroutine
564 ! CHECK: %[[CHRTMP:.*]] = fir.alloca !fir.char<2,10> {bindc_name = ".chrtmp"}
565 ! CHECK: %[[RESULT:.*]] = fir.convert %[[CHRTMP]] : (!fir.ref<!fir.char<2,10>>) -> !fir.ref<i16>
566 ! CHECK: fir.call @_FortranAReduceChar2(%[[RESULT]], {{.*}})
568 pure function red_char4(a,b)
569 character(kind=4), intent(in) :: a, b
570 character(kind=4) :: red_char4
571 red_char4 = a // b
572 end function
574 subroutine char4(a)
575 character(kind=4), intent(in) :: a(:)
576 character(kind=4) :: res
577 res = reduce(a, red_char4)
578 end subroutine
580 ! CHECK: fir.call @_FortranAReduceChar4
582 pure function red_type(a,b)
583 type(t1), intent(in) :: a, b
584 type(t1) :: red_type
585 red_type%a = a%a + b%a
586 end function
588 subroutine testtype(a)
589 type(t1), intent(in) :: a(:)
590 type(t1) :: res
591 res = reduce(a, red_type)
592 end subroutine
594 ! CHECK: fir.call @_FortranAReduceDerivedType
596 subroutine integer1dim(a, id)
597 integer(1), intent(in) :: a(:,:)
598 integer(1), allocatable :: res(:)
600 res = reduce(a, red_int1, 2)
601 res = reduce(a, red_int1_value, 2)
602 end subroutine
604 ! CHECK: fir.call @_FortranAReduceInteger1DimRef
605 ! CHECK: fir.call @_FortranAReduceInteger1DimValue
607 subroutine integer2dim(a, id)
608 integer(2), intent(in) :: a(:,:)
609 integer(2), allocatable :: res(:)
611 res = reduce(a, red_int2, 2)
612 res = reduce(a, red_int2_value, 2)
613 end subroutine
615 ! CHECK: fir.call @_FortranAReduceInteger2DimRef
616 ! CHECK: fir.call @_FortranAReduceInteger2DimValue
618 subroutine integer4dim(a, id)
619 integer(4), intent(in) :: a(:,:)
620 integer(4), allocatable :: res(:)
622 res = reduce(a, red_int4, 2)
623 res = reduce(a, red_int4_value, 2)
624 end subroutine
626 ! CHECK: fir.call @_FortranAReduceInteger4DimRef
627 ! CHECK: fir.call @_FortranAReduceInteger4DimValue
629 subroutine integer8dim(a, id)
630 integer(8), intent(in) :: a(:,:)
631 integer(8), allocatable :: res(:)
633 res = reduce(a, red_int8, 2)
634 res = reduce(a, red_int8_value, 2)
635 end subroutine
637 ! CHECK: fir.call @_FortranAReduceInteger8DimRef
638 ! CHECK: fir.call @_FortranAReduceInteger8DimValue
640 subroutine integer16dim(a, id)
641 integer(16), intent(in) :: a(:,:)
642 integer(16), allocatable :: res(:)
644 res = reduce(a, red_int16, 2)
645 res = reduce(a, red_int16_value, 2)
646 end subroutine
648 ! CHECK: fir.call @_FortranAReduceInteger16DimRef
649 ! CHECK: fir.call @_FortranAReduceInteger16DimValue
651 subroutine real2dim(a, id)
652 real(2), intent(in) :: a(:,:)
653 real(2), allocatable :: res(:)
655 res = reduce(a, red_real2, 2)
656 res = reduce(a, red_real2_value, 2)
657 end subroutine
659 ! CHECK: fir.call @_FortranAReduceReal2DimRef
660 ! CHECK: fir.call @_FortranAReduceReal2DimValue
662 subroutine real3dim(a, id)
663 real(3), intent(in) :: a(:,:)
664 real(3), allocatable :: res(:)
666 res = reduce(a, red_real3, 2)
667 res = reduce(a, red_real3_value, 2)
668 end subroutine
670 ! CHECK: fir.call @_FortranAReduceReal3DimRef
671 ! CHECK: fir.call @_FortranAReduceReal3DimValue
673 subroutine real4dim(a, id)
674 real(4), intent(in) :: a(:,:)
675 real(4), allocatable :: res(:)
677 res = reduce(a, red_real4, 2)
678 res = reduce(a, red_real4_value, 2)
679 end subroutine
681 ! CHECK: fir.call @_FortranAReduceReal4DimRef
682 ! CHECK: fir.call @_FortranAReduceReal4DimValue
684 subroutine real8dim(a, id)
685 real(8), intent(in) :: a(:,:)
686 real(8), allocatable :: res(:)
688 res = reduce(a, red_real8, 2)
689 res = reduce(a, red_real8_value, 2)
690 end subroutine
692 ! CHECK: fir.call @_FortranAReduceReal8DimRef
693 ! CHECK: fir.call @_FortranAReduceReal8DimValue
695 subroutine real10dim(a, id)
696 real(10), intent(in) :: a(:,:)
697 real(10), allocatable :: res(:)
699 res = reduce(a, red_real10, 2)
700 res = reduce(a, red_real10_value, 2)
701 end subroutine
703 ! CHECK: fir.call @_FortranAReduceReal10DimRef
704 ! CHECK: fir.call @_FortranAReduceReal10DimValue
706 subroutine real16dim(a, id)
707 real(16), intent(in) :: a(:,:)
708 real(16), allocatable :: res(:)
710 res = reduce(a, red_real16, 2)
711 res = reduce(a, red_real16_value, 2)
712 end subroutine
714 ! CHECK: fir.call @_FortranAReduceReal16DimRef
715 ! CHECK: fir.call @_FortranAReduceReal16DimValue
717 subroutine complex2dim(a, id)
718 complex(2), intent(in) :: a(:,:)
719 complex(2), allocatable :: res(:)
721 res = reduce(a, red_complex2, 2)
722 res = reduce(a, red_complex2_value, 2)
723 end subroutine
725 ! CHECK: fir.call @_FortranACppReduceComplex2DimRef
726 ! CHECK: fir.call @_FortranACppReduceComplex2DimValue
728 subroutine complex3dim(a, id)
729 complex(3), intent(in) :: a(:,:)
730 complex(3), allocatable :: res(:)
732 res = reduce(a, red_complex3, 2)
733 res = reduce(a, red_complex3_value, 2)
734 end subroutine
736 ! CHECK: fir.call @_FortranACppReduceComplex3DimRef
737 ! CHECK: fir.call @_FortranACppReduceComplex3DimValue
739 subroutine complex4dim(a, id)
740 complex(4), intent(in) :: a(:,:)
741 complex(4), allocatable :: res(:)
743 res = reduce(a, red_complex4, 2)
744 res = reduce(a, red_complex4_value, 2)
745 end subroutine
747 ! CHECK: fir.call @_FortranACppReduceComplex4DimRef
748 ! CHECK: fir.call @_FortranACppReduceComplex4DimValue
750 subroutine complex8dim(a, id)
751 complex(8), intent(in) :: a(:,:)
752 complex(8), allocatable :: res(:)
754 res = reduce(a, red_complex8, 2)
755 res = reduce(a, red_complex8_value, 2)
756 end subroutine
758 ! CHECK: fir.call @_FortranACppReduceComplex8DimRef
759 ! CHECK: fir.call @_FortranACppReduceComplex8DimValue
761 subroutine complex10dim(a, id)
762 complex(10), intent(in) :: a(:,:)
763 complex(10), allocatable :: res(:)
765 res = reduce(a, red_complex10, 2)
766 res = reduce(a, red_complex10_value, 2)
767 end subroutine
769 ! CHECK: fir.call @_FortranACppReduceComplex10DimRef
770 ! CHECK: fir.call @_FortranACppReduceComplex10DimValue
772 subroutine complex16dim(a, id)
773 complex(16), intent(in) :: a(:,:)
774 complex(16), allocatable :: res(:)
776 res = reduce(a, red_complex16, 2)
777 res = reduce(a, red_complex16_value, 2)
778 end subroutine
780 ! CHECK: fir.call @_FortranACppReduceComplex16DimRef
781 ! CHECK: fir.call @_FortranACppReduceComplex16DimValue
783 subroutine logical1dim(a, id)
784 logical(1), intent(in) :: a(:,:)
785 logical(1), allocatable :: res(:)
787 res = reduce(a, red_log1, 2)
788 res = reduce(a, red_log1_value, 2)
789 end subroutine
791 ! CHECK: fir.call @_FortranAReduceLogical1DimRef
792 ! CHECK: fir.call @_FortranAReduceLogical1DimValue
794 subroutine logical2dim(a, id)
795 logical(2), intent(in) :: a(:,:)
796 logical(2), allocatable :: res(:)
798 res = reduce(a, red_log2, 2)
799 res = reduce(a, red_log2_value, 2)
800 end subroutine
802 ! CHECK: fir.call @_FortranAReduceLogical2DimRef
803 ! CHECK: fir.call @_FortranAReduceLogical2DimValue
805 subroutine logical4dim(a, id)
806 logical(4), intent(in) :: a(:,:)
807 logical(4), allocatable :: res(:)
809 res = reduce(a, red_log4, 2)
810 res = reduce(a, red_log4_value, 2)
811 end subroutine
813 ! CHECK: fir.call @_FortranAReduceLogical4DimRef
814 ! CHECK: fir.call @_FortranAReduceLogical4DimValue
816 subroutine logical8dim(a, id)
817 logical(8), intent(in) :: a(:,:)
818 logical(8), allocatable :: res(:)
820 res = reduce(a, red_log8, 2)
821 res = reduce(a, red_log8_value, 2)
822 end subroutine
824 ! CHECK: fir.call @_FortranAReduceLogical8DimRef
825 ! CHECK: fir.call @_FortranAReduceLogical8DimValue
827 subroutine testtypeDim(a)
828 type(t1), intent(in) :: a(:,:)
829 type(t1), allocatable :: res(:)
830 res = reduce(a, red_type, 2)
831 end subroutine
833 ! CHECK: fir.call @_FortranAReduceDerivedTypeDim
835 subroutine char1dim(a)
836 character(1), intent(in) :: a(:, :)
837 character(1), allocatable :: res(:)
838 res = reduce(a, red_char1, 2)
839 end subroutine
841 ! CHECK: fir.call @_FortranAReduceCharacter1Dim
843 subroutine char2dim(a)
844 character(kind=2, len=10), intent(in) :: a(:, :)
845 character(kind=2, len=10), allocatable :: res(:)
846 res = reduce(a, red_char2, 2)
847 end subroutine
849 ! CHECK: fir.call @_FortranAReduceCharacter2Dim
851 subroutine char4dim(a)
852 character(kind=4), intent(in) :: a(:, :)
853 character(kind=4), allocatable :: res(:)
854 res = reduce(a, red_char4, 2)
855 end subroutine
857 ! CHECK: fir.call @_FortranAReduceCharacter4Dim
859 pure function red_char_dyn(a, b)
860 character(*), intent(In) :: a, b
861 character(max(len(a),len(b))) :: red_char_dyn
862 red_char_dyn = max(a, b)
863 end function
865 subroutine charDyn()
866 character(5) :: res
867 character(:), allocatable :: a(:)
868 allocate(character(10)::a(10))
869 res = reduce(a, red_char_dyn)
870 end subroutine
872 ! CHECK: %[[BOX_ELESIZE:.*]] = fir.box_elesize %{{.*}} : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>) -> index
873 ! CHECK: %[[CHRTMP:.*]] = fir.alloca !fir.char<1,?>(%[[BOX_ELESIZE]] : index) {bindc_name = ".chrtmp"}
874 ! CHECK: %[[RESULT:.*]] = fir.convert %[[CHRTMP]] : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<i8>
875 ! CHECK: fir.call @_FortranAReduceChar1(%[[RESULT]], {{.*}})
877 end module