ze1.f90 1.35 KB
function  ze1(z)
!
!       ====================================================
!       Purpose: Compute complex exponential integral E1(z)
!       Input :  z   --- Argument of E1(z)
!       Output:  CE1 --- E1(z)
!       ====================================================
!
! Déclaration des variables en passage de paramètre
!
use fvn_common
implicit none
complex(kind=dp_kind), intent(in) :: z
complex(kind=dp_kind) :: ze1
!
!  Déclaration des variables locales
!
integer(kind=ip_kind) :: k
real(kind=dp_kind) :: x,a0
complex(kind=dp_kind) :: cr,ct0,ct

!
! traitement en fonction des différents cas
! - Z nul entraîne E1 infini
! - module de Z inférieur à 10 ou 20 : formule log+gam+somme
! - module de Z supérieur à 10 ou 20 : formule asymptotique
!
 x=real(z)
 a0=abs(z)
 if (a0==0.0D0) then
   ze1 = cmplx(1.0D+300,0.0D0,dp_kind)
 else if ((a0 <= 10.D0).or.(x <= 0.D0.and.a0 <= 20.D0)) then
   ze1 = cmplx(1.0D0,0.0D0,dp_kind)
   cr = cmplx(1.0D0,0.0D0,dp_kind)
   k=0
   do while (abs(cr)>=abs(ze1)*1.0D-15)
     k = k+1
     cr = -cr*k*z/(k+1.0D0)**2
     ze1 = ze1+cr
   end do
   ze1 = -fvn_el-log(z)+z*ze1
 else
   ct0 = cmplx(0.0D0,0.0D0,dp_kind)
   do k=120,1,-1
      ct0 = k/(1.0D0+k/(z+ct0))
   end do
   ct = 1.0D0/(z+ct0)
   ze1 = exp(-z)*ct
   if (x <= 0.D0 .AND. aimag(z) == 0.0d0) ze1 = ze1-fvn_pi*cmplx(0.D0,1.D0,dp_kind)
 end if
!
 return
end function