xref: /llvm-project/flang/test/Lower/HLFIR/concat.f90 (revision 81ea6b7e4b6c374c026dcf1ce742db36de2e56d4)
1! Test lowering of character concatenation to HLFIR
2! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s
3
4subroutine concat(c1, c2, c3)
5  character(*) :: c1, c2, c3
6  c1 = c2 // c3
7end subroutine
8! CHECK-LABEL: func.func @_QPconcat
9! CHECK:  hlfir.declare {{.*}}c1
10! CHECK:  %[[VAL_5:.*]]:2 = fir.unboxchar %{{.*}} : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
11! CHECK:  %[[VAL_6:.*]]:2 = hlfir.declare {{.*}}c2
12! CHECK:  %[[VAL_7:.*]]:2 = fir.unboxchar %{{.*}} : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
13! CHECK:  %[[VAL_8:.*]]:2 = hlfir.declare {{.*}}c3
14! CHECK:  %[[VAL_9:.*]] = arith.addi %[[VAL_5]]#1, %[[VAL_7]]#1 : index
15! CHECK:  %[[VAL_10:.*]] = hlfir.concat %[[VAL_6]]#0, %[[VAL_8]]#0 len %[[VAL_9]] : (!fir.boxchar<1>, !fir.boxchar<1>, index) -> !hlfir.expr<!fir.char<1,?>>
16
17subroutine concat_2(c1, c2, c3)
18  character(*) :: c1(100)
19  character :: c2(100)*10, c3(100)*20
20  c1(1) = c2(1) // c3(1)
21end subroutine
22! CHECK-LABEL: func.func @_QPconcat_2
23! CHECK:  %[[VAL_9:.*]] = arith.constant 10 : index
24! CHECK:  %[[VAL_13:.*]]:2 = hlfir.declare %{{.*}}c2
25! CHECK:  %[[VAL_15:.*]] = arith.constant 20 : index
26! CHECK:  %[[VAL_19:.*]]:2 = hlfir.declare {{.*}}c3
27! CHECK:  %[[VAL_21:.*]] = hlfir.designate %[[VAL_13]]#0 (%{{.*}})  typeparams %[[VAL_9]] : (!fir.ref<!fir.array<100x!fir.char<1,10>>>, index, index) -> !fir.ref<!fir.char<1,10>>
28! CHECK:  %[[VAL_23:.*]] = hlfir.designate %[[VAL_19]]#0 (%{{.*}})  typeparams %[[VAL_15]] : (!fir.ref<!fir.array<100x!fir.char<1,20>>>, index, index) -> !fir.ref<!fir.char<1,20>>
29! CHECK:  %[[VAL_24:.*]] = arith.addi %[[VAL_9]], %[[VAL_15]] : index
30! CHECK:  %[[VAL_25:.*]] = hlfir.concat %[[VAL_21]], %[[VAL_23]] len %[[VAL_24]] : (!fir.ref<!fir.char<1,10>>, !fir.ref<!fir.char<1,20>>, index) -> !hlfir.expr<!fir.char<1,30>>
31
32subroutine concat3(c1, c2, c3, c4)
33  character(*) :: c1, c2, c3, c4
34  c1 = c2 // c3 // c4
35end subroutine
36! CHECK-LABEL: func.func @_QPconcat3
37! CHECK:  hlfir.declare {{.*}}c1
38! CHECK:  %[[VAL_5:.*]]:2 = fir.unboxchar %{{.*}}
39! CHECK:  %[[VAL_6:.*]]:2 = hlfir.declare {{.*}}c2
40! CHECK:  %[[VAL_7:.*]]:2 = fir.unboxchar %{{.*}}
41! CHECK:  %[[VAL_8:.*]]:2 = hlfir.declare {{.*}}c3
42! CHECK:  %[[VAL_9:.*]]:2 = fir.unboxchar %{{.*}}
43! CHECK:  %[[VAL_10:.*]]:2 = hlfir.declare {{.*}}c4
44! CHECK:  %[[VAL_11:.*]] = arith.addi %[[VAL_5]]#1, %[[VAL_7]]#1 : index
45! CHECK:  %[[VAL_12:.*]] = hlfir.concat %[[VAL_6]]#0, %[[VAL_8]]#0 len %[[VAL_11]] : (!fir.boxchar<1>, !fir.boxchar<1>, index) -> !hlfir.expr<!fir.char<1,?>>
46! CHECK:  %[[VAL_13:.*]] = arith.addi %[[VAL_11]], %[[VAL_9]]#1 : index
47! CHECK:  %[[VAL_14:.*]] = hlfir.concat %[[VAL_12]], %[[VAL_10]]#0 len %[[VAL_13]] : (!hlfir.expr<!fir.char<1,?>>, !fir.boxchar<1>, index) -> !hlfir.expr<!fir.char<1,?>>
48