llvm-project/flang/test/Lower/entry-statement-init.f90
jeanPerier 22d9726593
[flang] do not finalize or initialize unused entry dummy (#125482)
Dummy arguments from other entry statement that are not live in the current entry have no backing storage, user code referring to them is not allowed to be reached. The compiler was generating initialization/destruction code for them when INTENT(OUT), causing undefined behaviors.
2025-02-03 18:09:01 +01:00

27 lines
585 B
Fortran

! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
! Test initialization and finalizations of dummy arguments in entry statements.
module m
type t
end type
contains
subroutine test1(x)
class(t), intent(out) :: x
entry test1_entry()
end subroutine
subroutine test2(x)
class(t), intent(out) :: x
entry test2_entry(x)
end subroutine
end module
! CHECK-LABEL: func.func @_QMmPtest1_entry(
! CHECK-NOT: Destroy
! CHECK-NOT: Initialize
! CHECK: return
! CHECK-LABEL: func.func @_QMmPtest2_entry(
! CHECK: Destroy
! CHECK: Initialize
! CHECK: return