Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / pre-fir-tree01.f90
blobbc7a06fabe5646d9981fd0df7a34ec4e5e2fc04a
1 ! RUN: bbc -pft-test -o %t %s | FileCheck %s
3 ! Test structure of the Pre-FIR tree
5 ! CHECK: Subroutine foo
6 subroutine foo()
7 ! CHECK: <<DoConstruct>>
8 ! CHECK: NonLabelDoStmt
9 do i=1,5
10 ! CHECK: PrintStmt
11 print *, "hey"
12 ! CHECK: <<DoConstruct>>
13 ! CHECK: NonLabelDoStmt
14 do j=1,5
15 ! CHECK: PrintStmt
16 print *, "hello", i, j
17 ! CHECK: EndDoStmt
18 end do
19 ! CHECK: <<End DoConstruct>>
20 ! CHECK: EndDoStmt
21 end do
22 ! CHECK: <<End DoConstruct>>
23 ! CHECK: EndSubroutineStmt
24 end subroutine
25 ! CHECK: End Subroutine foo
27 ! CHECK: BlockData
28 block data
29 integer, parameter :: n = 100
30 integer, dimension(n) :: a, b, c
31 common /arrays/ a, b, c
32 end
33 ! CHECK: End BlockData
35 ! CHECK: Module test_mod
36 module test_mod
37 interface
38 ! check specification parts are not part of the PFT.
39 ! CHECK-NOT: node
40 module subroutine dump()
41 end subroutine
42 end interface
43 integer :: xdim
44 real, allocatable :: pressure(:)
45 contains
46 ! CHECK: Subroutine foo
47 subroutine foo()
48 ! CHECK: EndSubroutineStmt
49 contains
50 ! CHECK: Subroutine subfoo
51 subroutine subfoo()
52 ! CHECK: EndSubroutineStmt
53 9 end subroutine
54 ! CHECK: End Subroutine subfoo
55 ! CHECK: Function subfoo2
56 function subfoo2()
57 ! CHECK: EndFunctionStmt
58 9 end function
59 ! CHECK: End Function subfoo2
60 end subroutine
61 ! CHECK: End Subroutine foo
63 ! CHECK: Function foo2
64 function foo2(i, j)
65 integer i, j, foo2
66 ! CHECK: AssignmentStmt
67 foo2 = i + j
68 ! CHECK: EndFunctionStmt
69 contains
70 ! CHECK: Subroutine subfoo
71 subroutine subfoo()
72 ! CHECK: EndSubroutineStmt
73 end subroutine
74 ! CHECK: End Subroutine subfoo
75 end function
76 ! CHECK: End Function foo2
77 end module
78 ! CHECK: End Module test_mod
80 ! CHECK: Submodule test_mod_impl: submodule(test_mod) test_mod_impl
81 submodule (test_mod) test_mod_impl
82 contains
83 ! CHECK: Subroutine foo
84 subroutine foo()
85 ! CHECK: EndSubroutineStmt
86 contains
87 ! CHECK: Subroutine subfoo
88 subroutine subfoo()
89 ! CHECK: EndSubroutineStmt
90 end subroutine
91 ! CHECK: End Subroutine subfoo
92 ! CHECK: Function subfoo2
93 function subfoo2()
94 ! CHECK: EndFunctionStmt
95 end function
96 ! CHECK: End Function subfoo2
97 end subroutine
98 ! CHECK: End Subroutine foo
99 ! CHECK: MpSubprogram dump
100 module procedure dump
101 ! CHECK: FormatStmt
102 11 format (2E16.4, I6)
103 ! CHECK: <<IfConstruct>>
104 ! CHECK: IfThenStmt
105 if (xdim > 100) then
106 ! CHECK: PrintStmt
107 print *, "test: ", xdim
108 ! CHECK: ElseStmt
109 else
110 ! CHECK: WriteStmt
111 write (*, 11) "test: ", xdim, pressure
112 ! CHECK: EndIfStmt
113 end if
114 ! CHECK: <<End IfConstruct>>
115 end procedure
116 end submodule
117 ! CHECK: End Submodule test_mod_impl
119 ! CHECK: BlockData
120 block data named_block
121 integer i, j, k
122 common /indexes/ i, j, k
124 ! CHECK: End BlockData
126 ! CHECK: Function bar
127 function bar()
128 ! CHECK: EndFunctionStmt
129 end function
130 ! CHECK: End Function bar
132 ! Test top level directives
133 !DIR$ INTEGER=64
134 ! CHECK: CompilerDirective:
136 ! Test nested directive
137 ! CHECK: Subroutine test_directive
138 subroutine test_directive()
139 !DIR$ INTEGER=64
140 ! CHECK: CompilerDirective:
141 end subroutine
142 ! CHECK: EndSubroutine
144 ! CHECK: Program <anonymous>
145 ! check specification parts are not part of the PFT.
146 ! CHECK-NOT: node
147 use test_mod
148 real, allocatable :: x(:)
149 ! CHECK: AllocateStmt
150 allocate(x(foo2(10, 30)))
152 ! CHECK: End Program