!---------------------------------------------------------------------- SUBROUTINE potaph (rho, theta, xchi, pot) USE Numeric_Kinds_Module USE FileUnits_Module USE Masses_Module USE Save_Module USE Narran_Module ! P U R P O S E O F S U B R O U T I N E ! This routine calculates interparticle distances in Bohr and THEN ! calls surface to determine the interaction potential in Hartree's. ! I N P U T A R G U M E N T S ! rho hyperradius in Bohr. (0 < rho < infinity) ! theta hyperangle theta in radians. (0 < theta < pi/2) ! xchi hyperangle chi in radians. (0 < chi < 2pi) ! O U T P U T A R G U M E N T S ! pot potential energy V(rho,theta,chi) in Hartree atomic units. ! <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> IMPLICIT NONE ! I N T E G E R S INTEGER :: k ! R E A L S REAL (dp) :: pot, rho, theta, xchi, sbig (narran) !----------------------------------------------------------------------- ! Calculate the interpartical distances and store them in the arrary r. !----------------------------------------------------------------------- chi3 (1) = xchi chi3 (2) = chi3 (1) - chij (2, 1) chi3 (3) = chi3 (1) - chij (3, 1) DO k = 1, narran s (k) = rho * sqrt (0.5d0 - 0.5d0 * sin (theta) * cos (2.d0 * chi3 (k) ) ) sbig (k) = rho * sqrt (0.5d0 + 0.5d0 * sin (theta) * cos (2.d0 * chi3 (k) ) ) r (k) = d (k) * s (k) ENDDO !----------------------------------------------------------------------- ! This CALL returns the interaction potential in Hartree atomic units. !----------------------------------------------------------------------- CALL surface (pot, r) RETURN END SUBROUTINE potaph