Skip to content

Commit 7a2bffa

Browse files
committed
Modif of test_mean_f03 following fortran-lang#675 by @arteebraina
1 parent ddfd419 commit 7a2bffa

File tree

1 file changed

+91
-1
lines changed

1 file changed

+91
-1
lines changed

test/stats/test_mean_f03.fypp

+91-1
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
#:set NRANK = 4
55

66
module test_stats_meanf03
7-
use testdrive, only : new_unittest, unittest_type, error_type, check
7+
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
88
use stdlib_stats, only: mean
99
use stdlib_kinds, only : int8, int16, int32, int64, sp, dp, xdp, qp
1010
use, intrinsic :: ieee_arithmetic, only : ieee_is_nan
@@ -65,25 +65,36 @@ contains
6565
!> Error handling
6666
type(error_type), allocatable, intent(out) :: error
6767

68+
#:if MAXRANK > 7
6869
call check(error, mean(d8_${k1}$), sum(real(d8_${k1}$, dp))/real(size(d8_${k1}$), dp)&
6970
, 'mean(d8_${k1}$): uncorrect answer'&
7071
, thr = dptol)
7172
if (allocated(error)) return
73+
74+
#:else
75+
call skip_test(error, "Rank > 7 is not supported")
76+
#:endif
7277
end subroutine
7378

7479
subroutine test_stats_meanf03_all_optmask_${k1}$(error)
7580
!> Error handling
7681
type(error_type), allocatable, intent(out) :: error
7782

83+
#:if MAXRANK > 7
7884
call check(error, ieee_is_nan(mean(d8_${k1}$, .false.))&
7985
, 'mean(d8_${k1}$, .false.): uncorrect answer')
8086
if (allocated(error)) return
87+
88+
#:else
89+
call skip_test(error, "Rank > 7 is not supported")
90+
#:endif
8191
end subroutine
8292

8393
subroutine test_stats_meanf03_${k1}$(error)
8494
!> Error handling
8595
type(error_type), allocatable, intent(out) :: error
8696

97+
#:if MAXRANK > 7
8798
#:for dim in range(1, 9)
8899
call check(error&
89100
, sum(abs(mean(d8_${k1}$, ${dim}$) -&
@@ -92,12 +103,17 @@ contains
92103
)
93104
if (allocated(error)) return
94105
#:endfor
106+
107+
#:else
108+
call skip_test(error, "Rank > 7 is not supported")
109+
#:endif
95110
end subroutine
96111

97112
subroutine test_stats_meanf03_optmask_${k1}$(error)
98113
!> Error handling
99114
type(error_type), allocatable, intent(out) :: error
100115

116+
#:if MAXRANK > 7
101117
call check(error, ieee_is_nan(mean(d1_${k1}$, 1, .false.))&
102118
, 'mean(d1_${k1}$, 1, .false.): uncorrect answer'&
103119
)
@@ -108,23 +124,33 @@ contains
108124
, 'mean(d8_${k1}$, ${dim}$, .false.): uncorrect answer')
109125
if (allocated(error)) return
110126
#:endfor
127+
128+
#:else
129+
call skip_test(error, "Rank > 7 is not supported")
130+
#:endif
111131
end subroutine
112132

113133
subroutine test_stats_meanf03_mask_all_${k1}$(error)
114134
!> Error handling
115135
type(error_type), allocatable, intent(out) :: error
116136

137+
#:if MAXRANK > 7
117138
call check(error, mean(d8_${k1}$, d8_${k1}$ > 0)&
118139
, sum(real(d8_${k1}$, dp), d8_${k1}$ > 0)/real(count(d8_${k1}$ > 0), dp)&
119140
, 'mean(d8_${k1}$, d8_${k1}$ > 0): uncorrect answer'&
120141
, thr = dptol)
121142
if (allocated(error)) return
143+
144+
#:else
145+
call skip_test(error, "Rank > 7 is not supported")
146+
#:endif
122147
end subroutine
123148

124149
subroutine test_stats_meanf03_mask_${k1}$(error)
125150
!> Error handling
126151
type(error_type), allocatable, intent(out) :: error
127152

153+
#:if MAXRANK > 7
128154
#:for dim in range(1, 9)
129155
call check(error&
130156
, sum(abs(mean(d8_${k1}$, ${dim}$, d8_${k1}$ > 0) -&
@@ -133,6 +159,10 @@ contains
133159
)
134160
if (allocated(error)) return
135161
#:endfor
162+
163+
#:else
164+
call skip_test(error, "Rank > 7 is not supported")
165+
#:endif
136166
end subroutine
137167
#:endfor
138168

@@ -141,25 +171,36 @@ contains
141171
!> Error handling
142172
type(error_type), allocatable, intent(out) :: error
143173

174+
#:if MAXRANK > 7
144175
call check(error, mean(d8_${k1}$), sum(d8_${k1}$)/real(size(d8_${k1}$), ${k1}$)&
145176
, 'mean(d8_${k1}$): uncorrect answer'&
146177
, thr = ${k1}$tol)
147178
if (allocated(error)) return
179+
180+
#:else
181+
call skip_test(error, "Rank > 7 is not supported")
182+
#:endif
148183
end subroutine
149184

150185
subroutine test_stats_meanf03_all_optmask_${k1}$(error)
151186
!> Error handling
152187
type(error_type), allocatable, intent(out) :: error
153188

189+
#:if MAXRANK > 7
154190
call check(error, ieee_is_nan(mean(d8_${k1}$, .false.))&
155191
, 'mean(d8_${k1}$, .false.): uncorrect answer')
156192
if (allocated(error)) return
193+
194+
#:else
195+
call skip_test(error, "Rank > 7 is not supported")
196+
#:endif
157197
end subroutine
158198

159199
subroutine test_stats_meanf03_${k1}$(error)
160200
!> Error handling
161201
type(error_type), allocatable, intent(out) :: error
162202

203+
#:if MAXRANK > 7
163204
#:for dim in range(1, 9)
164205
call check(error&
165206
, sum(abs(mean(d8_${k1}$, ${dim}$) -&
@@ -168,34 +209,49 @@ contains
168209
)
169210
if (allocated(error)) return
170211
#:endfor
212+
213+
#:else
214+
call skip_test(error, "Rank > 7 is not supported")
215+
#:endif
171216
end subroutine
172217

173218
subroutine test_stats_meanf03_optmask_${k1}$(error)
174219
!> Error handling
175220
type(error_type), allocatable, intent(out) :: error
176221

222+
#:if MAXRANK > 7
177223
#:for dim in range(1, 9)
178224
call check(error, any(ieee_is_nan(mean(d8_${k1}$, ${dim}$, .false.)))&
179225
, 'mean(d8_${k1}$, ${dim}$, .false.): uncorrect answer')
180226
if (allocated(error)) return
181227
#:endfor
228+
229+
#:else
230+
call skip_test(error, "Rank > 7 is not supported")
231+
#:endif
182232
end subroutine
183233

184234
subroutine test_stats_meanf03_mask_all_${k1}$(error)
185235
!> Error handling
186236
type(error_type), allocatable, intent(out) :: error
187237

238+
#:if MAXRANK > 7
188239
call check(error, mean(d8_${k1}$, d8_${k1}$ > 0)&
189240
, sum(d8_${k1}$, d8_${k1}$ > 0)/real(count(d8_${k1}$ > 0), ${k1}$)&
190241
, 'mean(d8_${k1}$, d8_${k1}$ > 0): uncorrect answer'&
191242
, thr = ${k1}$tol)
192243
if (allocated(error)) return
244+
245+
#:else
246+
call skip_test(error, "Rank > 7 is not supported")
247+
#:endif
193248
end subroutine
194249

195250
subroutine test_stats_meanf03_mask_${k1}$(error)
196251
!> Error handling
197252
type(error_type), allocatable, intent(out) :: error
198253

254+
#:if MAXRANK > 7
199255
#:for dim in range(1, 9)
200256
call check(error&
201257
, sum(abs(mean(d8_${k1}$, ${dim}$, d8_${k1}$ > 0) -&
@@ -204,6 +260,10 @@ contains
204260
)
205261
if (allocated(error)) return
206262
#:endfor
263+
264+
#:else
265+
call skip_test(error, "Rank > 7 is not supported")
266+
#:endif
207267
end subroutine
208268
#:endfor
209269

@@ -212,25 +272,36 @@ contains
212272
!> Error handling
213273
type(error_type), allocatable, intent(out) :: error
214274

275+
#:if MAXRANK > 7
215276
call check(error, mean(d8_c${k1}$), sum(d8_c${k1}$)/real(size(d8_c${k1}$), ${k1}$)&
216277
, 'mean(d8_c${k1}$): uncorrect answer'&
217278
, thr = ${k1}$tol)
218279
if (allocated(error)) return
280+
281+
#:else
282+
call skip_test(error, "Rank > 7 is not supported")
283+
#:endif
219284
end subroutine
220285

221286
subroutine test_stats_meanf03_all_optmask_c${k1}$(error)
222287
!> Error handling
223288
type(error_type), allocatable, intent(out) :: error
224289

290+
#:if MAXRANK > 7
225291
call check(error, ieee_is_nan(real(mean(d8_c${k1}$, .false.)))&
226292
, 'mean(d8_c${k1}$, .false.): uncorrect answer')
227293
if (allocated(error)) return
294+
295+
#:else
296+
call skip_test(error, "Rank > 7 is not supported")
297+
#:endif
228298
end subroutine
229299

230300
subroutine test_stats_meanf03_c${k1}$(error)
231301
!> Error handling
232302
type(error_type), allocatable, intent(out) :: error
233303

304+
#:if MAXRANK > 7
234305
#:for dim in range(1, 9)
235306
call check(error&
236307
, sum(abs(mean(d8_c${k1}$, ${dim}$) -&
@@ -239,34 +310,49 @@ contains
239310
)
240311
if (allocated(error)) return
241312
#:endfor
313+
314+
#:else
315+
call skip_test(error, "Rank > 7 is not supported")
316+
#:endif
242317
end subroutine
243318

244319
subroutine test_stats_meanf03_optmask_c${k1}$(error)
245320
!> Error handling
246321
type(error_type), allocatable, intent(out) :: error
247322

323+
#:if MAXRANK > 7
248324
#:for dim in range(1, 9)
249325
call check(error, any(ieee_is_nan(real(mean(d8_c${k1}$, ${dim}$, .false.))))&
250326
, 'mean(d8_c${k1}$, ${dim}$, .false.): uncorrect answer')
251327
if (allocated(error)) return
252328
#:endfor
329+
330+
#:else
331+
call skip_test(error, "Rank > 7 is not supported")
332+
#:endif
253333
end subroutine
254334

255335
subroutine test_stats_meanf03_mask_all_c${k1}$(error)
256336
!> Error handling
257337
type(error_type), allocatable, intent(out) :: error
258338

339+
#:if MAXRANK > 7
259340
call check(error, mean(d8_c${k1}$, d8_c${k1}$%re > 0)&
260341
, sum(d8_c${k1}$, d8_c${k1}$%re > 0)/real(count(d8_c${k1}$%re > 0), ${k1}$)&
261342
, 'mean(d8_c${k1}$, d8_c${k1}$%re > 0): uncorrect answer'&
262343
, thr = ${k1}$tol)
263344
if (allocated(error)) return
345+
346+
#:else
347+
call skip_test(error, "Rank > 7 is not supported")
348+
#:endif
264349
end subroutine
265350

266351
subroutine test_stats_meanf03_mask_c${k1}$(error)
267352
!> Error handling
268353
type(error_type), allocatable, intent(out) :: error
269354

355+
#:if MAXRANK > 7
270356
#:for dim in range(1, 9)
271357
call check(error&
272358
, sum(abs(mean(d8_c${k1}$, ${dim}$, d8_c${k1}$%re > 0) -&
@@ -275,6 +361,10 @@ contains
275361
)
276362
if (allocated(error)) return
277363
#:endfor
364+
365+
#:else
366+
call skip_test(error, "Rank > 7 is not supported")
367+
#:endif
278368
end subroutine
279369
#:endfor
280370

0 commit comments

Comments
 (0)