SUBROUTINE DVR_kinetic(ntheta,t_theta,theta_val) !---------------------------------------------------------------------- ! USE the DVR method to construct the theta kninetic energy !--------------------------------------------------------------------- USE Numeric_Kinds_module USE FileUnits_Module USE DVR2_MODULE USE CommonInfo_Module USE masses_module IMPLICIT NONE !============================================================================== LOGICAL :: debug INTEGER :: ntheta,ltheta,i,j,info REAL(KIND=dp) :: t_theta(ntheta,ntheta),theta_val(ntheta) REAL(KIND=dp) :: phi(ntheta,ntheta) debug=.false. ltheta=0 ntheta=ntheta-1 !============================================================================== ! Set up dvr transformation for theta CALL tdv2fb1(ttheta,pttheta,whtheta,ntheta,ltheta, nthetmax,debug) ntheta=ntheta-ltheta+1 !============================================================================== ! Angmomthe determines the dvr j^2 matrix for theta and puts it in antothet CALL anmomthe(ttheta,pttheta,ntheta,nthetmax,ltheta,antothet,thetaj, debug) antothet=antothet/usys2 !============================================================================== ! Get the theta values. DO i=1,ntheta theta_val(i)=acos(pttheta(i))/2.0d0 DO j=1,ntheta t_theta(i,j)=antothet(i,j) ENDDO ENDDO !============================================================================== ! Check the symmetry of t_theta DO i=1,ntheta DO j=1,i-1 IF(abs(t_theta(i,j)-t_theta(j,i)).gt.1.0d-10) stop 'wrong' ENDDO ENDDO return END