SUBROUTINE Surface(v,rij) USE Numeric_Kinds_Module USE FileUnits_Common_Module USE PES_MODULE IMPLICIT NONE !----------------------------------------------------------------------- ! This routine supplies the potential energy surface for the ! reactive scattering codes. ! ! On entering: The array rij contains the internuclear distances ! in units of bohr (NOT mass scaled). ! ! On Exit: The variable v is the value of the potential energy ! surface in Hartree atomic units. ! ! !----------------------------------------------------------------------- REAL(KIND=WP_Kind) rij(3), v, r1, r2, r3, scf, e1, e2, e3, eps3, e4 EXTERNAL He3 CHARACTER(LEN=25) potname !----------------------------------------------------------------------- ! The character string potname must contain a string that uniquely ! specifies the potential energy surface to be used. !----------------------------------------------------------------------- DATA potname/'He3 CC fit (205 points) '/ !----------------------------------------------------------------------- ! Check for correct potential energy surface specification. !----------------------------------------------------------------------- IF(PES_Name/=potname)THEN WRITE(Out_Unit,*)'The potential energy surface name ', 'does not match', & ' the name in the potential energy surface routine.' WRITE(Out_Unit,'(1x,2a25)')PES_Name,potname WRITE(Out_Unit,*)'***error***: Execution stopped in ', 'routine surface' STOP "Surface" ENDIF !----------------------------------------------------------------------- ! This call to surfac supplies the potential energy surface ! for the particular system of interest. !----------------------------------------------------------------------- r1=rij(1) r2=rij(2) r3=rij(3) call He3 (R1, R2, R3, scf, e1, e2, e3, eps3, e4) tot=scf+e1+e2+e3+e4 RETURN ENDSUBROUTINE Surface