| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439 | *DECK RC6J      SUBROUTINE RC6J (L2, L3, L4, L5, L6, L1MIN, L1MAX, SIXCOF, NDIM,     +   IER)C***BEGIN PROLOGUE  RC6JC***PURPOSE  Evaluate the 6j symbol h(L1) = {L1 L2 L3}C                                           {L4 L5 L6}C            for all allowed values of L1, the other parametersC            being held fixed.C***LIBRARY   SLATECC***CATEGORY  C19C***TYPE      SINGLE PRECISION (RC6J-S, DRC6J-D)C***KEYWORDS  6J COEFFICIENTS, 6J SYMBOLS, CLEBSCH-GORDAN COEFFICIENTS,C             RACAH COEFFICIENTS, VECTOR ADDITION COEFFICIENTS,C             WIGNER COEFFICIENTSC***AUTHOR  Gordon, R. G., Harvard UniversityC           Schulten, K., Max Planck InstituteC***DESCRIPTIONCC *Usage:CC        REAL L2, L3, L4, L5, L6, L1MIN, L1MAX, SIXCOF(NDIM)C        INTEGER NDIM, IERCC        CALL RC6J(L2, L3, L4, L5, L6, L1MIN, L1MAX, SIXCOF, NDIM, IER)CC *Arguments:CC     L2 :IN      Parameter in 6j symbol.CC     L3 :IN      Parameter in 6j symbol.CC     L4 :IN      Parameter in 6j symbol.CC     L5 :IN      Parameter in 6j symbol.CC     L6 :IN      Parameter in 6j symbol.CC     L1MIN :OUT  Smallest allowable L1 in 6j symbol.CC     L1MAX :OUT  Largest allowable L1 in 6j symbol.CC     SIXCOF :OUT Set of 6j coefficients generated by evaluating theC                 6j symbol for all allowed values of L1.  SIXCOF(I)C                 will contain h(L1MIN+I-1), I=1,2,...,L1MAX-L1MIN+1.CC     NDIM :IN    Declared length of SIXCOF in calling program.CC     IER :OUT    Error flag.C                 IER=0 No errors.C                 IER=1 L2+L3+L5+L6 or L4+L2+L6 not an integer.C                 IER=2 L4, L2, L6 triangular condition not satisfied.C                 IER=3 L4, L5, L3 triangular condition not satisfied.C                 IER=4 L1MAX-L1MIN not an integer.C                 IER=5 L1MAX less than L1MIN.C                 IER=6 NDIM less than L1MAX-L1MIN+1.CC *Description:CC     The definition and properties of 6j symbols can be found, forC  example, in Appendix C of Volume II of A. Messiah. Although theC  parameters of the vector addition coefficients satisfy certainC  conventional restrictions, the restriction that they be non-negativeC  integers or non-negative integers plus 1/2 is not imposed on inputC  to this subroutine. The restrictions imposed areC       1. L2+L3+L5+L6 and L2+L4+L6 must be integers;C       2. ABS(L2-L4).LE.L6.LE.L2+L4 must be satisfied;C       3. ABS(L4-L5).LE.L3.LE.L4+L5 must be satisfied;C       4. L1MAX-L1MIN must be a non-negative integer, whereC          L1MAX=MIN(L2+L3,L5+L6) and L1MIN=MAX(ABS(L2-L3),ABS(L5-L6)).C  If all the conventional restrictions are satisfied, then theseC  restrictions are met. Conversely, if input to this subroutine meetsC  all of these restrictions and the conventional restriction statedC  above, then all the conventional restrictions are satisfied.CC     The user should be cautious in using input parameters that doC  not satisfy the conventional restrictions. For example, theC  the subroutine produces values ofC       h(L1) = { L1 2/3  1 }C               {2/3 2/3 2/3}C  for L1=1/3 and 4/3 but none of the symmetry properties of the 6jC  symbol, set forth on pages 1063 and 1064 of Messiah, is satisfied.CC     The subroutine generates h(L1MIN), h(L1MIN+1), ..., h(L1MAX)C  where L1MIN and L1MAX are defined above. The sequence h(L1) isC  generated by a three-term recurrence algorithm with scaling toC  control overflow. Both backward and forward recurrence are used toC  maintain numerical stability. The two recurrence sequences areC  matched at an interior point and are normalized from the unitaryC  property of 6j coefficients and Wigner's phase convention.CC    The algorithm is suited to applications in which large quantumC  numbers arise, such as in molecular dynamics.CC***REFERENCES  1. Messiah, Albert., Quantum Mechanics, Volume II,C                  North-Holland Publishing Company, 1963.C               2. Schulten, Klaus and Gordon, Roy G., Exact recursiveC                  evaluation of 3j and 6j coefficients for quantum-C                  mechanical coupling of angular momenta, J MathC                  Phys, v 16, no. 10, October 1975, pp. 1961-1970.C               3. Schulten, Klaus and Gordon, Roy G., SemiclassicalC                  approximations to 3j and 6j coefficients forC                  quantum-mechanical coupling of angular momenta,C                  J Math Phys, v 16, no. 10, October 1975,C                  pp. 1971-1988.C               4. Schulten, Klaus and Gordon, Roy G., RecursiveC                  evaluation of 3j and 6j coefficients, ComputerC                  Phys Comm, v 11, 1976, pp. 269-278.C***ROUTINES CALLED  R1MACH, XERMSGC***REVISION HISTORY  (YYMMDD)C   750101  DATE WRITTENC   880515  SLATEC prologue added by G. C. Nielson, NBS; parametersC           HUGE and TINY revised to depend on R1MACH.C   891229  Prologue description rewritten; other prologue sectionsC           revised; LMATCH (location of match point for recurrences)C           removed from argument list; argument IER changed to serveC           only as an error flag (previously, in cases without error,C           it returned the number of scalings); number of error codesC           increased to provide more precise error information;C           program comments revised; SLATEC error handler callsC           introduced to enable printing of error messages to meetC           SLATEC standards. These changes were done by D. W. Lozier,C           M. A. McClain and J. M. Smith of the National InstituteC           of Standards and Technology, formerly NBS.C   910415  Mixed type expressions eliminated; variable C1 initialized;C           description of SIXCOF expanded. These changes were done byC           D. W. Lozier.C***END PROLOGUE  RC6JC      INTEGER NDIM, IER      REAL L2, L3, L4, L5, L6, L1MIN, L1MAX, SIXCOF(NDIM)C      INTEGER I, INDEX, LSTEP, N, NFIN, NFINP1, NFINP2, NFINP3, NLIM,     +        NSTEP2      REAL A1, A1S, A2, A2S, C1, C1OLD, C2, CNORM, R1MACH,     +     DENOM, DV, EPS, HUGE, L1, NEWFAC, OLDFAC, ONE,     +     RATIO, SIGN1, SIGN2, SRHUGE, SRTINY, SUM1, SUM2,     +     SUMBAC, SUMFOR, SUMUNI, THREE, THRESH, TINY, TWO,     +     X, X1, X2, X3, Y, Y1, Y2, Y3, ZEROC      DATA  ZERO,EPS,ONE,TWO,THREE /0.0,0.01,1.0,2.0,3.0/CC***FIRST EXECUTABLE STATEMENT  RC6J      IER=0C  HUGE is the square root of one twentieth of the largest floatingC  point number, approximately.      HUGE = SQRT(R1MACH(2)/20.0)      SRHUGE = SQRT(HUGE)      TINY = 1.0/HUGE      SRTINY = 1.0/SRHUGECC     LMATCH = ZEROCC  Check error conditions 1, 2, and 3.      IF((MOD(L2+L3+L5+L6+EPS,ONE).GE.EPS+EPS).OR.     +   (MOD(L4+L2+L6+EPS,ONE).GE.EPS+EPS))THEN         IER=1         CALL XERMSG('SLATEC','RC6J','L2+L3+L5+L6 or L4+L2+L6 not '//     +      'integer.',IER,1)         RETURN      ELSEIF((L4+L2-L6.LT.ZERO).OR.(L4-L2+L6.LT.ZERO).OR.     +   (-L4+L2+L6.LT.ZERO))THEN         IER=2         CALL XERMSG('SLATEC','RC6J','L4, L2, L6 triangular '//     +      'condition not satisfied.',IER,1)         RETURN      ELSEIF((L4-L5+L3.LT.ZERO).OR.(L4+L5-L3.LT.ZERO).OR.     +   (-L4+L5+L3.LT.ZERO))THEN         IER=3         CALL XERMSG('SLATEC','RC6J','L4, L5, L3 triangular '//     +      'condition not satisfied.',IER,1)         RETURN      ENDIFCC  Limits for L1C      L1MIN = MAX(ABS(L2-L3),ABS(L5-L6))      L1MAX = MIN(L2+L3,L5+L6)CC  Check error condition 4.      IF(MOD(L1MAX-L1MIN+EPS,ONE).GE.EPS+EPS)THEN         IER=4         CALL XERMSG('SLATEC','RC6J','L1MAX-L1MIN not integer.',IER,1)         RETURN      ENDIF      IF(L1MIN.LT.L1MAX-EPS)   GO TO 20      IF(L1MIN.LT.L1MAX+EPS)   GO TO 10CC  Check error condition 5.      IER=5      CALL XERMSG('SLATEC','RC6J','L1MIN greater than L1MAX.',IER,1)      RETURNCCC  This is reached in case that L1 can take only one valueC   10 CONTINUEC     LSCALE = 0      SIXCOF(1) = (-ONE) ** INT(L2+L3+L5+L6+EPS) /     1            SQRT((L1MIN+L1MIN+ONE)*(L4+L4+ONE))      RETURNCCC  This is reached in case that L1 can take more than one value.C   20 CONTINUEC     LSCALE = 0      NFIN = INT(L1MAX-L1MIN+ONE+EPS)      IF(NDIM-NFIN)   21, 23, 23CC  Check error condition 6.   21 IER = 6      CALL XERMSG('SLATEC','RC6J','Dimension of result array for 6j '//     +            'coefficients too small.',IER,1)      RETURNCCC  Start of forward recursionC   23 L1 = L1MIN      NEWFAC = 0.0      C1 = 0.0      SIXCOF(1) = SRTINY      SUM1 = (L1+L1+ONE) * TINYC      LSTEP = 1   30 LSTEP = LSTEP + 1      L1 = L1 + ONEC      OLDFAC = NEWFAC      A1 = (L1+L2+L3+ONE) * (L1-L2+L3) * (L1+L2-L3) * (-L1+L2+L3+ONE)      A2 = (L1+L5+L6+ONE) * (L1-L5+L6) * (L1+L5-L6) * (-L1+L5+L6+ONE)      NEWFAC = SQRT(A1*A2)C      IF(L1.LT.ONE+EPS)   GO TO 40C      DV = TWO * ( L2*(L2+ONE)*L5*(L5+ONE) + L3*(L3+ONE)*L6*(L6+ONE)     1           - L1*(L1-ONE)*L4*(L4+ONE) )     2                   - (L2*(L2+ONE) + L3*(L3+ONE) - L1*(L1-ONE))     3                   * (L5*(L5+ONE) + L6*(L6+ONE) - L1*(L1-ONE))C      DENOM = (L1-ONE) * NEWFACC      IF(LSTEP-2)  32, 32, 31C   31 C1OLD = ABS(C1)   32 C1 = - (L1+L1-ONE) * DV / DENOM      GO TO 50CC  If L1 = 1, (L1 - 1) has to be factored out of DV, henceC   40 C1 = - TWO * ( L2*(L2+ONE) + L5*(L5+ONE) - L4*(L4+ONE) )     1 / NEWFACC   50 IF(LSTEP.GT.2)   GO TO 60CC  If L1 = L1MIN + 1, the third term in recursion equation vanishesC      X = SRTINY * C1      SIXCOF(2) = X      SUM1 = SUM1 + TINY * (L1+L1+ONE) * C1 * C1C      IF(LSTEP.EQ.NFIN)   GO TO 220      GO TO 30CC   60 C2 = - L1 * OLDFAC / DENOMCC  Recursion to the next 6j coefficient XC      X = C1 * SIXCOF(LSTEP-1) + C2 * SIXCOF(LSTEP-2)      SIXCOF(LSTEP) = XC      SUMFOR = SUM1      SUM1 = SUM1 + (L1+L1+ONE) * X * X      IF(LSTEP.EQ.NFIN)   GO TO 100CC  See if last unnormalized 6j coefficient exceeds SRHUGEC      IF(ABS(X).LT.SRHUGE)   GO TO 80CC  This is reached if last 6j coefficient larger than SRHUGE,C  so that the recursion series SIXCOF(1), ... ,SIXCOF(LSTEP)C  has to be rescaled to prevent overflowCC     LSCALE = LSCALE + 1      DO 70 I=1,LSTEP      IF(ABS(SIXCOF(I)).LT.SRTINY)   SIXCOF(I) = ZERO   70 SIXCOF(I) = SIXCOF(I) / SRHUGE      SUM1 = SUM1 / HUGE      SUMFOR = SUMFOR / HUGE      X = X / SRHUGECCC  As long as the coefficient ABS(C1) is decreasing, the recursionC  proceeds towards increasing 6j values and, hence, is numericallyC  stable.  Once an increase of ABS(C1) is detected, the recursionC  direction is reversed.C   80 IF(C1OLD-ABS(C1))   100, 100, 30CCC  Keep three 6j coefficients around LMATCH for comparison laterC  with backward recursion.C  100 CONTINUEC     LMATCH = L1 - 1      X1 = X      X2 = SIXCOF(LSTEP-1)      X3 = SIXCOF(LSTEP-2)CCCC  Starting backward recursion from L1MAX taking NSTEP2 steps, soC  that forward and backward recursion overlap at the three pointsC  L1 = LMATCH+1, LMATCH, LMATCH-1.C      NFINP1 = NFIN + 1      NFINP2 = NFIN + 2      NFINP3 = NFIN + 3      NSTEP2 = NFIN - LSTEP + 3      L1 = L1MAXC      SIXCOF(NFIN) = SRTINY      SUM2 = (L1+L1+ONE) * TINYCC      L1 = L1 + TWO      LSTEP = 1  110 LSTEP = LSTEP + 1      L1 = L1 - ONEC      OLDFAC = NEWFAC      A1S = (L1+L2+L3)*(L1-L2+L3-ONE)*(L1+L2-L3-ONE)*(-L1+L2+L3+TWO)      A2S = (L1+L5+L6)*(L1-L5+L6-ONE)*(L1+L5-L6-ONE)*(-L1+L5+L6+TWO)      NEWFAC = SQRT(A1S*A2S)C      DV = TWO * ( L2*(L2+ONE)*L5*(L5+ONE) + L3*(L3+ONE)*L6*(L6+ONE)     1           - L1*(L1-ONE)*L4*(L4+ONE) )     2                   - (L2*(L2+ONE) + L3*(L3+ONE) - L1*(L1-ONE))     3                   * (L5*(L5+ONE) + L6*(L6+ONE) - L1*(L1-ONE))C      DENOM = L1 * NEWFAC      C1 = - (L1+L1-ONE) * DV / DENOM      IF(LSTEP.GT.2)   GO TO 120CC  If L1 = L1MAX + 1 the third term in the recursion equation vanishesC      Y = SRTINY * C1      SIXCOF(NFIN-1) = Y      IF(LSTEP.EQ.NSTEP2)   GO TO 200      SUMBAC = SUM2      SUM2 = SUM2 + (L1+L1-THREE) * C1 * C1 * TINY      GO TO 110CC  120 C2 = - (L1-ONE) * OLDFAC / DENOMCC  Recursion to the next 6j coefficient YC      Y = C1 * SIXCOF(NFINP2-LSTEP) + C2 * SIXCOF(NFINP3-LSTEP)      IF(LSTEP.EQ.NSTEP2)   GO TO 200      SIXCOF(NFINP1-LSTEP) = Y      SUMBAC = SUM2      SUM2 = SUM2 + (L1+L1-THREE) * Y * YCC  See if last unnormalized 6j coefficient exceeds SRHUGEC      IF(ABS(Y).LT.SRHUGE)   GO TO 110CC  This is reached if last 6j coefficient larger than SRHUGE,C  so that the recursion series SIXCOF(NFIN), ... ,SIXCOF(NFIN-LSTEP+1)C  has to be rescaled to prevent overflowCC     LSCALE = LSCALE + 1      DO 130 I=1,LSTEP      INDEX = NFIN-I+1      IF(ABS(SIXCOF(INDEX)).LT.SRTINY)   SIXCOF(INDEX) = ZERO  130 SIXCOF(INDEX) = SIXCOF(INDEX) / SRHUGE      SUMBAC = SUMBAC / HUGE      SUM2 = SUM2 / HUGEC      GO TO 110CCC  The forward recursion 6j coefficients X1, X2, X3 are to be matchedC  with the corresponding backward recursion values Y1, Y2, Y3.C  200 Y3 = Y      Y2 = SIXCOF(NFINP2-LSTEP)      Y1 = SIXCOF(NFINP3-LSTEP)CCC  Determine now RATIO such that YI = RATIO * XI  (I=1,2,3) holdsC  with minimal error.C      RATIO = ( X1*Y1 + X2*Y2 + X3*Y3 ) / ( X1*X1 + X2*X2 + X3*X3 )      NLIM = NFIN - NSTEP2 + 1C      IF(ABS(RATIO).LT.ONE)   GO TO 211C      DO 210 N=1,NLIM  210 SIXCOF(N) = RATIO * SIXCOF(N)      SUMUNI = RATIO * RATIO * SUMFOR + SUMBAC      GO TO 230C  211 NLIM = NLIM + 1      RATIO = ONE / RATIO      DO 212 N=NLIM,NFIN  212 SIXCOF(N) = RATIO * SIXCOF(N)      SUMUNI = SUMFOR + RATIO*RATIO*SUMBAC      GO TO 230C  220 SUMUNI = SUM1CCC  Normalize 6j coefficientsC  230 CNORM = ONE / SQRT((L4+L4+ONE)*SUMUNI)CC  Sign convention for last 6j coefficient determines overall phaseC      SIGN1 = SIGN(ONE,SIXCOF(NFIN))      SIGN2 = (-ONE) ** INT(L2+L3+L5+L6+EPS)      IF(SIGN1*SIGN2) 235,235,236  235 CNORM = - CNORMC  236 IF(ABS(CNORM).LT.ONE)   GO TO 250C      DO 240 N=1,NFIN  240 SIXCOF(N) = CNORM * SIXCOF(N)      RETURNC  250 THRESH = TINY / ABS(CNORM)      DO 251 N=1,NFIN      IF(ABS(SIXCOF(N)).LT.THRESH)   SIXCOF(N) = ZERO  251 SIXCOF(N) = CNORM * SIXCOF(N)C      RETURN      END
 |