[lldb] fix fd leak during lldb testsuite (#118093)
[llvm-project.git] / flang / test / Lower / array-constructor-1.f90
bloba766357f588a65e0044a4793db2bea81433ee5a4
1 ! RUN: bbc -hlfir=false -o - %s | FileCheck %s
3 module units
4 integer, parameter :: preconnected_unit(3) = [0, 5, 6]
5 contains
6 ! CHECK-LABEL: _QMunitsPis_preconnected_unit
7 logical function is_preconnected_unit(u)
8 ! CHECK: [[units_ssa:%[0-9]+]] = fir.address_of(@_QMunitsECpreconnected_unit) : !fir.ref<!fir.array<3xi32>>
9 integer :: u
10 integer :: i
11 is_preconnected_unit = .true.
12 do i = lbound(preconnected_unit,1), ubound(preconnected_unit,1)
13 ! CHECK: fir.coordinate_of [[units_ssa]]
14 if (preconnected_unit(i) == u) return
15 end do
16 is_preconnected_unit = .false.
17 end function
18 end module units
20 ! CHECK-LABEL: _QPcheck_units
21 subroutine check_units
22 use units
23 do i=-1,8
24 if (is_preconnected_unit(i)) print*, i
25 enddo
26 end
28 ! CHECK-LABEL: _QPzero
29 subroutine zero
30 complex, parameter :: a(0) = [(((k,k=1,10),j=-2,2,-1),i=2,-2,-2)]
31 complex, parameter :: b(0) = [(7,i=3,-3)]
32 ! CHECK: fir.address_of(@_QQro.0xz4.null.0) : !fir.ref<!fir.array<0xcomplex<f32>>>
33 ! CHECK-NOT: _QQro
34 print*, '>', a, '<'
35 print*, '>', b, '<'
36 end
38 ! CHECK-LABEL: _QQmain
39 program prog
40 call check_units
41 call zero
42 end
44 ! CHECK: fir.global internal @_QFzeroECa constant : !fir.array<0xcomplex<f32>>
45 ! CHECK: %0 = fir.undefined !fir.array<0xcomplex<f32>>
46 ! CHECK: fir.has_value %0 : !fir.array<0xcomplex<f32>>