File: acc-serial.f90

package info (click to toggle)
llvm-toolchain-17 1%3A17.0.6-22
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 1,799,624 kB
  • sloc: cpp: 6,428,607; ansic: 1,383,196; asm: 793,408; python: 223,504; objc: 75,364; f90: 60,502; lisp: 33,869; pascal: 15,282; sh: 9,684; perl: 7,453; ml: 4,937; awk: 3,523; makefile: 2,889; javascript: 2,149; xml: 888; fortran: 619; cs: 573
file content (169 lines) | stat: -rw-r--r-- 3,774 bytes parent folder | download | duplicates (8)
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
! RUN: %python %S/../test_errors.py %s %flang -fopenacc

! Check OpenACC clause validity for the following construct and directive:
!   2.5.2 Serial

program openacc_serial_validity

  implicit none

  type atype
    real(8), dimension(10) :: arr
    real(8) :: s
  end type atype

  integer :: i, j, b, gang_size, vector_size, worker_size
  integer, parameter :: N = 256
  integer, dimension(N) :: c
  logical, dimension(N) :: d, e
  integer :: async1
  integer :: wait1, wait2
  real :: reduction_r
  logical :: reduction_l
  real(8), dimension(N, N) :: aa, bb, cc
  real(8), dimension(:), allocatable :: dd
  real(8), pointer :: p
  logical :: ifCondition = .TRUE.
  type(atype) :: t
  type(atype), dimension(10) :: ta

  real(8), dimension(N) :: a, f, g, h

  !$acc serial
  !ERROR: Directive SET may not be called within a compute region
  !$acc set default_async(i)
  !$acc end serial

  !$acc serial
  !$acc loop
  do i = 1, N
    !ERROR: Directive SET may not be called within a compute region
    !$acc set default_async(i)
    a(i) = 3.14
  end do
  !$acc end serial

  !$acc serial
  !$acc end serial

  !$acc serial async
  !$acc end serial

  !$acc serial async(1)
  !$acc end serial

  !ERROR: At most one ASYNC clause can appear on the SERIAL directive
  !$acc serial async(1) async(2)
  !$acc end serial

  !$acc serial async(async1)
  !$acc end serial

  !$acc serial wait
  !$acc end serial

  !$acc serial wait(1)
  !$acc end serial

  !$acc serial wait(wait1)
  !$acc end serial

  !$acc serial wait(1,2)
  !$acc end serial

  !$acc serial wait(wait1, wait2)
  !$acc end serial

  !$acc serial wait(wait1) wait(wait2)
  !$acc end serial

  !ERROR: NUM_GANGS clause is not allowed on the SERIAL directive
  !$acc serial num_gangs(8)
  !$acc end serial

  !ERROR: NUM_WORKERS clause is not allowed on the SERIAL directive
  !$acc serial num_workers(8)
  !$acc end serial

  !ERROR: VECTOR_LENGTH clause is not allowed on the SERIAL directive
  !$acc serial vector_length(128)
  !$acc end serial

  !$acc serial if(.true.)
  !$acc end serial

  !ERROR: At most one IF clause can appear on the SERIAL directive
  !$acc serial if(.true.) if(ifCondition)
  !$acc end serial

  !$acc serial if(ifCondition)
  !$acc end serial

  !$acc serial self
  !$acc end serial

  !$acc serial self(.true.)
  !$acc end serial

  !$acc serial self(ifCondition)
  !$acc end serial

  !$acc serial reduction(.neqv.: reduction_l)
  !$acc loop reduction(.neqv.: reduction_l)
  do i = 1, N
    reduction_l = d(i) .neqv. e(i)
  end do
  !$acc end serial

  !$acc serial copy(aa) copyin(bb) copyout(cc)
  !$acc end serial

  !$acc serial copy(aa, bb) copyout(zero: cc)
  !$acc end serial

  !$acc serial present(aa, bb) create(cc)
  !$acc end serial

  !$acc serial copyin(readonly: aa, bb) create(zero: cc)
  !$acc end serial

  !$acc serial deviceptr(aa, bb) no_create(cc)
  !$acc end serial

  !ERROR: Argument `aa` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
  !$acc serial attach(aa, dd, p)
  !$acc end serial

  !$acc serial firstprivate(bb, cc)
  !$acc end serial

  !$acc serial private(aa)
  !$acc end serial

  !$acc serial default(none)
  !$acc end serial

  !$acc serial default(present)
  !$acc end serial

  !ERROR: At most one DEFAULT clause can appear on the SERIAL directive
  !$acc serial default(present) default(none)
  !$acc end serial

  !$acc serial device_type(*) async wait
  !$acc end serial

  !$acc serial device_type(*) async
  do i = 1, N
    a(i) = 3.14
  end do
  !$acc end serial

  !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the SERIAL directive
  !$acc serial device_type(*) if(.TRUE.)
  do i = 1, N
    a(i) = 3.14
  end do
  !$acc end serial

end program openacc_serial_validity