File: acc-branch.f90

package info (click to toggle)
llvm-toolchain-13 1%3A13.0.1-11
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 1,418,840 kB
  • sloc: cpp: 5,290,826; ansic: 996,570; asm: 544,593; python: 188,212; objc: 72,027; lisp: 30,291; f90: 25,395; sh: 24,898; javascript: 9,780; pascal: 9,398; perl: 7,484; ml: 5,432; awk: 3,523; makefile: 2,913; xml: 953; cs: 573; fortran: 539
file content (173 lines) | stat: -rw-r--r-- 3,664 bytes parent folder | download | duplicates (3)
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
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
! RUN: %S/../test_errors.sh %s %t %flang -fopenacc
! REQUIRES: shell

! Check OpenACC restruction in branch in and out of some construct
!
program openacc_clause_validity

  implicit none

  integer :: i, j, k
  integer :: N = 256
  real(8) :: a(256)

  !$acc parallel
  !$acc loop
  do i = 1, N
    a(i) = 3.14
    !ERROR: RETURN statement is not allowed in a PARALLEL construct
    return
  end do
  !$acc end parallel

  !$acc parallel
  !$acc loop
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      exit
    end if
  end do
  !$acc end parallel

  ! Exit branches out of parallel construct, not attached to an OpenACC parallel construct.
  name1: do k=1, N
  !$acc parallel
  !$acc loop
  outer: do i=1, N
    inner: do j=1, N
      ifname: if (j == 2) then
        ! These are allowed.
        exit
        exit inner
        exit outer
        !ERROR: EXIT to construct 'name1' outside of PARALLEL construct is not allowed
        exit name1
        ! Exit to construct other than loops.
        exit ifname
      end if ifname
    end do inner
  end do outer
  !$acc end parallel
  end do name1

  ! Exit branches out of parallel construct, attached to an OpenACC parallel construct.
  thisblk: BLOCK
    fortname: if (.true.) then
      name1: do k = 1, N
        !$acc parallel
        !ERROR: EXIT to construct 'fortname' outside of PARALLEL construct is not allowed
        exit fortname
        !$acc loop
          do i = 1, N
            a(i) = 3.14
            if(i == N-1) THEN
              !ERROR: EXIT to construct 'name1' outside of PARALLEL construct is not allowed
              exit name1
            end if
          end do

          loop2: do i = 1, N
            a(i) = 3.33
            !ERROR: EXIT to construct 'thisblk' outside of PARALLEL construct is not allowed
            exit thisblk
          end do loop2
        !$acc end parallel
      end do name1
    end if fortname
  end BLOCK thisblk

  !Exit branches inside OpenACC construct.
  !$acc parallel
  !$acc loop
  do i = 1, N
    a(i) = 3.14
    ifname: if (i == 2) then
      ! This is allowed.
      exit ifname
    end if ifname
  end do
  !$acc end parallel

  !$acc parallel
  !$acc loop
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      !ERROR: STOP statement is not allowed in a PARALLEL construct
      stop 999
    end if
  end do
  !$acc end parallel

  !$acc kernels
  do i = 1, N
    a(i) = 3.14
    !ERROR: RETURN statement is not allowed in a KERNELS construct
    return
  end do
  !$acc end kernels

  !$acc kernels
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      exit
    end if
  end do
  !$acc end kernels

  !$acc kernels
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      !ERROR: STOP statement is not allowed in a KERNELS construct
      stop 999
    end if
  end do
  !$acc end kernels

  !$acc serial
  do i = 1, N
    a(i) = 3.14
    !ERROR: RETURN statement is not allowed in a SERIAL construct
    return
  end do
  !$acc end serial

  !$acc serial
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      exit
    end if
  end do
  !$acc end serial

  name2: do k=1, N
  !$acc serial
  do i = 1, N
    ifname: if (.true.) then
      print *, "LGTM"
    a(i) = 3.14
    if(i == N-1) THEN
        !ERROR: EXIT to construct 'name2' outside of SERIAL construct is not allowed
        exit name2
        exit ifname
      end if
    end if ifname
    end do
  !$acc end serial
  end do name2

  !$acc serial
  do i = 1, N
    a(i) = 3.14
    if(i == N-1) THEN
      !ERROR: STOP statement is not allowed in a SERIAL construct
      stop 999
    end if
  end do
  !$acc end serial

end program openacc_clause_validity