! SUBROUTINE CenTerm(r, jval, mu, cent0, cent1, cent2) USE Numeric_Kinds_Module IMPLICIT NONE !============================================================================== ! This subroutine determines the centrifugal barrier term of the effective ! electronic potential for the specified r, jval, and mu values !============================================================================== INTEGER :: jval REAL(dp) :: r, mu, cent0, cent1, cent2 !============================================================================== !determine the centrifugal term of the effective electronic potential, !along with the first and second derivative IF(jval.ne.0)THEN !centrifugal term not present when j=0 IF(r.ne.0.d0)THEN cent0=jval*(jval+1)/(2.d0*mu*r**2) !equation for centrifugal term cent1=-2.d0*cent0/r !derivative with respect to r cent2= 6.d0*cent0/r**2 !second derivative with respect to r ENDIF ELSE !no centrifugal term present when j=0 cent0=0.d0 cent1=0.d0 cent2=0.d0 ENDIF RETURN END SUBROUTINE CenTerm