SUBROUTINE diatomic_v(s,v,ichanl) ! !============================================================================================== ! This routine obtains a value of the diatomic potential at a given Jacobi Mass-Scaled s value. !============================================================================================== ! USE Numeric_Kinds_Module USE CommonInfo_Module USE Jacobi_Module Use Das_Module IMPLICIT NONE ! ! Set two of the interparticle separations to very large values to obtain the asymptotic diatomic potential ! Let r(1) be the diatomic internuclear distance !========================================================================================= ! I N P U T REAL(dp),INTENT(IN) :: s INTEGER :: ichanl !========================================================================================= ! O U T P U T REAL(dp),INTENT(OUT) :: v !========================================================================================= ! I N T E R N A L S REAL(dp) :: r(3) ! Interparticle separations !========================================================================================= ! Unscale Jacobi s coordinate and assign it to r(1). Scaling coefficient is d ! Set two of the interparticle separations to large values IF (ichanl.eq.1) THEN r(1)=dscale(1)*s r(2)=1.d30 r(3)=1.d30 ELSEIF (ichanl.eq.2) THEN r(2)=dscale(2)*s r(3)=1.d30 r(1)=1.d30 ELSEIF (ichanl.eq.3) THEN r(3)=dscale(3)*s r(1)=1.d30 r(2)=1.d30 ENDIF !=============================================== ! Obtain value of the diatomic potential at r(1) CALL surface(v,r) END SUBROUTINE diatomic_v