[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / HLFIR / dummy_deallocation.f90
blob9d3c51c843bcc83abe7a9385ede3a3e2e57b52e2
1 ! RUN: bbc -emit-fir -hlfir %s -o - | FileCheck %s
2 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
4 ! Test that the intent(out) allocatable dummy argument
5 ! is not deallocated in entry SUB_B.
7 ! CHECK-LABEL: func.func @_QPsub_a
8 ! CHECK: fir.freemem
10 ! CHECK-LABEL: func.func @_QPsub_b
11 ! CHECK-NOT: fir.freemem
12 SUBROUTINE SUB_A(A)
13 INTEGER, INTENT(out), ALLOCATABLE, DIMENSION (:) :: A
14 RETURN
15 ENTRY SUB_B
16 END SUBROUTINE SUB_A