xref: /llvm-project/flang/test/Lower/HLFIR/bindc-assumed-length.f90 (revision 5b6f3fcb48e9476c8780f7c5f4abb8f2e348fc0d)
1! Test that assumed length character scalars and explicit shape arrays are passed via
2! CFI descriptor (fir.box) in BIND(C) procedures. They are passed only by address
3! and length  in non BIND(C) procedures. See Fortran 2018 standard 18.3.6 point 2(5).
4! RUN: bbc -hlfir -emit-fir -o - %s 2>&1 | FileCheck %s
5
6module bindcchar
7contains
8! CHECK-LABEL: func.func @bindc(
9! CHECK-SAME: %{{[^:]*}}: !fir.box<!fir.char<1,?>>
10! CHECK-SAME: %{{[^:]*}}: !fir.box<!fir.array<100x!fir.char<1,?>>>
11subroutine bindc(c1, c3) bind(c)
12  character(*) ::  c1, c3(100)
13 print *, c1(1:3), c3(5)(1:3)
14end subroutine
15
16! CHECK-LABEL:  func.func @bindc_optional(
17! CHECK-SAME: %{{[^:]*}}: !fir.box<!fir.char<1,?>>
18! CHECK-SAME: %{{[^:]*}}: !fir.box<!fir.array<100x!fir.char<1,?>>>
19subroutine bindc_optional(c1, c3) bind(c)
20  character(*), optional ::  c1, c3(100)
21 print *, c1(1:3), c3(5)(1:3)
22end subroutine
23
24! CHECK-LABEL:  func.func @_QMbindccharPnot_bindc(
25! CHECK-SAME: %{{[^:]*}}: !fir.boxchar<1>
26! CHECK-SAME: %{{[^:]*}}: !fir.boxchar<1>
27subroutine not_bindc(c1, c3)
28  character(*) :: c1,  c3(100)
29  call bindc(c1, c3)
30  call bindc_optional(c1, c3)
31end subroutine
32
33! CHECK-LABEL:  func.func @_QMbindccharPnot_bindc_optional(
34! CHECK-SAME: %{{[^:]*}}: !fir.boxchar<1>
35! CHECK-SAME: %{{[^:]*}}: !fir.boxchar<1>
36subroutine not_bindc_optional(c1, c3)
37  character(*), optional :: c1,  c3(100)
38  call bindc(c1, c3)
39  call bindc_optional(c1, c3)
40end subroutine
41end module
42