@@ -21,23 +21,27 @@ contains
21
21
logical, intent(in), optional :: mask
22
22
real(${o1}$) :: res
23
23
24
- integer :: c, n
24
+ integer(kind = int64) :: c, n
25
25
${t1}$, allocatable :: x_tmp(:)
26
26
27
27
if (.not.optval(mask, .true.) .or. size(x) == 0) then
28
28
res = ieee_value(1._${o1}$, ieee_quiet_nan)
29
29
return
30
30
end if
31
+
32
+ n = size(x, kind=int64)
33
+ c = floor( (n + 1) / 2._${o1}$, kind=int64 )
31
34
32
- x_tmp = reshape(x, [size(x) ])
35
+ x_tmp = reshape(x, [n ])
33
36
34
37
call sort(x_tmp)
35
38
36
- n = size(x_tmp)
37
- c = floor( (n + 1) / 2._${o1}$ )
38
-
39
- if (mod(n, 2) == 0) then
39
+ if (mod(n, 2_int64) == 0) then
40
+ #:if t1[0] == 'r'
40
41
res = sum(x_tmp(c:c+1)) / 2._${o1}$
42
+ #:else
43
+ res = sum( real(x_tmp(c:c+1), kind=${o1}$) ) / 2._${o1}$
44
+ #:endif
41
45
else
42
46
res = x_tmp(c)
43
47
end if
@@ -56,9 +60,11 @@ contains
56
60
real(${o1}$) :: res${reduced_shape('x', rank, 'dim')}$
57
61
58
62
integer :: c, n
63
+ #:if rank > 1
59
64
#:for fj in range(1, rank+1)
60
65
integer :: j${"_" * fj}$
61
66
#:endfor
67
+ #:endif
62
68
${t1}$, allocatable :: x_tmp(:)
63
69
64
70
if (.not.optval(mask, .true.) .or. size(x) == 0) then
@@ -84,7 +90,12 @@ contains
84
90
call sort(x_tmp)
85
91
86
92
if (mod(n, 2) == 0) then
87
- res${reduce_subvector(rank, fi)}$ = sum(x_tmp(c:c+1)) / 2._${o1}$
93
+ res${reduce_subvector(rank, fi)}$ = &
94
+ #:if t1[0] == 'r'
95
+ sum(x_tmp(c:c+1)) / 2._${o1}$
96
+ #:else
97
+ sum(real(x_tmp(c:c+1), kind=${o1}$) ) / 2._${o1}$
98
+ #:endif
88
99
else
89
100
res${reduce_subvector(rank, fi)}$ = x_tmp(c)
90
101
end if
@@ -109,21 +120,25 @@ contains
109
120
logical, intent(in) :: mask${ranksuffix(rank)}$
110
121
real(${o1}$) :: res
111
122
112
- integer :: c, n
113
- ${t1}$, allocatable :: x_tmp(:)
123
+ integer(kind = int64) :: c, n
124
+ ${t1}$, allocatable :: x_tmp(:)
114
125
115
126
x_tmp = pack(x, mask)
116
127
117
128
call sort(x_tmp)
118
129
119
- n = size(x_tmp)
120
- c = floor( (n + 1) / 2._${o1}$ )
130
+ n = size(x_tmp, kind=int64 )
131
+ c = floor( (n + 1) / 2._${o1}$, kind=int64 )
121
132
122
133
if (n == 0) then
123
134
res = ieee_value(1._${o1}$, ieee_quiet_nan)
124
- else if (mod(n, 2) == 0) then
135
+ else if (mod(n, 2_int64) == 0) then
136
+ #:if t1[0] == 'r'
125
137
res = sum(x_tmp(c:c+1)) / 2._${o1}$
126
- else if (mod(n, 2) == 1) then
138
+ #:else
139
+ res = sum(real(x_tmp(c:c+1), kind=${o1}$)) / 2._${o1}$
140
+ #:endif
141
+ else if (mod(n, 2_int64) == 1) then
127
142
res = x_tmp(c)
128
143
end if
129
144
@@ -140,10 +155,12 @@ contains
140
155
logical, intent(in) :: mask${ranksuffix(rank)}$
141
156
real(${o1}$) :: res${reduced_shape('x', rank, 'dim')}$
142
157
143
- integer :: c, n
158
+ integer(kind = int64) :: c, n
159
+ #:if rank > 1
144
160
#:for fj in range(1, rank+1)
145
161
integer :: j${"_" * fj}$
146
162
#:endfor
163
+ #:endif
147
164
${t1}$, allocatable :: x_tmp(:)
148
165
149
166
select case(dim)
@@ -159,15 +176,20 @@ contains
159
176
mask${select_subvector(rank, fi)}$)
160
177
call sort(x_tmp)
161
178
162
- n = size(x_tmp)
163
- c = floor( (n + 1) / 2._${o1}$ )
179
+ n = size(x_tmp, kind=int64 )
180
+ c = floor( (n + 1) / 2._${o1}$, kind=int64 )
164
181
165
182
if (n == 0) then
166
183
res${reduce_subvector(rank, fi)}$ = &
167
184
ieee_value(1._${o1}$, ieee_quiet_nan)
168
- else if (mod(n, 2) == 0) then
169
- res${reduce_subvector(rank, fi)}$ = sum(x_tmp(c:c+1)) / 2._${o1}$
170
- else if (mod(n, 2) == 1) then
185
+ else if (mod(n, 2_int64) == 0) then
186
+ res${reduce_subvector(rank, fi)}$ = &
187
+ #:if t1[0] == 'r'
188
+ sum(x_tmp(c:c+1)) / 2._${o1}$
189
+ #:else
190
+ sum(real(x_tmp(c:c+1), kind=${o1}$)) / 2._${o1}$
191
+ #:endif
192
+ else if (mod(n, 2_int64) == 1) then
171
193
res${reduce_subvector(rank, fi)}$ = x_tmp(c)
172
194
end if
173
195
0 commit comments