xref: /llvm-project/flang/test/Lower/read-write-buffer.f90 (revision f35f863a88f83332bef9605ef4cfe4f05c066efb)
1! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
2
3! Test that we are passing the correct length when using character array as
4! Format (Fortran 2018 12.6.2.2 point 3)
5! CHECK-LABEL: func @_QPtest_array_format
6subroutine test_array_format
7  ! CHECK-DAG: %[[c2:.*]] = arith.constant 2 : index
8  ! CHECK-DAG: %[[c10:.*]] = arith.constant 10 : index
9  ! CHECK-DAG: %[[mem:.*]] = fir.alloca !fir.array<2x!fir.char<1,10>>
10  character(10) :: array(2)
11  array(1) ="(15HThis i"
12  array(2) ="s a test.)"
13  ! CHECK: %[[shape:.*]] = fir.shape %c2{{.*}} (index) -> !fir.shape<1>
14  ! CHECK: %[[fmtBox:.*]] = fir.embox %[[mem]](%[[shape]]) : (!fir.ref<!fir.array<2x!fir.char<1,10>>>, !fir.shape<1>) -> !fir.box<!fir.array<2x!fir.char<1,10>>>
15  ! CHECK: %[[fmtArg:.*]] = fir.zero_bits !fir.ref<i8>
16  ! CHECK: %[[fmtLenArg:.*]] = fir.zero_bits i64
17  ! CHECK: %[[fmtDesc:.*]] = fir.convert %[[fmtBox]] : (!fir.box<!fir.array<2x!fir.char<1,10>>>) -> !fir.box<none>
18  ! CHECK: fir.call @_FortranAioBeginExternalFormattedOutput(%[[fmtArg]], %[[fmtLenArg]], %[[fmtDesc]], {{.*}})
19  write(*, array)
20end subroutine
21
22! A test to check the buffer and it's length.
23! CHECK-LABEL: @_QPsome
24subroutine some()
25  character(LEN=255):: buffer
26  character(LEN=255):: greeting
2710 format (A255)
28  ! CHECK:  fir.address_of(@_QQclX636F6D70696C6572) :
29  write (buffer, 10) "compiler"
30  read (buffer, 10) greeting
31end
32! CHECK-LABEL: fir.global linkonce @_QQclX636F6D70696C6572
33! CHECK: %[[lit:.*]] = fir.string_lit "compiler"(8) : !fir.char<1,8>
34! CHECK: fir.has_value %[[lit]] : !fir.char<1,8>
35! CHECK: }
36