[libc] Fix the GPU build when building inside the NATIVE project (#118573)
[llvm-project.git] / flang / test / Lower / dummy-argument-optional.f90
bloba6749b6528e81be46a39c3b4ae13105a22645071
1 ! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
2 ! RUN: %flang_fc1 -fdefault-integer-8 -emit-fir -flang-deprecated-no-hlfir %s -o - | FileCheck %s
4 ! Test OPTIONAL lowering on caller/callee and PRESENT intrinsic.
5 module opt
6 implicit none
7 type t
8 real, allocatable :: p(:)
9 end type
10 contains
12 ! Test simple scalar optional
13 ! CHECK-LABEL: func @_QMoptPintrinsic_scalar(
14 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<f32> {fir.bindc_name = "x", fir.optional}) {
15 subroutine intrinsic_scalar(x)
16 real, optional :: x
17 ! CHECK: fir.is_present %[[arg0]] : (!fir.ref<f32>) -> i1
18 print *, present(x)
19 end subroutine
20 ! CHECK-LABEL: @_QMoptPcall_intrinsic_scalar()
21 subroutine call_intrinsic_scalar()
22 ! CHECK: %[[x:.*]] = fir.alloca f32
23 real :: x
24 ! CHECK: fir.call @_QMoptPintrinsic_scalar(%[[x]]) {{.*}}: (!fir.ref<f32>) -> ()
25 call intrinsic_scalar(x)
26 ! CHECK: %[[absent:.*]] = fir.absent !fir.ref<f32>
27 ! CHECK: fir.call @_QMoptPintrinsic_scalar(%[[absent]]) {{.*}}: (!fir.ref<f32>) -> ()
28 call intrinsic_scalar()
29 end subroutine
31 ! Test explicit shape array optional
32 ! CHECK-LABEL: func @_QMoptPintrinsic_f77_array(
33 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "x", fir.optional}) {
34 subroutine intrinsic_f77_array(x)
35 real, optional :: x(100)
36 ! CHECK: fir.is_present %[[arg0]] : (!fir.ref<!fir.array<100xf32>>) -> i1
37 print *, present(x)
38 end subroutine
39 ! CHECK-LABEL: func @_QMoptPcall_intrinsic_f77_array()
40 subroutine call_intrinsic_f77_array()
41 ! CHECK: %[[x:.*]] = fir.alloca !fir.array<100xf32>
42 real :: x(100)
43 ! CHECK: fir.call @_QMoptPintrinsic_f77_array(%[[x]]) {{.*}}: (!fir.ref<!fir.array<100xf32>>) -> ()
44 call intrinsic_f77_array(x)
45 ! CHECK: %[[absent:.*]] = fir.absent !fir.ref<!fir.array<100xf32>>
46 ! CHECK: fir.call @_QMoptPintrinsic_f77_array(%[[absent]]) {{.*}}: (!fir.ref<!fir.array<100xf32>>) -> ()
47 call intrinsic_f77_array()
48 end subroutine
50 ! Test optional character scalar
51 ! CHECK-LABEL: func @_QMoptPcharacter_scalar(
52 ! CHECK-SAME: %[[arg0:.*]]: !fir.boxchar<1> {fir.bindc_name = "x", fir.optional}) {
53 subroutine character_scalar(x)
54 ! CHECK: %[[unboxed:.*]]:2 = fir.unboxchar %[[arg0]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
55 ! CHECK: %[[ref:.*]] = fir.convert %[[unboxed]]#0 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<!fir.char<1,10>>
56 character(10), optional :: x
57 ! CHECK: fir.is_present %[[ref]] : (!fir.ref<!fir.char<1,10>>) -> i1
58 print *, present(x)
59 end subroutine
60 ! CHECK-LABEL: func @_QMoptPcall_character_scalar()
61 subroutine call_character_scalar()
62 ! CHECK: %[[addr:.*]] = fir.alloca !fir.char<1,10>
63 character(10) :: x
64 ! CHECK: %[[x:.*]] = fir.emboxchar %[[addr]], {{.*}}
65 ! CHECK: fir.call @_QMoptPcharacter_scalar(%[[x]]) {{.*}}: (!fir.boxchar<1>) -> ()
66 call character_scalar(x)
67 ! CHECK: %[[absent:.*]] = fir.absent !fir.boxchar<1>
68 ! CHECK: fir.call @_QMoptPcharacter_scalar(%[[absent]]) {{.*}}: (!fir.boxchar<1>) -> ()
69 call character_scalar()
70 end subroutine
72 ! Test optional character function
73 ! CHECK-LABEL: func @_QMoptPchar_proc(
74 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.char<1,3>>,
75 character(len=3) function char_proc(i)
76 integer :: i
77 char_proc = "XYZ"
78 end function
79 ! CHECK-LABEL: func @_QMoptPuse_char_proc(
80 ! CHECK-SAME: %[[arg0:.*]]: tuple<!fir.boxproc<() -> ()>, i64> {fir.char_proc},
81 subroutine use_char_proc(f, c)
82 optional :: f
83 interface
84 character(len=3) function f(i)
85 integer :: i
86 end function
87 end interface
88 character(len=3) :: c
89 ! CHECK: %[[boxProc:.*]] = fir.extract_value %[[arg0]], [0 : index] : (tuple<!fir.boxproc<() -> ()>, i64>) -> !fir.boxproc<() -> ()>
90 ! CHECK: %[[procAddr:.*]] = fir.box_addr %[[boxProc]] : (!fir.boxproc<() -> ()>) -> (() -> ())
91 ! CHECK: %{{.*}} = fir.is_present %[[procAddr]] : (() -> ()) -> i1
92 if (present(f)) then
93 c = f(0)
94 else
95 c = "ABC"
96 end if
97 end subroutine
98 ! CHECK-LABEL: func @_QMoptPcall_use_char_proc(
99 subroutine call_use_char_proc()
100 character(len=3) :: c
101 ! CHECK: %[[boxProc:.*]] = fir.absent !fir.boxproc<() -> ()>
102 ! CHECK: %[[undef:.*]] = fir.undefined index
103 ! CHECK: %[[charLen:.*]] = fir.convert %[[undef]] : (index) -> i64
104 ! CHECK: %[[tuple:.*]] = fir.undefined tuple<!fir.boxproc<() -> ()>, i64>
105 ! CHECK: %[[tuple2:.*]] = fir.insert_value %[[tuple]], %[[boxProc]], [0 : index] : (tuple<!fir.boxproc<() -> ()>, i64>, !fir.boxproc<() -> ()>) -> tuple<!fir.boxproc<() -> ()>, i64>
106 ! CHECK: %[[tuple3:.*]] = fir.insert_value %[[tuple2]], %[[charLen]], [1 : index] : (tuple<!fir.boxproc<() -> ()>, i64>, i64) -> tuple<!fir.boxproc<() -> ()>, i64>
107 ! CHECK: fir.call @_QMoptPuse_char_proc(%[[tuple3]], %{{.*}}){{.*}} : (tuple<!fir.boxproc<() -> ()>, i64>, !fir.boxchar<1>) -> ()
108 call use_char_proc(c=c)
109 ! CHECK: %[[funcAddr:.*]] = fir.address_of(@_QMoptPchar_proc) : (!fir.ref<!fir.char<1,3>>, index, {{.*}}) -> !fir.boxchar<1>
110 ! CHECK: %[[c3:.*]] = arith.constant 3 : i64
111 ! CHECK: %[[boxProc2:.*]] = fir.emboxproc %[[funcAddr]] : ((!fir.ref<!fir.char<1,3>>, index, {{.*}}) -> !fir.boxchar<1>) -> !fir.boxproc<() -> ()>
112 ! CHECK: %[[tuple4:.*]] = fir.undefined tuple<!fir.boxproc<() -> ()>, i64>
113 ! CHECK: %[[tuple5:.*]] = fir.insert_value %[[tuple4]], %[[boxProc2]], [0 : index] : (tuple<!fir.boxproc<() -> ()>, i64>, !fir.boxproc<() -> ()>) -> tuple<!fir.boxproc<() -> ()>, i64>
114 ! CHECK: %[[tuple6:.*]] = fir.insert_value %[[tuple5]], %[[c3]], [1 : index] : (tuple<!fir.boxproc<() -> ()>, i64>, i64) -> tuple<!fir.boxproc<() -> ()>, i64>
115 ! CHECK: fir.call @_QMoptPuse_char_proc(%[[tuple6]], {{.*}}){{.*}} : (tuple<!fir.boxproc<() -> ()>, i64>, !fir.boxchar<1>) -> ()
116 call use_char_proc(char_proc, c)
117 end subroutine
119 ! Test optional assumed shape
120 ! CHECK-LABEL: func @_QMoptPassumed_shape(
121 ! CHECK-SAME: %[[arg0:.*]]: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "x", fir.optional}) {
122 subroutine assumed_shape(x)
123 real, optional :: x(:)
124 ! CHECK: fir.is_present %[[arg0]] : (!fir.box<!fir.array<?xf32>>) -> i1
125 print *, present(x)
126 end subroutine
127 ! CHECK: func @_QMoptPcall_assumed_shape()
128 subroutine call_assumed_shape()
129 ! CHECK: %[[addr:.*]] = fir.alloca !fir.array<100xf32>
130 real :: x(100)
131 ! CHECK: %[[embox:.*]] = fir.embox %[[addr]]
132 ! CHECK: %[[x:.*]] = fir.convert %[[embox]] : (!fir.box<!fir.array<100xf32>>) -> !fir.box<!fir.array<?xf32>>
133 ! CHECK: fir.call @_QMoptPassumed_shape(%[[x]]) {{.*}}: (!fir.box<!fir.array<?xf32>>) -> ()
134 call assumed_shape(x)
135 ! CHECK: %[[absent:.*]] = fir.absent !fir.box<!fir.array<?xf32>>
136 ! CHECK: fir.call @_QMoptPassumed_shape(%[[absent]]) {{.*}}: (!fir.box<!fir.array<?xf32>>) -> ()
137 call assumed_shape()
138 end subroutine
140 ! Test optional allocatable
141 ! CHECK: func @_QMoptPallocatable_array(
142 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>> {fir.bindc_name = "x", fir.optional}) {
143 subroutine allocatable_array(x)
144 real, allocatable, optional :: x(:)
145 ! CHECK: fir.is_present %[[arg0]] : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> i1
146 print *, present(x)
147 end subroutine
148 ! CHECK: func @_QMoptPcall_allocatable_array()
149 subroutine call_allocatable_array()
150 ! CHECK: %[[x:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xf32>>>
151 real, allocatable :: x(:)
152 ! CHECK: fir.call @_QMoptPallocatable_array(%[[x]]) {{.*}}: (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> ()
153 call allocatable_array(x)
154 ! CHECK: %[[absent:.*]] = fir.absent !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
155 ! CHECK: fir.call @_QMoptPallocatable_array(%[[absent]]) {{.*}}: (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> ()
156 call allocatable_array()
157 end subroutine
159 ! CHECK: func @_QMoptPallocatable_to_assumed_optional_array(
160 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>{{.*}}) {
161 subroutine allocatable_to_assumed_optional_array(x)
162 real, allocatable :: x(:)
164 ! CHECK: %[[xboxload:.*]] = fir.load %[[arg0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
165 ! CHECK: %[[xptr:.*]] = fir.box_addr %[[xboxload]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>) -> !fir.heap<!fir.array<?xf32>>
166 ! CHECK: %[[xaddr:.*]] = fir.convert %[[xptr]] : (!fir.heap<!fir.array<?xf32>>) -> i64
167 ! CHECK: %[[isAlloc:.*]] = arith.cmpi ne, %[[xaddr]], %c0{{.*}} : i64
168 ! CHECK: %[[absent:.*]] = fir.absent !fir.box<!fir.array<?xf32>>
169 ! CHECK: %[[embox:.*]] = fir.embox %{{.*}}
170 ! CHECK: %[[actual:.*]] = arith.select %[[isAlloc]], %[[embox]], %[[absent]] : !fir.box<!fir.array<?xf32>>
171 ! CHECK: fir.call @_QMoptPassumed_shape(%[[actual]]) {{.*}}: (!fir.box<!fir.array<?xf32>>) -> ()
172 call assumed_shape(x)
173 end subroutine
175 ! CHECK-LABEL: func @_QMoptPalloc_component_to_optional_assumed_shape(
176 subroutine alloc_component_to_optional_assumed_shape(x)
177 type(t) :: x(100)
178 ! CHECK-DAG: %[[isAlloc:.*]] = arith.cmpi ne
179 ! CHECK-DAG: %[[absent:.*]] = fir.absent !fir.box<!fir.array<?xf32>>
180 ! CHECK: %[[select:.*]] = arith.select %[[isAlloc]], %{{.*}}, %[[absent]] : !fir.box<!fir.array<?xf32>>
181 ! CHECK: fir.call @_QMoptPassumed_shape(%[[select]])
182 call assumed_shape(x(55)%p)
183 end subroutine
185 ! CHECK-LABEL: func @_QMoptPalloc_component_eval_only_once(
186 subroutine alloc_component_eval_only_once(x)
187 integer, external :: ifoo
188 type(t) :: x(100)
189 ! Verify that the index in the component reference are not evaluated twice
190 ! because if the optional handling logic.
191 ! CHECK: fir.call @_QPifoo()
192 ! CHECK-NOT: fir.call @_QPifoo()
193 call assumed_shape(x(ifoo())%p)
194 end subroutine
196 ! CHECK-LABEL: func @_QMoptPnull_as_optional() {
197 subroutine null_as_optional
198 ! CHECK: %[[null_ptr:.*]] = fir.alloca !fir.box<!fir.ptr<none>>
199 ! CHECK: %[[null:.*]] = fir.zero_bits !fir.ptr<none>
200 ! CHECK: %[[null_box:.*]] = fir.embox %[[null]] : (!fir.ptr<none>) -> !fir.box<!fir.ptr<none>>
201 ! CHECK: fir.store %[[null_box]] to %[[null_ptr]] : !fir.ref<!fir.box<!fir.ptr<none>>>
202 ! CHECK: fir.call @_QMoptPassumed_shape(%{{.*}}) {{.*}}: (!fir.box<!fir.array<?xf32>>) -> ()
203 call assumed_shape(null())
204 end subroutine null_as_optional
206 end module