mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-17 17:16:44 +00:00

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.
27 lines
585 B
Fortran
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
|