Changes in src/mean_mod.f90 [4c64400:6a678e3] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/mean_mod.f90

    r4c64400 r6a678e3  
    2929    module procedure mean_sp
    3030    module procedure mean_dp
    31     module procedure mean_mixed_dss
    32     module procedure mean_mixed_dsd
    33 
     31    module procedure mean_mixed_prec
    3432  end interface mean
    3533
     
    6664    ! real(sp),parameter :: eps=1.0e-30
    6765
    68     integer,intent(in) :: number
    6966    real(sp), intent(in) :: x_sp(number)
    7067    real(sp), intent(out) ::xm,xs
     68    integer,intent(in) :: number
    7169    real(sp) :: xl,xq,xaux
    7270    real(sp),parameter :: eps=1.0e-30
     
    118116    implicit none
    119117
    120     integer,intent(in) :: number
    121118    real(dp), intent(in) :: x_dp(number)
    122119    real(dp), intent(out) ::xm,xs
     120    integer,intent(in) :: number
    123121    real(dp) :: xl,xq,xaux
    124122    real(dp),parameter :: eps=1.0e-30
     
    144142  end subroutine mean_dp
    145143
    146   subroutine mean_mixed_dss(x_dp,xm,xs,number)
     144  subroutine mean_mixed_prec(x_dp,xm,xs,number)
    147145
    148146!*****************************************************************************
     
    152150!      AUTHOR: Andreas Stohl, 25 January 1994                                *
    153151!                                                                            *
    154 !      Mixed precision version ESO 2016 (dp in, sp out, sp out)              *
     152!      Mixed precision version ESO 2016 (dp input, sp output)                *
    155153!*****************************************************************************
    156154!                                                                            *
     
    170168    implicit none
    171169
    172     integer,intent(in) :: number
    173170    real(dp), intent(in) :: x_dp(number)
    174171    real(sp), intent(out) ::xm,xs
     172    integer,intent(in) :: number
    175173    real(sp) :: xl,xq,xaux
    176174    real(sp),parameter :: eps=1.0e-30
     
    194192    endif
    195193
    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=xl/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 
     194  end subroutine mean_mixed_prec
    251195end module mean_mod
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG