SUBROUTINE get_erange USE Numeric_Kinds_Module USE CommonInfo_Module USE APH_Module USE Aph_Ham_Module USE SurfaceAph_Module USE Cheby_Module USE SymGroup_Module USE Masses_Module USE Convrsns_Module IMPLICIT NONE !============================================================================== ! Diagonalize kinetic energy operators. Chi and theta eigenvectors will ! be used ! to reduce the maximum aggregate eigenvalue. ! Assign energy bounds for chebychev propagation. !============================================================================== INTEGER :: i, iir, nchir first_theta=.true. clip_theta=.true. ALLOCATE( rho_eig(nrho) , rho_evec(nrho,nrho) ) ALLOCATE( tht_eig(ntheta) , tht_evec(ntheta,ntheta) , weights(ntheta)) ALLOCATE( compr2(ntheta, ntheta), compr_mat2(ntheta, ntheta, ntheta) ) ALLOCATE( tempvcut2(ntheta,ntheta), tempeig2(ntheta,ntheta) ) ALLOCATE( t_theta_clip(ntheta,ntheta), num_eig2(nrho) ) ! RHO ! ======================================================================== CALL diag_out(nrho, t_rho,rho_val,deltarho,1.d0,rho_eig,rho_evec,'rho') eigmax=rho_eig(nrho) ! THETA ! ====================================================================== ! weights determined by matching ground state to 1/Sqrt(2) IF (ntheta.gt.1) THEN CALL diag_out(ntheta, t_theta, theta_val, 1.d0, 1.d0, tht_eig,tht_evec, 'theta') Do i=1,ntheta weights(i)=2.d0*tht_evec(i,1)*tht_evec(i,1) Enddo IF (clip_theta) THEN eigmax=eigmax+vcut ELSE eigmax=eigmax+(tht_eig(ntheta)*rhom2(1)) ENDIF ELSE weights(1)=1.d0 ENDIF ! CHI ======================================================================== ! No need to diagonalize yet, eigmax will be set to vcut ! Create array that provides the location of each irreducible representaion ! block. ALLOCATE(indexchi_array(nirrep)) indexchi_array(1)=0 DO iir=1,nirrep-1 nchir=nchi_ir(iir) indexchi_array(iir+1)=indexchi_array(iir)+nchir ENDDO eigmax=eigmax+vcut+vcut+((15.d0*rhom2(1))/(4.d0*usys2)) eigmin=0.d0 !============================================================================== ! Write max eigenvalue information !------------------------------------------------------------------------------ WRITE(Out_Unit,71) 'Eigenvalue Info:','au','eV' WRITE(Out_Unit,72) 'rho eigmax', rho_eig(nrho), rho_eig(nrho)*autoev WRITE(Out_Unit,72) 'tht eigmax', tht_eig(ntheta)*rhom2(1), & tht_eig(ntheta)*rhom2(1)*autoev WRITE(Out_Unit,72) 'chi eigmax', vcut, vcut*autoev WRITE(Out_Unit,72) 'vcut ', vcut, vcut*autoev WRITE(Out_Unit,72) 'total ', eigmax, eigmax*autoev 71 FORMAT (/1X,a,T24,a,T34,a,/1X,50('-')) 72 FORMAT (1X,a,10('.'),f7.4,3X,f7.3) 73 FORMAT (1X,a,10('.'),f10.7,3X,f10.7) DEALLOCATE(rho_eig, rho_evec) END SUBROUTINE get_erange