@@ -21,23 +21,27 @@ contains
2121 logical, intent(in), optional :: mask
2222 real(${o1}$) :: res
2323
24- integer :: c, n
24+ integer(kind = int64) :: c, n
2525 ${t1}$, allocatable :: x_tmp(:)
2626
2727 if (.not.optval(mask, .true.) .or. size(x) == 0) then
2828 res = ieee_value(1._${o1}$, ieee_quiet_nan)
2929 return
3030 end if
31+
32+ n = size(x, kind=int64)
33+ c = floor( (n + 1) / 2._${o1}$, kind=int64 )
3134
32- x_tmp = reshape(x, [size(x) ])
35+ x_tmp = reshape(x, [n ])
3336
3437 call sort(x_tmp)
3538
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'
4041 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
4145 else
4246 res = x_tmp(c)
4347 end if
@@ -56,9 +60,11 @@ contains
5660 real(${o1}$) :: res${reduced_shape('x', rank, 'dim')}$
5761
5862 integer :: c, n
63+ #:if rank > 1
5964 #:for fj in range(1, rank+1)
6065 integer :: j${"_" * fj}$
6166 #:endfor
67+ #:endif
6268 ${t1}$, allocatable :: x_tmp(:)
6369
6470 if (.not.optval(mask, .true.) .or. size(x) == 0) then
@@ -84,7 +90,12 @@ contains
8490 call sort(x_tmp)
8591
8692 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
8899 else
89100 res${reduce_subvector(rank, fi)}$ = x_tmp(c)
90101 end if
@@ -109,21 +120,25 @@ contains
109120 logical, intent(in) :: mask${ranksuffix(rank)}$
110121 real(${o1}$) :: res
111122
112- integer :: c, n
113- ${t1}$, allocatable :: x_tmp(:)
123+ integer(kind = int64) :: c, n
124+ ${t1}$, allocatable :: x_tmp(:)
114125
115126 x_tmp = pack(x, mask)
116127
117128 call sort(x_tmp)
118129
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 )
121132
122133 if (n == 0) then
123134 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'
125137 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
127142 res = x_tmp(c)
128143 end if
129144
@@ -140,10 +155,12 @@ contains
140155 logical, intent(in) :: mask${ranksuffix(rank)}$
141156 real(${o1}$) :: res${reduced_shape('x', rank, 'dim')}$
142157
143- integer :: c, n
158+ integer(kind = int64) :: c, n
159+ #:if rank > 1
144160 #:for fj in range(1, rank+1)
145161 integer :: j${"_" * fj}$
146162 #:endfor
163+ #:endif
147164 ${t1}$, allocatable :: x_tmp(:)
148165
149166 select case(dim)
@@ -159,15 +176,20 @@ contains
159176 mask${select_subvector(rank, fi)}$)
160177 call sort(x_tmp)
161178
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 )
164181
165182 if (n == 0) then
166183 res${reduce_subvector(rank, fi)}$ = &
167184 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
171193 res${reduce_subvector(rank, fi)}$ = x_tmp(c)
172194 end if
173195
0 commit comments