Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/FLEXPART_9.1.3/src/erf.f90

    • Property svn:executable deleted
    r4 r13  
    4242
    4343  integer :: j
    44   real :: x,tmp,ser,xx,gammln
    45   real :: cof(6) = (/ &
     44  real(kind=dp) :: x,tmp,ser,xx,gammln
     45  real(KIND=dp) :: cof(6) = (/ &
    4646       76.18009173_dp, -86.50532033_dp, 24.01409822_dp, &
    4747       -1.231739516_dp, .120858003e-2_dp, -.536382e-5_dp    /)
    48   real :: stp = 2.50662827465_dp
    49   real :: half = 0.5_dp, one = 1.0_dp, fpf = 5.5_dp
     48  real(KIND=dp) :: stp = 2.50662827465_dp
     49  real(KIND=dp) :: half = 0.5_dp, one = 1.0_dp, fpf = 5.5_dp
    5050
    5151  x=xx-one
     
    6262function gammp(a,x)
    6363
    64   implicit none
    65 
    66   real :: a, x, gln, gamser, gammp, gammcf
     64  use par_mod, only: dp
     65
     66  implicit none
     67
     68  real(KIND=dp) :: a, x, gln, gamser, gammp, gammcf
    6769
    6870  if(x .lt. 0. .or. a .le. 0.) then
     
    8183function gammq(a,x)
    8284
    83   implicit none
    84 
    85   real :: a, x, gln, gamser, gammq, gammcf
     85  use par_mod, only: dp
     86
     87  implicit none
     88
     89  real(KIND=dp) :: a, x, gln, gamser, gammq, gammcf
    8690
    8791  if(x.lt.0..or.a.le.0.) then
     
    100104subroutine gser(gamser,a,x,gln)
    101105
     106  use par_mod, only: dp
     107
    102108  implicit none
    103109
    104110  integer :: n
    105   real :: gamser, a, x, gln, ap, summ, del
    106   real, external :: gammln
     111  real(KIND=dp) :: gamser, a, x, gln, ap, summ, del
     112  real(KIND=dp), external :: gammln
    107113
    108114  integer,parameter :: itmax=100
     
    134140subroutine gcf(gammcf,a,x,gln)
    135141
     142  use par_mod, only: dp
     143
    136144  implicit none
    137145
    138146  integer :: n
    139   real :: gammcf, a, x, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
    140   real, external :: gammln
     147  real(KIND=4) :: gammcf, x, a, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
     148  real(KIND=dp), external :: gammln
    141149
    142150  integer,parameter :: itmax=100
     
    172180function erf(x)
    173181
    174   implicit none
    175 
    176   real :: x, erf
    177   real, external :: gammp
     182  use par_mod, only: dp
     183
     184  implicit none
     185
     186  real(KIND=dp) :: x, erf
     187  real(KIND=dp), external :: gammp
    178188
    179189  if(x.lt.0.)then
     
    186196function erfc(x)
    187197
    188   implicit none
    189 
    190   real :: x, erfc
    191   real, external :: gammp, gammq
     198  use par_mod, only: dp
     199
     200  implicit none
     201
     202  real(KIND=dp) :: x, erfc
     203  real(KIND=dp), external :: gammp, gammq
    192204
    193205  if(x.lt.0.)then
     
    200212function erfcc(x)
    201213
    202   implicit none
    203 
    204   real :: x, z, t, erfcc
     214  use par_mod, only: dp
     215
     216  implicit none
     217
     218  real(KIND=dp) :: x, z, t, erfcc
    205219
    206220  z=abs(x)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG