4
4
#:set NRANK = 4
5
5
6
6
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
8
8
use stdlib_stats, only: mean
9
9
use stdlib_kinds, only : int8, int16, int32, int64, sp, dp, xdp, qp
10
10
use, intrinsic :: ieee_arithmetic, only : ieee_is_nan
@@ -65,25 +65,36 @@ contains
65
65
!> Error handling
66
66
type(error_type), allocatable, intent(out) :: error
67
67
68
+ #:if MAXRANK > 7
68
69
call check(error, mean(d8_${k1}$), sum(real(d8_${k1}$, dp))/real(size(d8_${k1}$), dp)&
69
70
, 'mean(d8_${k1}$): uncorrect answer'&
70
71
, thr = dptol)
71
72
if (allocated(error)) return
73
+
74
+ #:else
75
+ call skip_test(error, "Rank > 7 is not supported")
76
+ #:endif
72
77
end subroutine
73
78
74
79
subroutine test_stats_meanf03_all_optmask_${k1}$(error)
75
80
!> Error handling
76
81
type(error_type), allocatable, intent(out) :: error
77
82
83
+ #:if MAXRANK > 7
78
84
call check(error, ieee_is_nan(mean(d8_${k1}$, .false.))&
79
85
, 'mean(d8_${k1}$, .false.): uncorrect answer')
80
86
if (allocated(error)) return
87
+
88
+ #:else
89
+ call skip_test(error, "Rank > 7 is not supported")
90
+ #:endif
81
91
end subroutine
82
92
83
93
subroutine test_stats_meanf03_${k1}$(error)
84
94
!> Error handling
85
95
type(error_type), allocatable, intent(out) :: error
86
96
97
+ #:if MAXRANK > 7
87
98
#:for dim in range(1, 9)
88
99
call check(error&
89
100
, sum(abs(mean(d8_${k1}$, ${dim}$) -&
@@ -92,12 +103,17 @@ contains
92
103
)
93
104
if (allocated(error)) return
94
105
#:endfor
106
+
107
+ #:else
108
+ call skip_test(error, "Rank > 7 is not supported")
109
+ #:endif
95
110
end subroutine
96
111
97
112
subroutine test_stats_meanf03_optmask_${k1}$(error)
98
113
!> Error handling
99
114
type(error_type), allocatable, intent(out) :: error
100
115
116
+ #:if MAXRANK > 7
101
117
call check(error, ieee_is_nan(mean(d1_${k1}$, 1, .false.))&
102
118
, 'mean(d1_${k1}$, 1, .false.): uncorrect answer'&
103
119
)
@@ -108,23 +124,33 @@ contains
108
124
, 'mean(d8_${k1}$, ${dim}$, .false.): uncorrect answer')
109
125
if (allocated(error)) return
110
126
#:endfor
127
+
128
+ #:else
129
+ call skip_test(error, "Rank > 7 is not supported")
130
+ #:endif
111
131
end subroutine
112
132
113
133
subroutine test_stats_meanf03_mask_all_${k1}$(error)
114
134
!> Error handling
115
135
type(error_type), allocatable, intent(out) :: error
116
136
137
+ #:if MAXRANK > 7
117
138
call check(error, mean(d8_${k1}$, d8_${k1}$ > 0)&
118
139
, sum(real(d8_${k1}$, dp), d8_${k1}$ > 0)/real(count(d8_${k1}$ > 0), dp)&
119
140
, 'mean(d8_${k1}$, d8_${k1}$ > 0): uncorrect answer'&
120
141
, thr = dptol)
121
142
if (allocated(error)) return
143
+
144
+ #:else
145
+ call skip_test(error, "Rank > 7 is not supported")
146
+ #:endif
122
147
end subroutine
123
148
124
149
subroutine test_stats_meanf03_mask_${k1}$(error)
125
150
!> Error handling
126
151
type(error_type), allocatable, intent(out) :: error
127
152
153
+ #:if MAXRANK > 7
128
154
#:for dim in range(1, 9)
129
155
call check(error&
130
156
, sum(abs(mean(d8_${k1}$, ${dim}$, d8_${k1}$ > 0) -&
@@ -133,6 +159,10 @@ contains
133
159
)
134
160
if (allocated(error)) return
135
161
#:endfor
162
+
163
+ #:else
164
+ call skip_test(error, "Rank > 7 is not supported")
165
+ #:endif
136
166
end subroutine
137
167
#:endfor
138
168
@@ -141,25 +171,36 @@ contains
141
171
!> Error handling
142
172
type(error_type), allocatable, intent(out) :: error
143
173
174
+ #:if MAXRANK > 7
144
175
call check(error, mean(d8_${k1}$), sum(d8_${k1}$)/real(size(d8_${k1}$), ${k1}$)&
145
176
, 'mean(d8_${k1}$): uncorrect answer'&
146
177
, thr = ${k1}$tol)
147
178
if (allocated(error)) return
179
+
180
+ #:else
181
+ call skip_test(error, "Rank > 7 is not supported")
182
+ #:endif
148
183
end subroutine
149
184
150
185
subroutine test_stats_meanf03_all_optmask_${k1}$(error)
151
186
!> Error handling
152
187
type(error_type), allocatable, intent(out) :: error
153
188
189
+ #:if MAXRANK > 7
154
190
call check(error, ieee_is_nan(mean(d8_${k1}$, .false.))&
155
191
, 'mean(d8_${k1}$, .false.): uncorrect answer')
156
192
if (allocated(error)) return
193
+
194
+ #:else
195
+ call skip_test(error, "Rank > 7 is not supported")
196
+ #:endif
157
197
end subroutine
158
198
159
199
subroutine test_stats_meanf03_${k1}$(error)
160
200
!> Error handling
161
201
type(error_type), allocatable, intent(out) :: error
162
202
203
+ #:if MAXRANK > 7
163
204
#:for dim in range(1, 9)
164
205
call check(error&
165
206
, sum(abs(mean(d8_${k1}$, ${dim}$) -&
@@ -168,34 +209,49 @@ contains
168
209
)
169
210
if (allocated(error)) return
170
211
#:endfor
212
+
213
+ #:else
214
+ call skip_test(error, "Rank > 7 is not supported")
215
+ #:endif
171
216
end subroutine
172
217
173
218
subroutine test_stats_meanf03_optmask_${k1}$(error)
174
219
!> Error handling
175
220
type(error_type), allocatable, intent(out) :: error
176
221
222
+ #:if MAXRANK > 7
177
223
#:for dim in range(1, 9)
178
224
call check(error, any(ieee_is_nan(mean(d8_${k1}$, ${dim}$, .false.)))&
179
225
, 'mean(d8_${k1}$, ${dim}$, .false.): uncorrect answer')
180
226
if (allocated(error)) return
181
227
#:endfor
228
+
229
+ #:else
230
+ call skip_test(error, "Rank > 7 is not supported")
231
+ #:endif
182
232
end subroutine
183
233
184
234
subroutine test_stats_meanf03_mask_all_${k1}$(error)
185
235
!> Error handling
186
236
type(error_type), allocatable, intent(out) :: error
187
237
238
+ #:if MAXRANK > 7
188
239
call check(error, mean(d8_${k1}$, d8_${k1}$ > 0)&
189
240
, sum(d8_${k1}$, d8_${k1}$ > 0)/real(count(d8_${k1}$ > 0), ${k1}$)&
190
241
, 'mean(d8_${k1}$, d8_${k1}$ > 0): uncorrect answer'&
191
242
, thr = ${k1}$tol)
192
243
if (allocated(error)) return
244
+
245
+ #:else
246
+ call skip_test(error, "Rank > 7 is not supported")
247
+ #:endif
193
248
end subroutine
194
249
195
250
subroutine test_stats_meanf03_mask_${k1}$(error)
196
251
!> Error handling
197
252
type(error_type), allocatable, intent(out) :: error
198
253
254
+ #:if MAXRANK > 7
199
255
#:for dim in range(1, 9)
200
256
call check(error&
201
257
, sum(abs(mean(d8_${k1}$, ${dim}$, d8_${k1}$ > 0) -&
@@ -204,6 +260,10 @@ contains
204
260
)
205
261
if (allocated(error)) return
206
262
#:endfor
263
+
264
+ #:else
265
+ call skip_test(error, "Rank > 7 is not supported")
266
+ #:endif
207
267
end subroutine
208
268
#:endfor
209
269
@@ -212,25 +272,36 @@ contains
212
272
!> Error handling
213
273
type(error_type), allocatable, intent(out) :: error
214
274
275
+ #:if MAXRANK > 7
215
276
call check(error, mean(d8_c${k1}$), sum(d8_c${k1}$)/real(size(d8_c${k1}$), ${k1}$)&
216
277
, 'mean(d8_c${k1}$): uncorrect answer'&
217
278
, thr = ${k1}$tol)
218
279
if (allocated(error)) return
280
+
281
+ #:else
282
+ call skip_test(error, "Rank > 7 is not supported")
283
+ #:endif
219
284
end subroutine
220
285
221
286
subroutine test_stats_meanf03_all_optmask_c${k1}$(error)
222
287
!> Error handling
223
288
type(error_type), allocatable, intent(out) :: error
224
289
290
+ #:if MAXRANK > 7
225
291
call check(error, ieee_is_nan(real(mean(d8_c${k1}$, .false.)))&
226
292
, 'mean(d8_c${k1}$, .false.): uncorrect answer')
227
293
if (allocated(error)) return
294
+
295
+ #:else
296
+ call skip_test(error, "Rank > 7 is not supported")
297
+ #:endif
228
298
end subroutine
229
299
230
300
subroutine test_stats_meanf03_c${k1}$(error)
231
301
!> Error handling
232
302
type(error_type), allocatable, intent(out) :: error
233
303
304
+ #:if MAXRANK > 7
234
305
#:for dim in range(1, 9)
235
306
call check(error&
236
307
, sum(abs(mean(d8_c${k1}$, ${dim}$) -&
@@ -239,34 +310,49 @@ contains
239
310
)
240
311
if (allocated(error)) return
241
312
#:endfor
313
+
314
+ #:else
315
+ call skip_test(error, "Rank > 7 is not supported")
316
+ #:endif
242
317
end subroutine
243
318
244
319
subroutine test_stats_meanf03_optmask_c${k1}$(error)
245
320
!> Error handling
246
321
type(error_type), allocatable, intent(out) :: error
247
322
323
+ #:if MAXRANK > 7
248
324
#:for dim in range(1, 9)
249
325
call check(error, any(ieee_is_nan(real(mean(d8_c${k1}$, ${dim}$, .false.))))&
250
326
, 'mean(d8_c${k1}$, ${dim}$, .false.): uncorrect answer')
251
327
if (allocated(error)) return
252
328
#:endfor
329
+
330
+ #:else
331
+ call skip_test(error, "Rank > 7 is not supported")
332
+ #:endif
253
333
end subroutine
254
334
255
335
subroutine test_stats_meanf03_mask_all_c${k1}$(error)
256
336
!> Error handling
257
337
type(error_type), allocatable, intent(out) :: error
258
338
339
+ #:if MAXRANK > 7
259
340
call check(error, mean(d8_c${k1}$, d8_c${k1}$%re > 0)&
260
341
, sum(d8_c${k1}$, d8_c${k1}$%re > 0)/real(count(d8_c${k1}$%re > 0), ${k1}$)&
261
342
, 'mean(d8_c${k1}$, d8_c${k1}$%re > 0): uncorrect answer'&
262
343
, thr = ${k1}$tol)
263
344
if (allocated(error)) return
345
+
346
+ #:else
347
+ call skip_test(error, "Rank > 7 is not supported")
348
+ #:endif
264
349
end subroutine
265
350
266
351
subroutine test_stats_meanf03_mask_c${k1}$(error)
267
352
!> Error handling
268
353
type(error_type), allocatable, intent(out) :: error
269
354
355
+ #:if MAXRANK > 7
270
356
#:for dim in range(1, 9)
271
357
call check(error&
272
358
, sum(abs(mean(d8_c${k1}$, ${dim}$, d8_c${k1}$%re > 0) -&
@@ -275,6 +361,10 @@ contains
275
361
)
276
362
if (allocated(error)) return
277
363
#:endfor
364
+
365
+ #:else
366
+ call skip_test(error, "Rank > 7 is not supported")
367
+ #:endif
278
368
end subroutine
279
369
#:endfor
280
370
0 commit comments