Files
llvm/flang/test/Lower/array-constructor-1.f90
Slava Zakharin be5747e516 [flang] Fixed global name creation for literal constants.
The global names were created using a hash based on the address
of std::vector::data address. Since the memory may be reused
by different std::vector's, this may cause non-equivalent
constant expressions to map to the same name. This is what is happening
in the modified flang/test/Lower/constant-literal-mangling.f90 test.

I changed the name creation to use a map between the constant expressions
and corresponding unique names. The uniquing is done using a name counter
in FirConverter. The effect of this change is that the equivalent
constant expressions are now mapped to the same global, and the naming
is "stable" (i.e. it does not change from compilation to compilation).

Though, the issue is not HLFIR specific it was affecting several tests
when using HLFIR lowering.

Differential Revision: https://reviews.llvm.org/D150380
2023-05-12 13:40:22 -07:00

47 lines
1.3 KiB
Fortran

! RUN: bbc -o - %s | FileCheck %s
module units
integer, parameter :: preconnected_unit(3) = [0, 5, 6]
contains
! CHECK-LABEL: _QMunitsPis_preconnected_unit
logical function is_preconnected_unit(u)
! CHECK: [[units_ssa:%[0-9]+]] = fir.address_of(@_QMunitsECpreconnected_unit) : !fir.ref<!fir.array<3xi32>>
integer :: u
integer :: i
is_preconnected_unit = .true.
do i = lbound(preconnected_unit,1), ubound(preconnected_unit,1)
! CHECK: fir.coordinate_of [[units_ssa]]
if (preconnected_unit(i) == u) return
end do
is_preconnected_unit = .false.
end function
end module units
! CHECK-LABEL: _QPcheck_units
subroutine check_units
use units
do i=-1,8
if (is_preconnected_unit(i)) print*, i
enddo
end
! CHECK-LABEL: _QPzero
subroutine zero
complex, parameter :: a(0) = [(((k,k=1,10),j=-2,2,-1),i=2,-2,-2)]
complex, parameter :: b(0) = [(7,i=3,-3)]
! CHECK: fir.address_of(@_QQro.0xz4.null.0) : !fir.ref<!fir.array<0x!fir.complex<4>>>
! CHECK-NOT: _QQro
print*, '>', a, '<'
print*, '>', b, '<'
end
! CHECK-LABEL: _QQmain
program prog
call check_units
call zero
end
! CHECK: fir.global internal @_QFzeroECa constant : !fir.array<0x!fir.complex<4>>
! CHECK: %0 = fir.undefined !fir.array<0x!fir.complex<4>>
! CHECK: fir.has_value %0 : !fir.array<0x!fir.complex<4>>