File: atomic04.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-- 7,366 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
! RUN: %python %S/test_errors.py %s %flang_fc1
! This test checks for semantic errors in atomic_define subroutine calls based on
! the interface defined in section 16.9.23 of the Fortran 2018 standard.

program test_atomic_define
  use iso_fortran_env, only: atomic_int_kind, atomic_logical_kind
  implicit none

  integer(kind=atomic_int_kind) :: scalar_coarray[*], non_scalar_coarray(10)[*], val, non_coarray
  integer(kind=atomic_int_kind) :: repeated_atom[*], repeated_val, array(10)
  integer :: status, default_kind_coarray[*], coindexed_status[*], extra_arg, repeated_status, status_array(10), default_int_val
  real :: non_integer_coarray[*], non_int_or_logical
  logical(kind=atomic_logical_kind) :: atom_logical[*], val_logical, non_scalar_logical_coarray(10)[*], non_coarray_logical
  logical :: non_integer, default_kind_logical_coarray[*], default_logical_val

  ! These variables are used in this test based on the assumption that atomic_int_kind is not equal to kind=1
  ! This is true at the time of writing of the test, but of course is not guaranteed to stay the same
  integer(kind=1) :: kind1_coarray[*]
  logical(kind=1) :: kind1_logical_coarray[*]

  !___ standard-conforming calls ___
  call atomic_define(scalar_coarray, val)
  call atomic_define(scalar_coarray, default_int_val)
  call atomic_define(scalar_coarray[1], val)
  call atomic_define(scalar_coarray, default_int_val, status)
  call atomic_define(scalar_coarray[1], val, status)
  call atomic_define(scalar_coarray, default_int_val, stat=status)
  call atomic_define(scalar_coarray, value=val, stat=status)
  call atomic_define(atom=scalar_coarray, value=default_int_val)
  call atomic_define(atom=scalar_coarray, value=val, stat=status)
  call atomic_define(stat=status, value=default_int_val, atom=scalar_coarray)

  call atomic_define(atom_logical, val_logical)
  call atomic_define(atom_logical, default_logical_val)
  call atomic_define(atom_logical[1], val_logical)
  call atomic_define(atom_logical, val_logical, status)
  call atomic_define(atom_logical[1], val_logical, status)
  call atomic_define(atom_logical, val_logical, stat=status)
  call atomic_define(atom_logical, value=val_logical, stat=status)
  call atomic_define(atom=atom_logical, value=val_logical)
  call atomic_define(atom=atom_logical, value=val_logical, stat=status)
  call atomic_define(stat=status, value=val_logical, atom=atom_logical)

  !___ non-standard-conforming calls ___

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_scalar_coarray, val)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_scalar_coarray[1], val)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_scalar_logical_coarray, val_logical)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_scalar_logical_coarray[1], val_logical)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_coarray, val)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(non_coarray_logical, val_logical)

  !ERROR: 'atom=' argument must be a scalar coarray or coindexed object for intrinsic 'atomic_define'
  call atomic_define(array, val)

  !ERROR: Actual argument for 'atom=' must have kind=atomic_int_kind or atomic_logical_kind, but is 'INTEGER(4)'
  call atomic_define(default_kind_coarray, val)

  !ERROR: Actual argument for 'atom=' must have kind=atomic_int_kind or atomic_logical_kind, but is 'INTEGER(1)'
  call atomic_define(kind1_coarray, val)

  !ERROR: Actual argument for 'atom=' must have kind=atomic_int_kind or atomic_logical_kind, but is 'LOGICAL(4)'
  call atomic_define(default_kind_logical_coarray, val_logical)

  !ERROR: Actual argument for 'atom=' must have kind=atomic_int_kind or atomic_logical_kind, but is 'LOGICAL(1)'
  call atomic_define(kind1_logical_coarray, val_logical)

  !ERROR: 'value=' argument to 'atomic_define' must have same type as 'atom=', but is 'LOGICAL(8)'
  call atomic_define(scalar_coarray, val_logical)

  !ERROR: 'value=' argument to 'atomic_define' must have same type as 'atom=', but is 'INTEGER(8)'
  call atomic_define(atom_logical, val)

  !ERROR: Actual argument for 'atom=' has bad type 'REAL(4)'
  call atomic_define(non_integer_coarray, val)

  !ERROR: 'value=' argument has unacceptable rank 1
  call atomic_define(scalar_coarray, array)

  !ERROR: Actual argument for 'value=' has bad type 'REAL(4)'
  call atomic_define(scalar_coarray, non_int_or_logical)

  !ERROR: Actual argument for 'value=' has bad type 'REAL(4)'
  call atomic_define(atom_logical, non_int_or_logical)

  !ERROR: Actual argument for 'stat=' has bad type 'LOGICAL(4)'
  call atomic_define(scalar_coarray, val, non_integer)

  !ERROR: 'stat=' argument has unacceptable rank 1
  call atomic_define(scalar_coarray, val, status_array)

  !ERROR: 'stat' argument to 'atomic_define' may not be a coindexed object
  call atomic_define(scalar_coarray, val, coindexed_status[1])

  !ERROR: Actual argument associated with INTENT(OUT) dummy argument 'stat=' is not definable
  !BECAUSE: '1_4' is not a variable or pointer
  call atomic_define(scalar_coarray, val, 1)

  !ERROR: missing mandatory 'atom=' argument
  call atomic_define()

  !ERROR: missing mandatory 'atom=' argument
  call atomic_define(value=val, stat=status)

  !ERROR: missing mandatory 'value=' argument
  call atomic_define(scalar_coarray)

  !ERROR: missing mandatory 'value=' argument
  call atomic_define(atom=scalar_coarray, stat=status)

  !ERROR: too many actual arguments for intrinsic 'atomic_define'
  call atomic_define(scalar_coarray, val, status, extra_arg)

  !ERROR: repeated keyword argument to intrinsic 'atomic_define'
  call atomic_define(atom=scalar_coarray, atom=repeated_atom, value=val, stat=status)

  !ERROR: repeated keyword argument to intrinsic 'atomic_define'
  call atomic_define(atom=scalar_coarray, value=val, value=repeated_val, stat=status)

  !ERROR: repeated keyword argument to intrinsic 'atomic_define'
  call atomic_define(atom=scalar_coarray, value=val, stat=status, stat=repeated_status)

  !ERROR: unknown keyword argument to intrinsic 'atomic_define'
  call atomic_define(atomic=scalar_coarray, value=val, stat=status)

  !ERROR: unknown keyword argument to intrinsic 'atomic_define'
  call atomic_define(atom=scalar_coarray, values=val, stat=status)

  !ERROR: unknown keyword argument to intrinsic 'atomic_define'
  call atomic_define(atom=scalar_coarray, value=val, status=status)

  !ERROR: keyword argument to intrinsic 'atomic_define' was supplied positionally by an earlier actual argument
  call atomic_define(scalar_coarray, val, atom=repeated_atom)

  !ERROR: keyword argument to intrinsic 'atomic_define' was supplied positionally by an earlier actual argument
  call atomic_define(scalar_coarray, val, value=repeated_val)

  !ERROR: keyword argument to intrinsic 'atomic_define' was supplied positionally by an earlier actual argument
  call atomic_define(scalar_coarray, val, status, stat=repeated_status)

end program test_atomic_define