SUBROUTINE get_daf (nxval, xval, delta, mval, dafx, hermit, ndaf, nd_daf, toe, kmax) USE Numeric_Kinds_Module USE FileUnits_Module USE DAFSigma_Module USE CommonInfo_Module USE masses_module !----------------------------------------------------------------------- ! This routine was written by G. A. Parker ! IF you find an error or have an improvement please send a messge to ! parker@phyast.nhn.uoknor.edu !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER (len=29) :: filename INTEGER :: mval, jhalf, ndaf, kmax, idaf, karg, nd_daf, nxval REAL (dp) :: dafx (0:nd_daf, 0:ndaf), hermit (0:mval + ndaf + 1) REAL (dp) :: delta, aterm, bterm, cterm, sigma_ratio REAL (dp) :: toe (0:nd_daf), xval (nxval) !----------------------------------------------------------------------- ! This section gets a guess for the best sigma. One could refine ! this guess but is probably not very useful. !----------------------------------------------------------------------- aterm = 10.4893d0 bterm = - 3.5095d0 cterm = - 0.4744d0 - 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) !----------------------------------------------------------------------- ! 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) DO karg = 0, max (kmax, nd_daf) IF (karg.le.kmax) THEN toe (karg) = - dafx (karg, 2) / usys2 ELSE toe (karg) = 0.d0 ENDIF ENDDO RETURN END SUBROUTINE get_daf