SUBROUTINE Surface(Vtot,rij) USE Numeric_Kinds_Module USE PES_Module IMPLICIT NONE CHARACTER(LEN=25) PotName REAL*8 Vtot, rij, r4pot DIMENSION rij(3), r4pot(3) EXTERNAL VLiH2 !----------------------------------------------------------------------- ! The character string potname must contain a string that uniquely ! specifies the potential energy surface to be used. !----------------------------------------------------------------------- DATA PotName/'LiH2_Gianturco_Pot'/ !----------------------------------------------------------------------- ! Check for correct potential energy surface specification. !----------------------------------------------------------------------- IF(Pes_Name.ne.PotName)THEN WRITE(6,*)'Pes_Name is not equal to PotName.' WRITE(6,*)'***error***: Execution stopped in routine surface: VLiH2' WRITE(6,'(1x,A)')' Name read in from input data: ', Pes_Name WRITE(6,'(1x,A)')' Name of the potential energy surface routine: ',PotName STOP 'surface: VLiH2' ENDIF !----------------------------------------------------------------------- ! This call to surfac supplies the potential energy surface ! for the particular system of interest. !----------------------------------------------------------------------- r4Pot(1)=rij(3) r4Pot(2)=rij(1) r4Pot(3)=rij(2) CALL VLiH2_Gianturco(r4pot,Vtot) !The total energy is the collision energy for Li+H2 (v=0,j=0) RETURN ENDSUBROUTINE Surface