llvm-project/flang/test/Lower/pre-fir-tree01.f90
V Donaldson 518e6f12f3 [flang] Submodules
A submodule is a program unit that may contain the implementions of procedures
declared in an ancestor module or submodule.

Processing for the equivalence groups and variables declared in a submodule
scope is similar to existing processing for the equivalence groups and
variables in module and procedure scopes. However, module and procedure scopes
are tied directly to code in the Pre-FIR Tree (PFT), whereas processing for a
submodule must have access to an ancestor module scope that is guaranteed
to be present in a .mod file, but is not guaranteed to be in the PFT. This
difference is accommodated by tying processing directly to a front end scope.
Function scopes that can be processed on the fly are done that way; the
resulting variable information is never stored. Module and submodule scopes
whose symbol information may be needed during lowering of any number of module
procedures are instead cached on first use, and reused as needed.

These changes are a direct extension of current code. All module and submodule
variables in scope are processed, whether referenced or not. A possible
alternative would be to instead process symbols only when first used. While
this could ultimately be beneficial, such an approach must account for the
presence of equivalence groups. That information is not currently available
for on-the-fly variable processing.

Some additional changes are needed to include submodules in places where
modules must be considered, and to include separate module procedures in
places where other subprogram variants are considered. There is also a fix
for a bug involving the use of variables in an equivalence group in a
namelist group, which also involves scope processing code.
2022-12-13 13:06:07 -08:00

153 lines
3.3 KiB
Fortran

! RUN: bbc -pft-test -o %t %s | FileCheck %s
! Test structure of the Pre-FIR tree
! CHECK: Subroutine foo
subroutine foo()
! CHECK: <<DoConstruct>>
! CHECK: NonLabelDoStmt
do i=1,5
! CHECK: PrintStmt
print *, "hey"
! CHECK: <<DoConstruct>>
! CHECK: NonLabelDoStmt
do j=1,5
! CHECK: PrintStmt
print *, "hello", i, j
! CHECK: EndDoStmt
end do
! CHECK: <<End DoConstruct>>
! CHECK: EndDoStmt
end do
! CHECK: <<End DoConstruct>>
! CHECK: EndSubroutineStmt
end subroutine
! CHECK: End Subroutine foo
! CHECK: BlockData
block data
integer, parameter :: n = 100
integer, dimension(n) :: a, b, c
common /arrays/ a, b, c
end
! CHECK: End BlockData
! CHECK: Module test_mod
module test_mod
interface
! check specification parts are not part of the PFT.
! CHECK-NOT: node
module subroutine dump()
end subroutine
end interface
integer :: xdim
real, allocatable :: pressure(:)
contains
! CHECK: Subroutine foo
subroutine foo()
! CHECK: EndSubroutineStmt
contains
! CHECK: Subroutine subfoo
subroutine subfoo()
! CHECK: EndSubroutineStmt
9 end subroutine
! CHECK: End Subroutine subfoo
! CHECK: Function subfoo2
function subfoo2()
! CHECK: EndFunctionStmt
9 end function
! CHECK: End Function subfoo2
end subroutine
! CHECK: End Subroutine foo
! CHECK: Function foo2
function foo2(i, j)
integer i, j, foo2
! CHECK: AssignmentStmt
foo2 = i + j
! CHECK: EndFunctionStmt
contains
! CHECK: Subroutine subfoo
subroutine subfoo()
! CHECK: EndSubroutineStmt
end subroutine
! CHECK: End Subroutine subfoo
end function
! CHECK: End Function foo2
end module
! CHECK: End Module test_mod
! CHECK: Submodule test_mod_impl: submodule(test_mod) test_mod_impl
submodule (test_mod) test_mod_impl
contains
! CHECK: Subroutine foo
subroutine foo()
! CHECK: EndSubroutineStmt
contains
! CHECK: Subroutine subfoo
subroutine subfoo()
! CHECK: EndSubroutineStmt
end subroutine
! CHECK: End Subroutine subfoo
! CHECK: Function subfoo2
function subfoo2()
! CHECK: EndFunctionStmt
end function
! CHECK: End Function subfoo2
end subroutine
! CHECK: End Subroutine foo
! CHECK: MpSubprogram dump
module procedure dump
! CHECK: FormatStmt
11 format (2E16.4, I6)
! CHECK: <<IfConstruct>>
! CHECK: IfThenStmt
if (xdim > 100) then
! CHECK: PrintStmt
print *, "test: ", xdim
! CHECK: ElseStmt
else
! CHECK: WriteStmt
write (*, 11) "test: ", xdim, pressure
! CHECK: EndIfStmt
end if
! CHECK: <<End IfConstruct>>
end procedure
end submodule
! CHECK: End Submodule test_mod_impl
! CHECK: BlockData
block data named_block
integer i, j, k
common /indexes/ i, j, k
end
! CHECK: End BlockData
! CHECK: Function bar
function bar()
! CHECK: EndFunctionStmt
end function
! CHECK: End Function bar
! Test top level directives
!DIR$ INTEGER=64
! CHECK: CompilerDirective:
! Test nested directive
! CHECK: Subroutine test_directive
subroutine test_directive()
!DIR$ INTEGER=64
! CHECK: CompilerDirective:
end subroutine
! CHECK: EndSubroutine
! CHECK: Program <anonymous>
! check specification parts are not part of the PFT.
! CHECK-NOT: node
use test_mod
real, allocatable :: x(:)
! CHECK: AllocateStmt
allocate(x(foo2(10, 30)))
end
! CHECK: End Program