source: flexpart.git/src/mean_mod.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 8.9 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4module mean_mod
5  public
6
7! Interface to select single or double precision version of the 'mean'
8! function from type of input arguments ("function overloading")
9!********************************************************************
10  interface mean
11    module procedure mean_sp
12    module procedure mean_dp
13    module procedure mean_mixed_dss
14    module procedure mean_mixed_dsd
15
16  end interface mean
17
18contains
19
20  subroutine mean_sp(x_sp,xm,xs,number)
21
22!*****************************************************************************
23!                                                                            *
24!  This subroutine calculates mean and standard deviation of a given element.*
25!                                                                            *
26!      AUTHOR: Andreas Stohl, 25 January 1994                                *
27!                                                                            *
28!      Single precision version ESO 2016                                     *
29!*****************************************************************************
30!                                                                            *
31! Variables:                                                                 *
32! x_sp(number)        field of input data                                    *
33! xm                  mean                                                   *
34! xs                  standard deviation                                     *
35! number              number of elements of field x_sp                       *
36!                                                                            *
37! Constants:                                                                 *
38! eps                 tiny number                                            *
39!                                                                            *
40!*****************************************************************************
41
42    use par_mod, only: sp
43
44    implicit none
45
46    ! integer :: number,i
47    ! real(sp) :: x_sp(number),xm,xs,xl,xq,xaux
48    ! real(sp),parameter :: eps=1.0e-30
49
50    integer,intent(in) :: number
51    real(sp), intent(in) :: x_sp(number)
52    real(sp), intent(out) ::xm,xs
53    real(sp) :: xl,xq,xaux
54    real(sp),parameter :: eps=1.0e-30
55    integer :: i
56
57    xl=0.
58    xq=0.
59    do i=1,number
60      xl=xl+x_sp(i)
61      xq=xq+x_sp(i)*x_sp(i)
62    end do
63
64    xm=xl/real(number,kind=sp)
65
66    xaux=xq-xl*xl/real(number,kind=sp)
67
68    if (xaux.lt.eps) then
69      xs=0.
70    else
71      xs=sqrt(xaux/real(number-1,kind=sp))
72    endif
73
74  end subroutine mean_sp
75
76  subroutine mean_dp(x_dp,xm,xs,number)
77
78!*****************************************************************************
79!                                                                            *
80!  This subroutine calculates mean and standard deviation of a given element.*
81!                                                                            *
82!      AUTHOR: Andreas Stohl, 25 January 1994                                *
83!                                                                            *
84!      Double precision version ESO 2016                                     *
85!*****************************************************************************
86!                                                                            *
87! Variables:                                                                 *
88! x_dp(number)        field of input data                                    *
89! xm                  mean                                                   *
90! xs                  standard deviation                                     *
91! number              number of elements of field x_dp                       *
92!                                                                            *
93! Constants:                                                                 *
94! eps                 tiny number                                            *
95!                                                                            *
96!*****************************************************************************
97
98    use par_mod, only: dp
99
100    implicit none
101
102    integer,intent(in) :: number
103    real(dp), intent(in) :: x_dp(number)
104    real(dp), intent(out) ::xm,xs
105    real(dp) :: xl,xq,xaux
106    real(dp),parameter :: eps=1.0e-30
107    integer :: i
108
109    xl=0._dp
110    xq=0._dp
111    do i=1,number
112      xl=xl+x_dp(i)
113      xq=xq+x_dp(i)*x_dp(i)
114    end do
115
116    xm=xl/real(number,kind=dp)
117
118    xaux=xq-xl*xl/real(number,kind=dp)
119
120    if (xaux.lt.eps) then
121      xs=0._dp
122    else
123      xs=sqrt(xaux/real(number-1,kind=dp))
124    endif
125
126  end subroutine mean_dp
127
128  subroutine mean_mixed_dss(x_dp,xm,xs,number)
129
130!*****************************************************************************
131!                                                                            *
132!  This subroutine calculates mean and standard deviation of a given element.*
133!                                                                            *
134!      AUTHOR: Andreas Stohl, 25 January 1994                                *
135!                                                                            *
136!      Mixed precision version ESO 2016 (dp in, sp out, sp out)              *
137!*****************************************************************************
138!                                                                            *
139! Variables:                                                                 *
140! x_dp(number)        field of input data                                    *
141! xm                  mean                                                   *
142! xs                  standard deviation                                     *
143! number              number of elements of field x_dp                       *
144!                                                                            *
145! Constants:                                                                 *
146! eps                 tiny number                                            *
147!                                                                            *
148!*****************************************************************************
149
150    use par_mod, only: sp,dp
151
152    implicit none
153
154    integer,intent(in) :: number
155    real(dp), intent(in) :: x_dp(number)
156    real(sp), intent(out) ::xm,xs
157    real(sp) :: xl,xq,xaux
158    real(sp),parameter :: eps=1.0e-30
159    integer :: i
160
161    xl=0._sp
162    xq=0._sp
163    do i=1,number
164      xl=xl+real(x_dp(i),kind=sp)
165      xq=xq+real(x_dp(i),kind=sp)*real(x_dp(i),kind=sp)
166    end do
167
168    xm=xl/real(number,kind=sp)
169
170    xaux=xq-xl*xl/real(number,kind=sp)
171
172    if (xaux.lt.eps) then
173      xs=0._sp
174    else
175      xs=sqrt(xaux/real(number-1,kind=sp))
176    endif
177
178  end subroutine mean_mixed_dss
179
180  subroutine mean_mixed_dsd(x_dp,xm,xs_dp,number)
181
182!*****************************************************************************
183!                                                                            *
184!  This subroutine calculates mean and standard deviation of a given element.*
185!                                                                            *
186!      AUTHOR: Andreas Stohl, 25 January 1994                                *
187!                                                                            *
188!      Mixed precision version ESO 2016 (dp in, sp out, dp out)              *
189!*****************************************************************************
190!                                                                            *
191! Variables:                                                                 *
192! x_dp(number)        field of input data                                    *
193! xm                  mean                                                   *
194! xs_dp               standard deviation                                     *
195! number              number of elements of field x_dp                       *
196!                                                                            *
197! Constants:                                                                 *
198! eps                 tiny number                                            *
199!                                                                            *
200!*****************************************************************************
201
202    use par_mod, only: sp,dp
203
204    implicit none
205
206    integer,intent(in) :: number
207    real(dp), intent(in) :: x_dp(number)
208    real(sp), intent(out) ::xm
209    real(dp), intent(out) ::xs_dp
210    real(dp) :: xl,xq,xaux
211    real(dp),parameter :: eps=1.0e-30_dp
212    integer :: i
213
214    xl=0._dp
215    xq=0._dp
216    do i=1,number
217      xl=xl+x_dp(i)
218      xq=xq+x_dp(i)*x_dp(i)
219    end do
220
221    xm=real(xl,kind=sp)/real(number,kind=sp)
222
223    xaux=xq-xl*xl/real(number,kind=dp)
224
225    if (xaux.lt.eps) then
226      xs_dp=0._dp
227    else
228      xs_dp=sqrt(xaux/real(number-1,kind=dp))
229    endif
230
231  end subroutine mean_mixed_dsd
232
233end module mean_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG