source: flexpart.git/src/mean_mod.f90 @ 3481cc1

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

move license from headers to a different file

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