File: omp-atomic-assignment-stmt.f90

package info (click to toggle)
llvm-toolchain-20 1%3A20.1.8-1~exp1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 2,111,388 kB
  • sloc: cpp: 7,438,767; ansic: 1,393,871; asm: 1,012,926; python: 241,728; f90: 86,635; objc: 75,411; lisp: 42,144; pascal: 17,286; sh: 10,027; ml: 5,082; perl: 4,730; awk: 3,523; makefile: 3,349; javascript: 2,251; xml: 892; fortran: 672
file content (162 lines) | stat: -rw-r--r-- 5,348 bytes parent folder | download
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
! REQUIRES: openmp_runtime

! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags -fopenmp-version=50
! Semantic checks for various assignments related to atomic constructs

program sample
    use omp_lib
    integer :: x, v
    integer :: y(10)
    integer, allocatable :: k
    integer a(10)
    type sample_type
        integer :: y
        integer :: m
    endtype
    type(sample_type) :: z
    character :: l, r
    !$omp atomic read
        v = x

    !$omp atomic read
    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
    !ERROR: Expected scalar expression on the RHS of atomic assignment statement
        v = y(1:3)

    !$omp atomic read
    !ERROR: Expected scalar variable of intrinsic type on RHS of atomic assignment statement
        v = x * (10 + x)

    !$omp atomic read
    !ERROR: Expected scalar variable of intrinsic type on RHS of atomic assignment statement
        v = 4

    !$omp atomic read
    !ERROR: k must not have ALLOCATABLE attribute
        v = k

    !$omp atomic write
    !ERROR: k must not have ALLOCATABLE attribute
        k = x

    !$omp atomic update
    !ERROR: k must not have ALLOCATABLE attribute
        k = k + x * (v * x)

    !$omp atomic
    !ERROR: k must not have ALLOCATABLE attribute
        k = v * k  
         
    !$omp atomic write
    !ERROR: RHS expression on atomic assignment statement cannot access 'z%y'
       z%y = x + z%y

    !$omp atomic write
    !ERROR: RHS expression on atomic assignment statement cannot access 'x'
        x = x

    !$omp atomic write
    !ERROR: RHS expression on atomic assignment statement cannot access 'm'
        m = min(m, x, z%m) + k
 
    !$omp atomic read
    !ERROR: RHS expression on atomic assignment statement cannot access 'x'
        x = x

    !$omp atomic read
    !ERROR: Expected scalar variable of intrinsic type on RHS of atomic assignment statement
    !ERROR: RHS expression on atomic assignment statement cannot access 'm'
        m = min(m, x, z%m) + k

    !$omp atomic read
    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
    !ERROR: Expected scalar expression on the RHS of atomic assignment statement
        x = a

    !$omp atomic read
    !ERROR: Expected scalar variable on the LHS of atomic assignment statement
        a = x

    !$omp atomic write
    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
    !ERROR: Expected scalar expression on the RHS of atomic assignment statement
        x = a

    !$omp atomic write
    !ERROR: Expected scalar variable on the LHS of atomic assignment statement
        a = x

    !$omp atomic capture
        v = x
        x = x + 1
    !$omp end atomic

    !$omp atomic release capture
        v = x
    !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
        x = b + (x*1)
    !$omp end atomic

    !$omp atomic capture hint(0)
        v = x
        x = 1
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Captured variable/array element/derived-type component x expected to be assigned in the second statement of ATOMIC CAPTURE construct
        v = x
        b = b + 1
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Captured variable/array element/derived-type component x expected to be assigned in the second statement of ATOMIC CAPTURE construct
        v = x
        b = 10
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Updated variable/array element/derived-type component x expected to be captured in the second statement of ATOMIC CAPTURE construct
        x = x + 10
        v = b
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Invalid ATOMIC CAPTURE construct statements. Expected one of [update-stmt, capture-stmt], [capture-stmt, update-stmt], or [capture-stmt, write-stmt]
        v = 1
        x = 4
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Captured variable/array element/derived-type component z%y expected to be assigned in the second statement of ATOMIC CAPTURE construct
        x = z%y
        z%m = z%m + 1.0
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Updated variable/array element/derived-type component z%m expected to be captured in the second statement of ATOMIC CAPTURE construct
        z%m = z%m + 1.0
        x = z%y
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Captured variable/array element/derived-type component y(2) expected to be assigned in the second statement of ATOMIC CAPTURE construct
        x = y(2)
        y(1) = y(1) + 1
    !$omp end atomic

    !$omp atomic capture
    !ERROR: Updated variable/array element/derived-type component y(1) expected to be captured in the second statement of ATOMIC CAPTURE construct
        y(1) = y(1) + 1
        x = y(2)
    !$omp end atomic

    !$omp atomic read
    !ERROR: Expected scalar variable on the LHS of atomic assignment statement
    !ERROR: Expected scalar expression on the RHS of atomic assignment statement
        l = r

    !$omp atomic write
    !ERROR: Expected scalar variable on the LHS of atomic assignment statement
    !ERROR: Expected scalar expression on the RHS of atomic assignment statement
        l = r
end program