[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Lower / attributes.f90
blob413024d0a449931c3a43365ad174f970622f6cd9
1 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
3 ! Test propagation of Fortran attributes to FIR.
6 ! CHECK-LABEL: func @_QPfoo1(
7 ! CHECK-SAME: %arg0: !fir.ref<f32> {fir.bindc_name = "x", fir.optional},
8 ! CHECK-SAME: %arg1: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "y", fir.optional},
9 ! CHECK-SAME: %arg2: !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> {fir.bindc_name = "i", fir.optional},
10 ! CHECK-SAME: %arg3: !fir.boxchar<1> {fir.bindc_name = "c", fir.optional}
11 subroutine foo1(x, y, i, c)
12 real, optional :: x, y(:)
13 integer, allocatable, optional :: i(:)
14 character, optional :: c
15 end subroutine
17 ! CHECK-LABEL: func @_QPfoo2(
18 ! CHECK-SAME: %arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "x", fir.contiguous},
19 ! CHECK-SAME: %arg1: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>> {fir.bindc_name = "i", fir.contiguous}
20 subroutine foo2(x, i)
21 real, contiguous :: x(:)
22 integer, pointer, contiguous :: i(:)
23 end subroutine
25 ! CHECK-LABEL: func @_QPfoo3
26 ! CHECK-SAME: %arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "x", fir.contiguous, fir.optional}
27 subroutine foo3(x)
28 real, optional, contiguous :: x(:)
29 end subroutine
31 ! CHECK-LABEL: func @_QPfoo4
32 ! CHECK-SAME: %arg0: !fir.ref<f32> {fir.bindc_name = "x", fir.target}
33 ! CHECK-SAME: %arg1: !fir.ref<f32> {fir.asynchronous, fir.bindc_name = "y"}
34 subroutine foo4(x, y)
35 real, target :: x
36 real, asynchronous :: y
37 end subroutine