Here we give the FORTRAN program for computing or
for the transitions considered in the present paper. The
program makes use of the data given in Tables 3, 4 and 5. It assumes that
the data for the transition in question has been stored (including the
heading line of text) in a separate file. The interpolations are performed
by the function programs SPLINE and POLY4. The authors are willing to send
files of the program and tables by e-mail, on request.
# PROGRAM LILIKE Computes Omega and Upsilon for LiLike ions *N.B. IUNIT is the UNIT number for the input data files. * Ensure that the value is suitable for your computer. Code: LOGICAL OK CHARACTER ANS*1,OU*1 DIMENSION SMN(5,5) IUNIT=1 *Input Smn matrix file 1 CALL SMNINP(IUNIT,OU,ITYPE,C,CZ,NMAX,SMN,OK) IF (OK.EQV..FALSE.) GO TO 5 2 PRINT* PRINT*, 'Enter: Nuclear charge Z0, Eij (Ryd or cm-1), Ej(Ryd)' PRINT*, '(Use a -ve value to exit from a sequence)' PRINT* *Enter Z0 WRITE(*,100) ' Z0 = ' READ*,Z IF (Z.LT.0.0) GO TO 5 *Enter Eij WRITE(*,100) ' Eij = ' READ*,EIJ IF (EIJ.LT.0.0) GO TO 5 IF (EIJ.GT.9.0*Z*Z) EIJ=EIJ/1.09737E5 Z=Z-3.0 ZR=Z/(Z+CZ) 3 PRINT* *Enter Ej or T IF (OU.EQ.'O') WRITE(*,100) ' Ej = ' IF (OU.EQ.'U') WRITE(*,100) ' T = ' READ*, X IF (X.LT.0.0) GO TO 4 IF (OU.EQ.'U') X=6.3336E-6*X XR=X/(X+C*EIJ) *Interpolate in Z and Ej or T Y=FINTER(ITYPE,NMAX,SMN,ZR,XR) EPS=2.6626E-5 *Calculate Omega (see eq. 62) IF (OU.EQ.'O') THEN Y=(1.0+EPS*(X+EIJ))*(1.0+EPS*X)*Y/(Z+1.0)**2 WRITE(*,101) ' Omega =',Y ENDIF *Calculate Upsilon (see eq. 62) IF (OU.EQ.'U') THEN Y=(1.0+EPS*(EIJ+X*(2.0+EPS*(EIJ+2.0*X))))*Y/(Z+1.0)**2 WRITE(*,101) 'Upsilon =',Y ENDIF GO TO 3 4 GO TO 2 5 WRITE(*,100) 'Another case? (Y/N): ' READ*, ANS IF ((ANS.NE.'Y').AND.(ANS.NE.'N').AND.(ANS.NE.'y').AND.(ANS.NE. + 'n')) GO TO 5 IF ((ANS.EQ.'Y').OR.(ANS.EQ.'y')) GO TO 1 STOP 100 FORMAT((A$)) 101 FORMAT(A9,1PE11.4) END ****** SUBROUTINE SMNINP(IUNIT,OU,ITYPE,C,CZ,NMAX,SMN,OK) CHARACTER ANS*1, FILENM*15, HEAD*80, OU*1 LOGICAL FOUND,AVAIL,OK DIMENSION SMN(5,5) 1 WRITE(*,100) 'Smn file name = ' READ*, FILENM INQUIRE (FILE=FILENM, EXIST=FOUND) IF (.NOT.FOUND) THEN PRINT*, 'File not found.' OK=.FALSE. RETURN ENDIF OPEN (UNIT=IUNIT, FILE=FILENM) REWIND(UNIT=IUNIT) READ (UNIT=IUNIT,FMT=101,ERR=200) HEAD READ (UNIT=IUNIT,FMT=*,ERR=200) ITYPE,C,CZ IF ((ITYPE.NE.12).AND.(ITYPE.NE.212)) GO TO 200 IF ((C.LE.0.0).OR.(CZ.LE.0.0)) GO TO 200 IF (ITYPE.EQ.12) NMAX=5 IF (ITYPE.EQ.212) NMAX=4 READ (UNIT=IUNIT,FMT=*,ERR=200) ((SMN(M,N),N=1,NMAX),M=1,NMAX) CLOSE(UNIT=IUNIT) OK=.TRUE. OU=HEAD(1:1) PRINT* WRITE(*,101) 'Contents of Smn file:', HEAD WRITE(*,102) ITYPE,C,CZ DO 2 M=1,NMAX WRITE(*,103) (SMN(M,N),N=1,NMAX) 2 CONTINUE RETURN 100 FORMAT((A$)) 101 FORMAT(A80) 102 FORMAT(I5,2F10.5) 103 FORMAT(5F10.5) 200 PRINT*, 'File unreadable.' INQUIRE (UNIT=IUNIT, OPENED=AVAIL) IF (AVAIL) CLOSE(UNIT=IUNIT) OK=.FALSE. RETURN END ****** FUNCTION FINTER(ITYPE,NMAX,SMN,ZR,XR) DIMENSION SMN(5,5),P(5),Q(5) DO 2 N=1,NMAX DO 1 M=1,NMAX P(M)=SMN(M,N) 1 CONTINUE *Interpolate in Z IF (ITYPE.EQ.12) THEN Q(N)=SPLINE(P,ZR) ELSE Q(N)=POLY4(P,ZR) ENDIF 2 CONTINUE *Interpolate in E or T IF (ITYPE.EQ.12) THEN FINTER=SPLINE(Q,XR) ELSE FINTER=POLY4(Q,XR) ENDIF RETURN END ****** FUNCTION SPLINE(P,X) Calculates 5-point spline interpolation of Y(X), * for X in the range (0,1). *Input: * Nodal values P(1)=Y(0),P(2)=Y(1/4),P(3)=Y(1/2),P(4)=Y(3/4),P(5)=Y(1) * and X. *Output: * SPLINE=Y(X). Code: DIMENSION P(5) S=1.0/30.0 S2=32.0*S*(19.0*P(1)-43.0*P(2)+30.0*P(3)-7.0*P(4)+P(5)) S3=160.0*S*(-P(1)+7.0*P(2)-12.0*P(3)+7.0*P(4)-P(5)) S4=32.0*S*(P(1)-7.0*P(2)+30.0*P(3)-43.0*P(4)+19.0*P(5)) IF(X.GT.0.25) GO TO 1 X0=X-0.125 T3=0.0 T2=0.5*S2 T1=4.0*(P(2)-P(1)) T0=0.5*(P(1)+P(2))-0.015625*T2 GO TO 4 1 IF(X.GT.0.5) GO TO 2 X0=X-0.375 T3=20.0*S*(S3-S2) T2=0.25*(S2+S3) T1=4.0*(P(3)-P(2))-0.015625*T3 T0=0.5*(P(2)+P(3))-0.015625*T2 GO TO 4 2 IF(X.GT.0.75) GO TO 3 X0=X-0.625 T3=20.0*S*(S4-S3) T2=0.25*(S3+S4) T1=4.0*(P(4)-P(3))-0.015625*T3 T0=0.5*(P(3)+P(4))-0.015625*T2 GO TO 4 3 X0=X-0.875 T3=0.0 T2=0.5*S4 T1=4.0*(P(5)-P(4)) T0=0.5*(P(4)+P(5))-0.015625*T2 4 SPLINE=T0+X0*(T1+X0*(T2+X0*T3)) RETURN END ****** FUNCTION POLY4(P,X) Calculates 4-point polynomial interpolation of Y(X), * for X in the range (0,1). *Input: * Nodal values P(1)=Y(0), P(2)=Y(1/3), P(3)=Y(2/3), P(4)=Y(1) and X. *Output: * POLY4=Y(X). Code: DIMENSION P(4) T=3.0*X T1=(T-1.0)*(T-2.0)*(1.0-X) T2=T*(T-2.0)*(T-3.0) T3=T*(T-1.0)*(3.0-T) T4=X*(T-1.0)*(T-2.0) POLY4=0.5*(T1*P(1)+T2*P(2)+T3*P(3)+T4*P(4)) RETURN END ******
Copyright The European Southern Observatory (ESO)