SUBROUTINE pot(r, v0, v1, v2, jval, mu, ichanl) USE Numeric_Kinds_Module IMPLICIT none !============================================================================== ! This subroutine determines the effective electronic potential for the ! specified r and jval values !============================================================================== INTEGER :: jval, ichanl REAL(dp), PARAMETER :: re=2.d0, de=2.d0, beta=2.5d0, vasy=0.d0 REAL(dp) :: r, v0, v1, v2, mu, cent0, cent1, cent2, h REAL(dp) :: vph,vmh vmh=0.d0 vph=0.d0 !============================================================================= ! Determine actual electronic potential and its derivatives CALL diatomic_v(r,v0,ichanl) h=1.d-4 CALL diatomic_v(r+h,vph,ichanl) CALL diatomic_v(r-h,vmh,ichanl) v1=(vph-vmh)/(2.d0*h) CALL diatomic_v(r+2.d0*h,vph,ichanl) CALL diatomic_v(r-2.d0*h,vmh,ichanl) v2=(vph-2.d0*v0+vmh)/(4.d0*h**2) ! These initial values are needed in order to prevent V from going to infinity IF(r.eq.0)THEN v1=-68.0d0 v2=1.86d0 ENDIF !============================================================================== ! Determine and add centrifugal term of effective electronic potential ! to the actual electronic potential IF (jval.gt.0) THEN CALL CenTerm(r, jval, mu, cent0, cent1, cent2) v0=v0+cent0 v1=v1+cent1 v2=v2+cent2 ENDIF RETURN END SUBROUTINE pot