SUBROUTINE Get_DAF(nxval, xval, delta, mval, dafx, hermit, ndaf, nd_daf, toe, usys2, kmax) USE FileUnits_Module USE DAFSigma_Module !----------------------------------------------------------------------- ! This routine was written by G. A. Parker ! IF you find an error or have an improvement please send a messge to ! parker@ou.edu !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(len=255) :: filename CHARACTER(LEN=255), PARAMETER:: OutDir='E:\ParkerE\DAF_And_Numerov\' INTEGER :: mval, jhalf, ndaf, kmax, idaf, karg, nd_daf, nxval REAL(KIND=WP_Kind) :: dafx (0:nd_daf, 0:ndaf), hermit (0:mval + ndaf + 1), & delta, usys2, aterm, bterm, cterm, sigma_ratio, toe (0: nd_daf), xval (nxval) WRITE(Out_Unit, * ) WRITE(Out_Unit, * ) 'Begin(Get_Daf)' !----------------------------------------------------------------------- ! This section gets a guess for the best sigma. One could refine ! this guess but is probably not very useful. !----------------------------------------------------------------------- aterm = 10.4893 bterm = - 3.5095 cterm = - 0.4744 - mval sigma_ratio = ( - bterm + sqrt (bterm**2 - 4.d0 * aterm * cterm) ) / (2.d0 * aterm) sigma = sigma_ratio * delta jhalf = nd_daf / 2 + 1 kmax = (jhalf - 1) WRITE(Out_Unit, * ) 'sigma_ratio=', sigma_ratio WRITE(Out_Unit, * ) 'sigma,delta=', sigma, delta !----------------------------------------------------------------------- ! calculate the daf deltas. !----------------------------------------------------------------------- kmax = max (kmax, nd_daf) dafx = 0.d0 CALL daf (sigma, delta, mval, dafx, kmax, hermit, ndaf, nd_daf, nd_daf) !----------------------------------------------------------------------- ! output the daf deltas for subsequent plotting. !----------------------------------------------------------------------- DO idaf = 0, ndaf IF (idaf.eq.0) filename = TRIM(OutDir)//'dafx(0)_graph.csv' IF (idaf.eq.1) filename = TRIM(OutDir)//'dafx(1)_graph.csv' IF (idaf.eq.2) filename = TRIM(OutDir)//'dafx(2)_graph.csv' WRITE(Out_Unit, * ) 'Creating dafx(idaf)_graph.csv for idaf=', idaf CALL Graf_DAF(delta, delta, dafx (0, idaf), nd_daf, filename, 0, idaf) ENDDO WRITE(Out_Unit, * ) 'usys2,kmax,nd_daf=', usys2, kmax, nd_daf DO karg = 0, max (kmax, nd_daf - 1) IF (karg.le.kmax) THEN toe (karg) = - dafx (karg, 0) / usys2 ELSE toe (karg) = 0.d0 ENDIF ENDDO 99 FORMAT(1x,2es13.5) WRITE(Out_Unit, * ) 'END(Get_Daf)' WRITE(Out_Unit, * ) RETURN END SUBROUTINE Get_DAF