SUBROUTINE phot_mat(rho, n, g0, g1, g2, dmu, psi, gamma, rhoval) ! ! interpolates dipole moment function, ! reads lower state wave function, ! determines dipole operator clebsch gordon algebra, ! combines these three elements to create inhomogeneity gamma ! ! -m. braunstein, Jan. 1991 ! USE FileUnits_MODULE USE TotalEng_Module USE Masses_Module USE fuzzy_MODULE USE centerho_MODULE USE Numbers_MODULE USE constnts_MODULE USE dip_MODULE IMPLICIT NONE !#include !#include !#include !#include !#include !#include !#include !#include LOGICAL little, medium, full, midzero INTEGER n, nrho, nmodes, i, j, maxrho, npoint, ia, ib, ic REAL(Kind=WP_Kind) rho, rholast, wig, rho0, rho1, rho2, a0, a1, a2, fact REAL(Kind=WP_Kind) cleb, efield, sum, rhop, ra, rb, rc REAL(Kind=WP_Kind) g0(n,n), g1(n,n), g2(n,n), dmu(n,n), psi(n) REAL(Kind=WP_Kind) gamma(n), rhoval(*) !---------------------------------------------------------------------- ! rho hyperpsherical radius ! n number of coupled equations ! dmu dipole moment matrix evaluated at rho. dipole moment matrix ! the determined by a lagrange interpolation of w0, w1, w2. ! g0 stores dipole moment matrix at rho-0 ! g1 stores dipole moment matrix at rho-1 ! g2 stores dipole moment matrix at rho-2 ! psi wave function for lower state ! gamma inhomogeneous term !----------------------------------------------------------------------- ! start of a new sector read in values of the dipole matrix element !----------------------------------------------------------------------- DATA little/.false./,medium/.false./,full/.false./ DATA nrho/1/ DATA rholast/-1.d0/,midzero/.true./ ! DATA wig/0.d0/ ! ! read control ! WRITE(Out_Unit,*)'rho,rholast',rho,rholast 1 IF((rho>rhoval(nrho).AND.ABS(rho-rhoval(nrho))>fuzz) & .or.ABS(rho-rholast)nrho)GOTO 1 ! rho0=rho1 ! rho1=rho2 ! rho2=rhoval(maxrho) ! DO 50 j=1,nmodes ! IF(j<=n)THEN ! DO 60 i=1,n ! g0(i,j)=g1(i,j) ! 60 g1(i,j)=g2(i,j) ! READ(dmu_unit)(g2(i,j),i=1,n) ! ELSE ! READ(dmu_unit) ! ENDIF ! 50 CONTINUE ! ENDIF !---------------------------------------------------------------------- ! set lagrange constants to determine electronic dipole moment at rho. !---------------------------------------------------------------------- IF(ABS(rho1-rho2)