SUBROUTINE enlvls(r, n, w) ! P U R P O S E O F S U B R O U T I N E ! Calculates the adiabatic energy levels. ! I N P U T A R G U M E N T S ! r Current propagation distance. ! w Interaction matrix to be diagonalized. The eigenvalues are ! the adabatic energy levels. ! n Dimension of the matrix w. ! O U T P U T A R G U M E N T S ! NONE ! <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> USE FileUnits_Module USE nstate_Module USE doenlvls_Module USE TotalEng_Module USE Masses_Module USE convrsns_Module USE engpro_Module IMPLICIT NONE INTEGER n, ithcall, ithsub, nn2, i LOGICAL little, medium, full REAL(Kind=WP_Kind) w(n*n), temp(nstate*(nstate+1)/2), elevls(nstate), scr(nstate), vec(nstate*nstate) REAL(Kind=WP_Kind) r, xkin INTEGER, PARAMETER :: ione=1 !------------------------------------------------------------------ ! Obtain printing options. !------------------------------------------------------------------ DATA ithcall/0/, ithsub/0/ DATA little/.false./, medium/.false./, full/.false./ CALL popt('enlvls ', little, medium, full, ithcall, ithsub) !------------------------------------------------------------------ ! WRITE(Msg_Unit,*)'here*********************',lenlvls,kenergy IF(.NOT.lenlvls.or.kenergy>1)RETURN !trp>> Following line commented out 9/12/97 to conform to Sefano's code. c<