source: flexpart.git/src/mean_mod.f90 @ 02095e3

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 02095e3 was b5127f9, checked in by Espen Sollum ATMOS <eso@…>, 7 years ago

Fixed an inconsistency (serial vs parallel) with domain-filling option

  • Property mode set to 100644
File size: 10.2 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22module mean_mod
23  public
24
25! Interface to select single or double precision version of the 'mean'
26! function from type of input arguments ("function overloading")
27!********************************************************************
28  interface mean
29    module procedure mean_sp
30    module procedure mean_dp
31    module procedure mean_mixed_dss
32    module procedure mean_mixed_dsd
33
34  end interface mean
35
36contains
37
38  subroutine mean_sp(x_sp,xm,xs,number)
39
40!*****************************************************************************
41!                                                                            *
42!  This subroutine calculates mean and standard deviation of a given element.*
43!                                                                            *
44!      AUTHOR: Andreas Stohl, 25 January 1994                                *
45!                                                                            *
46!      Single precision version ESO 2016                                     *
47!*****************************************************************************
48!                                                                            *
49! Variables:                                                                 *
50! x_sp(number)        field of input data                                    *
51! xm                  mean                                                   *
52! xs                  standard deviation                                     *
53! number              number of elements of field x_sp                       *
54!                                                                            *
55! Constants:                                                                 *
56! eps                 tiny number                                            *
57!                                                                            *
58!*****************************************************************************
59
60    use par_mod, only: sp
61
62    implicit none
63
64    ! integer :: number,i
65    ! real(sp) :: x_sp(number),xm,xs,xl,xq,xaux
66    ! real(sp),parameter :: eps=1.0e-30
67
68    integer,intent(in) :: number
69    real(sp), intent(in) :: x_sp(number)
70    real(sp), intent(out) ::xm,xs
71    real(sp) :: xl,xq,xaux
72    real(sp),parameter :: eps=1.0e-30
73    integer :: i
74
75    xl=0.
76    xq=0.
77    do i=1,number
78      xl=xl+x_sp(i)
79      xq=xq+x_sp(i)*x_sp(i)
80    end do
81
82    xm=xl/real(number,kind=sp)
83
84    xaux=xq-xl*xl/real(number,kind=sp)
85
86    if (xaux.lt.eps) then
87      xs=0.
88    else
89      xs=sqrt(xaux/real(number-1,kind=sp))
90    endif
91
92  end subroutine mean_sp
93
94  subroutine mean_dp(x_dp,xm,xs,number)
95
96!*****************************************************************************
97!                                                                            *
98!  This subroutine calculates mean and standard deviation of a given element.*
99!                                                                            *
100!      AUTHOR: Andreas Stohl, 25 January 1994                                *
101!                                                                            *
102!      Double precision version ESO 2016                                     *
103!*****************************************************************************
104!                                                                            *
105! Variables:                                                                 *
106! x_dp(number)        field of input data                                    *
107! xm                  mean                                                   *
108! xs                  standard deviation                                     *
109! number              number of elements of field x_dp                       *
110!                                                                            *
111! Constants:                                                                 *
112! eps                 tiny number                                            *
113!                                                                            *
114!*****************************************************************************
115
116    use par_mod, only: dp
117
118    implicit none
119
120    integer,intent(in) :: number
121    real(dp), intent(in) :: x_dp(number)
122    real(dp), intent(out) ::xm,xs
123    real(dp) :: xl,xq,xaux
124    real(dp),parameter :: eps=1.0e-30
125    integer :: i
126
127    xl=0._dp
128    xq=0._dp
129    do i=1,number
130      xl=xl+x_dp(i)
131      xq=xq+x_dp(i)*x_dp(i)
132    end do
133
134    xm=xl/real(number,kind=dp)
135
136    xaux=xq-xl*xl/real(number,kind=dp)
137
138    if (xaux.lt.eps) then
139      xs=0._dp
140    else
141      xs=sqrt(xaux/real(number-1,kind=dp))
142    endif
143
144  end subroutine mean_dp
145
146  subroutine mean_mixed_dss(x_dp,xm,xs,number)
147
148!*****************************************************************************
149!                                                                            *
150!  This subroutine calculates mean and standard deviation of a given element.*
151!                                                                            *
152!      AUTHOR: Andreas Stohl, 25 January 1994                                *
153!                                                                            *
154!      Mixed precision version ESO 2016 (dp in, sp out, sp out)              *
155!*****************************************************************************
156!                                                                            *
157! Variables:                                                                 *
158! x_dp(number)        field of input data                                    *
159! xm                  mean                                                   *
160! xs                  standard deviation                                     *
161! number              number of elements of field x_dp                       *
162!                                                                            *
163! Constants:                                                                 *
164! eps                 tiny number                                            *
165!                                                                            *
166!*****************************************************************************
167
168    use par_mod, only: sp,dp
169
170    implicit none
171
172    integer,intent(in) :: number
173    real(dp), intent(in) :: x_dp(number)
174    real(sp), intent(out) ::xm,xs
175    real(sp) :: xl,xq,xaux
176    real(sp),parameter :: eps=1.0e-30
177    integer :: i
178
179    xl=0._sp
180    xq=0._sp
181    do i=1,number
182      xl=xl+real(x_dp(i),kind=sp)
183      xq=xq+real(x_dp(i),kind=sp)*real(x_dp(i),kind=sp)
184    end do
185
186    xm=xl/real(number,kind=sp)
187
188    xaux=xq-xl*xl/real(number,kind=sp)
189
190    if (xaux.lt.eps) then
191      xs=0._sp
192    else
193      xs=sqrt(xaux/real(number-1,kind=sp))
194    endif
195
196  end subroutine mean_mixed_dss
197
198  subroutine mean_mixed_dsd(x_dp,xm,xs_dp,number)
199
200!*****************************************************************************
201!                                                                            *
202!  This subroutine calculates mean and standard deviation of a given element.*
203!                                                                            *
204!      AUTHOR: Andreas Stohl, 25 January 1994                                *
205!                                                                            *
206!      Mixed precision version ESO 2016 (dp in, sp out, dp out)              *
207!*****************************************************************************
208!                                                                            *
209! Variables:                                                                 *
210! x_dp(number)        field of input data                                    *
211! xm                  mean                                                   *
212! xs_dp               standard deviation                                     *
213! number              number of elements of field x_dp                       *
214!                                                                            *
215! Constants:                                                                 *
216! eps                 tiny number                                            *
217!                                                                            *
218!*****************************************************************************
219
220    use par_mod, only: sp,dp
221
222    implicit none
223
224    integer,intent(in) :: number
225    real(dp), intent(in) :: x_dp(number)
226    real(sp), intent(out) ::xm
227    real(dp), intent(out) ::xs_dp
228    real(dp) :: xl,xq,xaux
229    real(dp),parameter :: eps=1.0e-30_dp
230    integer :: i
231
232    xl=0._dp
233    xq=0._dp
234    do i=1,number
235      xl=xl+x_dp(i)
236      xq=xq+x_dp(i)*x_dp(i)
237    end do
238
239    xm=real(xl,kind=sp)/real(number,kind=sp)
240
241    xaux=xq-xl*xl/real(number,kind=dp)
242
243    if (xaux.lt.eps) then
244      xs_dp=0._dp
245    else
246      xs_dp=sqrt(xaux/real(number-1,kind=dp))
247    endif
248
249  end subroutine mean_mixed_dsd
250
251end module mean_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG