File: pre-fir-tree01.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (152 lines) | stat: -rw-r--r-- 3,414 bytes parent folder | download | duplicates (14)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
! 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