File: ignore_tkr01.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 (227 lines) | stat: -rw-r--r-- 4,900 bytes parent folder | download | duplicates (2)
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
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
! RUN: %python %S/test_errors.py %s %flang_fc1
! !DIR$ IGNORE_TKR tests

!ERROR: !DIR$ IGNORE_TKR directive must appear in a subroutine or function
!dir$ ignore_tkr

module m

!ERROR: !DIR$ IGNORE_TKR directive must appear in a subroutine or function
!dir$ ignore_tkr

  interface
    subroutine t1(x)
!dir$ ignore_tkr
      real, intent(in) :: x
    end

    subroutine t2(x)
!dir$ ignore_tkr(t) x
      real, intent(in) :: x
    end

    subroutine t3(x)
!dir$ ignore_tkr(k) x
      real, intent(in) :: x
    end

    subroutine t4(a)
!dir$ ignore_tkr(r) a
      real, intent(in) :: a(2)
    end

    subroutine t5(m)
!dir$ ignore_tkr(r) m
      real, intent(in) :: m(2,2)
    end

    subroutine t6(x)
!dir$ ignore_tkr(a) x
      real, intent(in) :: x
    end

    subroutine t7(x)
!ERROR: !DIR$ IGNORE_TKR directive may not have an empty parenthesized list of letters
!dir$ ignore_tkr() x
      real, intent(in) :: x
    end

    subroutine t8(x)
!dir$ ignore_tkr x
      real, intent(in) :: x
    end

    subroutine t9(x)
!dir$ ignore_tkr x
!WARNING: !DIR$ IGNORE_TKR should not apply to an allocatable or pointer
      real, intent(in), allocatable :: x
    end

    subroutine t10(x)
!dir$ ignore_tkr x
!WARNING: !DIR$ IGNORE_TKR should not apply to an allocatable or pointer
      real, intent(in), pointer :: x
    end

    subroutine t11
!dir$ ignore_tkr x
!ERROR: !DIR$ IGNORE_TKR directive may apply only to a dummy data argument
      real :: x
    end

    subroutine t12(p,q,r)
!dir$ ignore_tkr p, q
!ERROR: 'p' is a data object and may not be EXTERNAL
      real, external :: p
!ERROR: 'q' is already declared as an object
      procedure(real) :: q
      procedure(), pointer :: r
!ERROR: 'r' must be an object
!dir$ ignore_tkr r
    end

    elemental subroutine t13(x)
!dir$ ignore_tkr(r) x
!ERROR: !DIR$ IGNORE_TKR(R) may not apply in an ELEMENTAL procedure
      real, intent(in) :: x
    end

    subroutine t14(x)
!dir$ ignore_tkr(r) x
!WARNING: !DIR$ IGNORE_TKR(R) should not apply to a dummy argument passed via descriptor
      real x(:)
    end

  end interface

 contains
    subroutine t15(x)
!dir$ ignore_tkr x
!ERROR: !DIR$ IGNORE_TKR may not apply to an allocatable or pointer
      real, intent(in), allocatable :: x
    end

    subroutine t16(x)
!dir$ ignore_tkr x
!ERROR: !DIR$ IGNORE_TKR may not apply to an allocatable or pointer
      real, intent(in), pointer :: x
    end

  subroutine t17(x)
    real x
    x = x + 1.
!ERROR: !DIR$ IGNORE_TKR directive must appear in the specification part
!dir$ ignore_tkr x
  end

  subroutine t18(x)
!ERROR: 'q' is not a valid letter for !DIR$ IGNORE_TKR directive
!dir$ ignore_tkr(q) x
    real x
    x = x + 1.
  end

  subroutine t19(x)
    real x
   contains
    subroutine inner
!ERROR: 'x' must be local to this subprogram
!dir$ ignore_tkr x
    end
  end

  subroutine t20(x)
    real x
    block
!ERROR: 'x' must be local to this subprogram
!dir$ ignore_tkr x
    end block
  end

  subroutine t21(x)
!dir$ ignore_tkr(c) x
!ERROR: !DIR$ IGNORE_TKR(C) may apply only to an assumed-shape array
    real x(1)
  end

  subroutine t22(x)
!dir$ ignore_tkr(r) x
!WARNING: !DIR$ IGNORE_TKR(R) is not meaningful for an assumed-rank array
    real x(..)
  end

  subroutine t23(x)
!dir$ ignore_tkr(r) x
!ERROR: !DIR$ IGNORE_TKR(R) may not apply to a dummy argument passed via descriptor
    real x(:)
  end

end

subroutine bad1(x)
!dir$ ignore_tkr x
!ERROR: !DIR$ IGNORE_TKR may apply only in an interface or a module procedure
  real, intent(in) :: x
end

program test

!ERROR: !DIR$ IGNORE_TKR directive must appear in a subroutine or function
!dir$ ignore_tkr

  use m
  real x
  real a(2)
  real m(2,2)
  double precision dx

  call t1(1)
  call t1(dx)
  call t1('a')
  call t1((1.,2.))
  call t1(.true.)

  call t2(1)
  !ERROR: Actual argument type 'REAL(8)' is not compatible with dummy argument type 'REAL(4)'
  call t2(dx)
  call t2('a')
  call t2((1.,2.))
  call t2(.true.)

  !ERROR: Actual argument type 'INTEGER(4)' is not compatible with dummy argument type 'REAL(4)'
  call t3(1)
  call t3(dx)
  !ERROR: passing Hollerith or character literal as if it were BOZ
  call t3('a')
  !ERROR: Actual argument type 'COMPLEX(4)' is not compatible with dummy argument type 'REAL(4)'
  call t3((1.,2.))
  !ERROR: Actual argument type 'LOGICAL(4)' is not compatible with dummy argument type 'REAL(4)'
  call t3(.true.)

  call t4(x)
  call t4(m)
  call t5(x)
  !WARNING: Actual argument array is smaller (2 element(s)) than dummy argument 'm=' array (4)
  call t5(a)

  call t6(1)
  call t6(dx)
  call t6('a')
  call t6((1.,2.))
  call t6(.true.)
  call t6(a)

  call t8(1)
  call t8(dx)
  call t8('a')
  call t8((1.,2.))
  call t8(.true.)
  call t8(a)

 contains
  subroutine inner(x)
!dir$ ignore_tkr x
!ERROR: !DIR$ IGNORE_TKR may apply only in an interface or a module procedure
    real, intent(in) :: x
  end
end