Skip to content
Snippets Groups Projects
Commit 29ed2451 authored by Arbanas, Goran's avatar Arbanas, Goran Committed by Holcomb, Andrew
Browse files

Adding some comments to array names (essentially copying them from the xct07.f).

parent 23fd845b
No related branches found
No related tags found
No related merge requests found
......@@ -33,7 +33,12 @@ module XctCrossCalc_M
integer::Ifcoul = 0 ! do we need to calculate coulomb data
logical::addElimKapt !ADD ELIMINATED CAPTURE CHANNEL TO FINA
real(kind=8),allocatable,dimension(:,:)::Alj ! used to count the number of Clebsch-Gordon coefficients
real(kind=8),allocatable,dimension(:,:)::Alj ! Eqs. (II B1 b.13) and (II B1 b.4) for 1- and 2-channel case, respectively [SAMMY 8 Users' Guide]
! *** Alj = (2*J+1) * (2*el+1) *del2 (el, s, J) in one-channel case
! *** Alj = (2*J+1) * sqrt { (2*el +1) *del2 (el , s , J) } * 2
! *** * sqrt { (2*el'+1) *del2 (el', s', J) } in 2-channel
real(kind=8),allocatable,dimension(:)::Xx ! 0.0 or if SHIFT RESONANCE ENERGIES VIA SHIFT FACTOR, the factor
real(kind=8),allocatable,dimension(:)::XxHelper ! helper array to calculate Xx
real(kind=8),allocatable,dimension(:)::Xlmn
......@@ -49,35 +54,81 @@ module XctCrossCalc_M
real(kind=8),allocatable,dimension(:)::Difen ! resonance energy minus currrent energy or 0 if resonance is not included in calculation
real(kind=8),allocatable,dimension(:,:)::Pi, Pr
real(kind=8),allocatable,dimension(:,:)::Pi, Pr ! Penetrability, P, real and imaginary part thereof.
real(kind=8),allocatable,dimension(:,:)::Cscs
real(kind=8),allocatable,dimension(:,:)::Cscs ! Looks like Cos(a + b), Sin(a + b), where b may be phi
real(kind=8),allocatable,dimension(:)::Sinsqr ! sin^2( phase shift )
real(kind=8),allocatable,dimension(:)::Sin2ph ! sin( 2 * phase shift )
real(kind=8),allocatable,dimension(:)::Dphi
real(kind=8),allocatable,dimension(:)::Sinphi, Cosphi
real(kind=8),allocatable,dimension(:)::Dphi ! partial derivative of Phi wrt Rho
real(kind=8),allocatable,dimension(:)::Sinphi, Cosphi ! ( sin, cos ) ( phase shift )
real(kind=8),allocatable,dimension(:)::Dpdr ! partial P wrt Rho
real(kind=8),allocatable,dimension(:)::Dsdr ! partial S wrt Rho
real(kind=8),allocatable,dimension(:,:)::Rmat, Ymat, Yinv
real(kind=8),allocatable,dimension(:)::Rootp
real(kind=8),allocatable,dimension(:)::Elinvr,Elinvi
real(kind=8),allocatable,dimension(:)::Psmall
real(kind=8),allocatable,dimension(:)::Xxxxr, Xxxxi
real(kind=8),allocatable,dimension(:,:)::Xqr,Xqi
real(kind=8),allocatable,dimension(:,:)::Pxrhor, Pxrhoi
real(kind=8),allocatable,dimension(:,:)::Qr, Qi
real(kind=8),allocatable,dimension(:,:)::Tr, Ti
real(kind=8),allocatable,dimension(:,:,:)::Tx
real(kind=8),allocatable,dimension(:)::Ddddd, Ddddtl
logical,allocatable, dimension(:,:)::useChannel
real(kind=8),allocatable,dimension(:,:)::Prei, Prer
real(kind=8),allocatable,dimension(:)::Dsf
real(kind=8),allocatable,dimension(:,:,:)::Dsfx, Dstx
real(kind=8),allocatable,dimension(:,:)::Dstt, Dst
real(kind=8),allocatable,dimension(:)::Xden
real(kind=8),allocatable,dimension(:)::termf, termfx
real(kind=8),allocatable,dimension(:,:)::Rmat ! Rmat = SUM Beta*Beta/((DEL E)-i(Gamgam/2))
real(kind=8),allocatable,dimension(:,:)::Ymat ! Ymat = Linv - Rmat , Linv = 1/(S-B+IP)
real(kind=8),allocatable,dimension(:,:)::Yinv ! Yinv = 1 / Ymat
real(kind=8),allocatable,dimension(:)::Rootp ! Rmat = SUM Beta*Beta/((DEL E)-i(Gamgam/2))
real(kind=8),allocatable,dimension(:)::Elinvr,Elinvi ! Real and imaginary part of Linv
real(kind=8),allocatable,dimension(:)::Psmall ! Is Psmall used?
! The following comments were copied from the preamble of the Subroutine Setxqx in mxct09.f90:
! *** XQ = Yinv * Rmat and
! *** XXXX = P/L + sqrt(P)/L (1/L-R)**-1 sqrt(P)/L
! *** = sqrt(P)/(S-B+IP) * Yinv * Rmat * sqrt(P)
! *** = sqrt(P)/L * XQ * sqrt(P)
!
! *** Note that the matrix W defined in SAMMY manual is given
! *** by W(c,c') = delta(c,c') + 2i XXXX(c,c')
! *** as in Eq. (II.B1.3) in SAMMY manual R7
!
! *** ie W = I + 2i XXXX
real(kind=8),allocatable,dimension(:)::Xxxxr, Xxxxi ! *** Xxxx = sqrt(P)/L * xq * sqrt(P) ... symmetric
real(kind=8),allocatable,dimension(:,:)::Xqr,Xqi ! *** Xq = (L**-1-R)**-1 * R ... note asymmetry
real(kind=8),allocatable,dimension(:,:)::Pxrhor, Pxrhoi ! Pxrho_ = partial(Xxxx_) wrt (Rho)
! *** Purpose -- Generate QR,QI =
! *** SQRT(P)/(S-B+IP) * Yinv*Yinv * SQRT(P)/(S-B+IP)
! ***
! *** That is, Qr(KL,Ij) is (real part of) partial of XXXX(Kl) wrt R(Ij)
real(kind=8),allocatable,dimension(:,:)::Qr, Qi ! see above
! *** For angular distributions
! *** prtl (1-U)(kl) wrt R(ij) = prtl(1-U)(kl) wrt X(kl) * prtl X wrt R
! *** Tx(1,ij,kl) = prtl Re(1-U) wrt ReR = -prtl Im (1-U) wrt ImR
! *** Tx(2,ij,kl) = prtl Re(1-U) wrt ImR = prtl Re (1-U) wrt ReR
real(kind=8),allocatable,dimension(:,:,:)::Tx ! see above
! *** generate Deriv(k,Itzero) & Deriv(k,Ilzero); ditto Derivx
! *** ie Deriv(k,i) = partial Crss(k) wrt either Tzero or LZero
! *** Calculating Deriv(K,I?z) = (2T)(Pre)(Z)(E?z), where
! *** Tr + i Ti = (partial sigmaX wrt R) * Half
! *** Prer + i Prei = partial R wrt E
! *** Z = partial E wrt sqrt(E) = 2*sqrt(E)
! *** Etz = partial sqrt(E) wrt tzero
! *** ELz = partial sqrt(E) wrt eLzero
! *** but do not include the E?z part yet, or missing {dgoj * 1/E^2},
! *** and store in Ddddtl
real(kind=8),allocatable,dimension(:,:)::Tr, Ti ! see above
real(kind=8),allocatable,dimension(:,:)::Prei, Prer ! see above
real(kind=8),allocatable,dimension(:)::Ddddd, Ddddtl ! see above
logical,allocatable, dimension(:,:)::useChannel
! *** generate derivatives of Crss & Crssx wrt rho
! *** Dsf ( I) = Deriv of Crss(1 ) wrt rho via phi(I)
! *** Dst (J ,I) = Deriv of Crss(J ) wrt rho via P(I) & S(I)
! *** Dstt(Jj,I) = Deriv of Crss(Jj+2) wrt rho via P(I) & S(I)
real(kind=8),allocatable,dimension(:)::Dsf ! see above
real(kind=8),allocatable,dimension(:,:)::Dstt, Dst ! see above
real(kind=8),allocatable,dimension(:,:,:)::Dsfx, Dstx ! *** Note that the "f" in Dsf is for "effective" rho, i.e., radius.
real(kind=8),allocatable,dimension(:)::Xden ! The inverse of Eq. (II D1 b.7) = 1/[(E-E_resonance)^2 + (gamma/2)^2]
real(kind=8),allocatable,dimension(:)::termf, termfx ! termf(1) = elastic, (2) = absorption, (3) = reaction channels; "x" number of parameters (Numdet) of the ETA detector efficiency is greater than 0.
real(kind=8),allocatable,dimension(:,:,:)::crossInternal ! used to keep track of cross section+deriv for one row and all channels
real(kind=8),allocatable,dimension(:,:,:,:,:)::angInternal ! used to keep track of angula section+deriv for one row and all channels
......@@ -91,7 +142,7 @@ module XctCrossCalc_M
! direct capture arrays. Todo update the direct capture to read and store data in C++ class
logical::hasDirectCapture
real(kind=8),allocatable,dimension(:,:)::Edrcpt
real(kind=8),allocatable,dimension(:,:)::Edrcpt
real(kind=8),allocatable,dimension(:,:)::Cdrcpt
real(kind=8),allocatable,dimension(:)::Xdrcpt
integer,allocatable,dimension(:)::Ndrcpt
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment