@@ -18,7 +18,7 @@ module function mean_1_${k1}$_${k1}$(x) result(res)
18
18
${t1}$, intent(in) :: x(:)
19
19
${t1}$ :: res
20
20
21
- res = sum(x) / real(size(x), ${k1}$)
21
+ res = sum(x) / real(size(x, kind = int64 ), ${k1}$)
22
22
23
23
end function mean_1_${k1}$_${k1}$
24
24
#:endfor
@@ -28,7 +28,7 @@ module function mean_1_${k1}$_dp(x) result(res)
28
28
${t1}$, intent(in) :: x(:)
29
29
real(dp) :: res
30
30
31
- res = sum(real(x, dp)) / real(size(x), dp)
31
+ res = sum(real(x, dp)) / real(size(x, kind = int64 ), dp)
32
32
33
33
end function mean_1_${k1}$_dp
34
34
#:endfor
@@ -39,7 +39,7 @@ module function mean_2_all_${k1}$_${k1}$(x) result(res)
39
39
${t1}$, intent(in) :: x(:,:)
40
40
${t1}$ :: res
41
41
42
- res = sum(x) / real(size(x), ${k1}$)
42
+ res = sum(x) / real(size(x, kind = int64 ), ${k1}$)
43
43
44
44
end function mean_2_all_${k1}$_${k1}$
45
45
#:endfor
@@ -49,7 +49,7 @@ module function mean_2_all_${k1}$_dp(x) result(res)
49
49
${t1}$, intent(in) :: x(:,:)
50
50
real(dp) :: res
51
51
52
- res = sum(real(x, dp)) / real(size(x), dp)
52
+ res = sum(real(x, dp)) / real(size(x, kind = int64 ), dp)
53
53
54
54
end function mean_2_all_${k1}$_dp
55
55
#:endfor
@@ -58,7 +58,7 @@ end function mean_2_all_${k1}$_dp
58
58
module function mean_2_${k1}$_${k1}$(x, dim) result(res)
59
59
${t1}$, intent(in) :: x(:,:)
60
60
integer, intent(in) :: dim
61
- ${t1}$ :: res(size(x)/ size(x, dim))
61
+ ${t1}$ :: res(merge( size(x, 1), size(x, 2), mask = 1 < dim ))
62
62
63
63
select case(dim)
64
64
case(1)
@@ -76,7 +76,7 @@ end function mean_2_${k1}$_${k1}$
76
76
module function mean_2_${k1}$_dp(x, dim) result(res)
77
77
${t1}$, intent(in) :: x(:,:)
78
78
integer, intent(in) :: dim
79
- real(dp) :: res(size(x)/ size(x, dim))
79
+ real(dp) :: res(merge( size(x, 1), size(x, 2), mask = 1 < dim ))
80
80
81
81
select case(dim)
82
82
case(1)
@@ -95,23 +95,6 @@ end function mean_2_${k1}$_dp
95
95
#{if rank > 0}#(${":" + ",:" * (rank - 1)}$)#{endif}#
96
96
#:enddef
97
97
98
- !As proposed by @arady
99
- #:def varsuffix(rank)
100
- ${str(rank)}$
101
- #:enddef
102
-
103
- #:def varlist(varname, startlist, endlist)
104
- #:if startlist > 0
105
- ${",".join([varname + varsuffix(i) for i in range(startlist, endlist + 1)])}$
106
- #:endif
107
- #:enddef
108
-
109
- #:def varlistskip(varname, rank, dim)
110
- #:if rank > 0
111
- ${varlist(varname,1,dim-1)}$#{if dim -1 > 0 and dim < rank}#,#{endif}#${varlist(varname,dim+1,rank)}$
112
- #:endif
113
- #:enddef
114
-
115
98
#:if VERSION90
116
99
#:set ranks = range(3,8)
117
100
#:else
@@ -124,7 +107,7 @@ module function mean_${rank}$_all_${k1}$_${k1}$(x) result(res)
124
107
${t1}$, intent(in) :: x${ranksuffix(rank)}$
125
108
${t1}$ :: res
126
109
127
- res = sum(x) / real(size(x), ${k1}$)
110
+ res = sum(x) / real(size(x, kind = int64 ), ${k1}$)
128
111
129
112
end function mean_${rank}$_all_${k1}$_${k1}$
130
113
#:endfor
@@ -136,7 +119,7 @@ module function mean_${rank}$_all_${k1}$_dp(x) result(res)
136
119
${t1}$, intent(in) :: x${ranksuffix(rank)}$
137
120
real(dp) :: res
138
121
139
- res = sum(real(x, dp)) / real(size(x), dp)
122
+ res = sum(real(x, dp)) / real(size(x, kind = int64 ), dp)
140
123
141
124
end function mean_${rank}$_all_${k1}$_dp
142
125
#:endfor
@@ -156,7 +139,7 @@ module function mean_${rank}$_${k1}$_${k1}$(x, dim) result(res)
156
139
select case(dim)
157
140
#:for fi in range(1,rank+1)
158
141
case(${fi}$)
159
- res=sum(x, ${fi}$) / real(size(x, ${fi}$), ${k1}$)
142
+ res=sum(x, ${fi}$) / real(size(x, ${fi}$), ${k1}$)
160
143
#:endfor
161
144
case default
162
145
call error_stop("ERROR (mean): wrong dimension")
@@ -180,7 +163,7 @@ module function mean_${rank}$_${k1}$_dp(x, dim) result(res)
180
163
select case(dim)
181
164
#:for fi in range(1,rank+1)
182
165
case(${fi}$)
183
- res=sum(real(x, dp), ${fi}$) / real(size(x, ${fi}$), dp)
166
+ res=sum(real(x, dp), ${fi}$) / real(size(x, ${fi}$), dp)
184
167
#:endfor
185
168
case default
186
169
call error_stop("ERROR (mean): wrong dimension")
0 commit comments