Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/erf.f90

    • Property svn:executable set to *
    r13 r4  
    4242
    4343  integer :: j
    44   real(kind=dp) :: x,tmp,ser,xx,gammln
    45   real(KIND=dp) :: cof(6) = (/ &
     44  real :: x,tmp,ser,xx,gammln
     45  real :: cof(6) = (/ &
    4646       76.18009173_dp, -86.50532033_dp, 24.01409822_dp, &
    4747       -1.231739516_dp, .120858003e-2_dp, -.536382e-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
     48  real :: stp = 2.50662827465_dp
     49  real :: half = 0.5_dp, one = 1.0_dp, fpf = 5.5_dp
    5050
    5151  x=xx-one
     
    6262function gammp(a,x)
    6363
    64   use par_mod, only: dp
    65 
    66   implicit none
    67 
    68   real(KIND=dp) :: a, x, gln, gamser, gammp, gammcf
     64  implicit none
     65
     66  real :: a, x, gln, gamser, gammp, gammcf
    6967
    7068  if(x .lt. 0. .or. a .le. 0.) then
     
    8381function gammq(a,x)
    8482
    85   use par_mod, only: dp
    86 
    87   implicit none
    88 
    89   real(KIND=dp) :: a, x, gln, gamser, gammq, gammcf
     83  implicit none
     84
     85  real :: a, x, gln, gamser, gammq, gammcf
    9086
    9187  if(x.lt.0..or.a.le.0.) then
     
    104100subroutine gser(gamser,a,x,gln)
    105101
    106   use par_mod, only: dp
    107 
    108102  implicit none
    109103
    110104  integer :: n
    111   real(KIND=dp) :: gamser, a, x, gln, ap, summ, del
    112   real(KIND=dp), external :: gammln
     105  real :: gamser, a, x, gln, ap, summ, del
     106  real, external :: gammln
    113107
    114108  integer,parameter :: itmax=100
     
    140134subroutine gcf(gammcf,a,x,gln)
    141135
    142   use par_mod, only: dp
    143 
    144136  implicit none
    145137
    146138  integer :: n
    147   real(KIND=4) :: gammcf, x, a, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
    148   real(KIND=dp), external :: gammln
     139  real :: gammcf, a, x, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
     140  real, external :: gammln
    149141
    150142  integer,parameter :: itmax=100
     
    180172function erf(x)
    181173
    182   use par_mod, only: dp
    183 
    184   implicit none
    185 
    186   real(KIND=dp) :: x, erf
    187   real(KIND=dp), external :: gammp
     174  implicit none
     175
     176  real :: x, erf
     177  real, external :: gammp
    188178
    189179  if(x.lt.0.)then
     
    196186function erfc(x)
    197187
    198   use par_mod, only: dp
    199 
    200   implicit none
    201 
    202   real(KIND=dp) :: x, erfc
    203   real(KIND=dp), external :: gammp, gammq
     188  implicit none
     189
     190  real :: x, erfc
     191  real, external :: gammp, gammq
    204192
    205193  if(x.lt.0.)then
     
    212200function erfcc(x)
    213201
    214   use par_mod, only: dp
    215 
    216   implicit none
    217 
    218   real(KIND=dp) :: x, z, t, erfcc
     202  implicit none
     203
     204  real :: x, z, t, erfcc
    219205
    220206  z=abs(x)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG