*DECK CQCBH SUBROUTINE CQCBH (LUN, KPRINT, IPASS) C***BEGIN PROLOGUE CQCBH C***SUBSIDIARY C***PURPOSE Quick check for SLATEC subroutine C CBESH C***LIBRARY SLATEC C***CATEGORY C10A4 C***TYPE COMPLEX (CQCBH-C, ZQCBH-Z) C***KEYWORDS QUICK CHECK, CBESH C***AUTHOR Amos, Don, (SNL) C Goudy, Sue, (SNL) C Walton, Lee, (SNL) C***DESCRIPTION C C *Usage: C C INTEGER LUN, KPRINT, IPASS C C CALL CQCBH (LUN, KPRINT, IPASS) C C *Arguments: C C LUN :IN is the unit number to which output is to be written. C C KPRINT :IN controls the amount of output, as specified in the C SLATEC Guidelines. C C IPASS :OUT indicates whether the test passed or failed. C A value of one is good, indicating no failures. C C *Description: C C CQCBH is a quick check routine for the complex H Bessel functions C generated by subroutine CBESH. C C CQCBH generates sequences of H Bessel functions for kinds 1 and 2 C from CBESH and checks them against the Wronskian evaluation C in the (Z,FNU) space. C C***REFERENCES Abramowitz, M. and Stegun, I. A., Handbook C of Mathematical Functions, Dover Publications, C New York, 1964. C Amos, D. E., A Subroutine Package for Bessel C Functions of a Complex Argument and Nonnegative C Order, SAND85-1018, May, 1985. C***ROUTINES CALLED CBESH, CUOIK, I1MACH, R1MACH C***REVISION HISTORY (YYMMDD) C 830501 DATE WRITTEN C 890831 Revised to meet new SLATEC standards C C***END PROLOGUE CQCBH C C*Internal Notes: C Machine constants are defined by functions I1MACH and R1MACH. C C The parameter MQC can have values 1 (the default) for a faster, C less definitive test or 2 for a slower, more definitive test. C C**End C C Set test complexity parameter. C INTEGER MQC PARAMETER (MQC=1) C C Declare arguments. C INTEGER LUN, KPRINT, IPASS C C Declare external functions. C INTEGER I1MACH REAL R1MACH EXTERNAL I1MACH, R1MACH C C Declare local variables. C COMPLEX CV, CW, CY, W, Y, Z, ZN REAL AA, AB, ACW, ACY, AER, ALIM, ATOL, AV, AW, AY, AZ, CT, DIG, * ELIM, EPS, ER, ERTOL, FILM, FNU, FNUL, FPI, HPI, PI, R, RFPI, * RL, RM, R1M4, R1M5, R2, SLAK, ST, T, TOL, TS, XNU INTEGER I, ICASE, IERR, IL, IR, IRB, IT, ITL, K, KDO, KEPS, KK, * KODE, K1, K2, LFLG, MFLG, N, NL, NU, NUL, NZ1, NZ2, N1 DIMENSION AER(20), KDO(20), KEPS(20), T(20), W(20), XNU(20), * Y(20) C C***FIRST EXECUTABLE STATEMENT CQCBH IF (KPRINT.GE.2) THEN WRITE (LUN,99999) 99999 FORMAT (' QUICK CHECK ROUTINE FOR THE H BESSEL FUNCTIONS FROM ', * 'CBESH'/) ENDIF C----------------------------------------------------------------------- C Set parameters related to machine constants. C TOL is the approximate unit roundoff limited to 1.0E-18. C ELIM is the approximate exponential over- and underflow limit. C exp(-ELIM).lt.exp(-ALIM)=exp(-ELIM)/TOL and C exp(ELIM).gt.exp(ALIM)=exp(ELIM)*TOL are intervals near C underflow and overflow limits where scaled arithmetic is done. C RL is the lower boundary of the asymptotic expansion for large Z. C DIG = number of base 10 digits in TOL = 10**(-DIG). C FNUL is the lower boundary of the asymptotic series for large FNU. C----------------------------------------------------------------------- R1M4 = R1MACH(4) TOL = MAX(R1M4,1.0E-18) ATOL = 100.0E0*TOL AA = -LOG10(R1M4) K1 = I1MACH(12) K2 = I1MACH(13) R1M5 = R1MACH(5) K = MIN(ABS(K1),ABS(K2)) ELIM = 2.303E0*(K*R1M5-3.0E0) AB = AA*2.303E0 ALIM = ELIM + MAX(-AB,-41.45E0) DIG = MIN(AA,18.0E0) FNUL = 10.0E0 + 6.0E0*(DIG-3.0E0) RL = 1.2E0*DIG + 3.0E0 SLAK = 3.0E0+4.0E0*(-LOG10(TOL)-7.0E0)/11.0E0 SLAK = MAX(SLAK,3.0E0) ERTOL = TOL*10.0E0**SLAK RM = 0.5E0*(ALIM + ELIM) RM = MIN(RM,200.0E0) RM = MAX(RM,RL+10.0E0) R2 = MIN(FNUL,RM) IF (KPRINT.GE.2) THEN WRITE (LUN,99998) 99998 FORMAT (' PARAMETERS'/ * 5X,'TOL ',8X,'ELIM',8X,'ALIM',8X,'RL ',8X,'FNUL',8X,'DIG') WRITE (LUN,99997) TOL, ELIM, ALIM, RL, FNUL, DIG 99997 FORMAT (6E12.4/) ENDIF C----------------------------------------------------------------------- C Set other constants needed in the tests. C----------------------------------------------------------------------- FPI = ATAN(1.0E0) HPI = FPI + FPI PI = HPI + HPI RFPI = 1.0E0/FPI ZN = CMPLX(0.0E0,-RFPI) C----------------------------------------------------------------------- C Generate angles for construction of complex Z to be used in tests. C----------------------------------------------------------------------- C KDO(K), K = 1,IL determines which of the IL angles in -PI to PI C are used to compute values of Z. C KDO(K) = 0 means that the index K will be used for one or two C values of Z, depending on the choice of KEPS(K) C = 1 means that the index K and the corresponding angle C will be skipped C KEPS(K), K = 1,IL determines which of the angles get incremented C up and down to put values of Z in regions where different C formulae are used. C KEPS(K) = 0 means that the angle will be used without change C = 1 means that the angle will be incremented up and C down by EPS C The angles to be used are stored in the T(I) array, I = 1,ITL. C----------------------------------------------------------------------- IF (MQC.NE.2) THEN NL = 2 IL = 5 DO 5 I = 1,IL KEPS(I) = 0 KDO(I) = 0 5 CONTINUE NUL = 5 XNU(1) = 0.0E0 XNU(2) = 1.0E0 XNU(3) = 2.0E0 XNU(4) = 0.5E0*FNUL XNU(5) = FNUL + 1.1E0 ELSE NL = 4 IL = 13 DO 6 I = 1,IL KDO(I) = 0 KEPS(I) = 0 6 CONTINUE KDO(2) = 1 KDO(6) = 1 KDO(8) = 1 KDO(12) = 1 KEPS(3) = 1 KEPS(4) = 1 KEPS(5) = 1 KEPS(9) = 1 KEPS(10) = 1 KEPS(11) = 1 NUL = 6 XNU(1) = 0.0E0 XNU(2) = 0.6E0 XNU(3) = 1.3E0 XNU(4) = 2.0E0 XNU(5) = 0.5E0*FNUL XNU(6) = FNUL + 1.1E0 ENDIF I = 2 EPS = 0.01E0 FILM = IL - 1 T(1) = -PI + EPS DO 30 K = 2,IL IF (KDO(K).EQ.0) THEN T(I) = PI*(-IL+2*K-1)/FILM IF (KEPS(K).NE.0) THEN TS = T(I) T(I) = TS - EPS I = I + 1 T(I) = TS + EPS ELSE I = I + 1 ENDIF ENDIF 30 CONTINUE ITL = I - 1 C----------------------------------------------------------------------- C Test values of Z in -PI.lt.arg(Z).le.PI. C----------------------------------------------------------------------- IF (KPRINT.GE.2) THEN WRITE (LUN,99996) 99996 FORMAT (' CHECKS IN THE (Z,FNU) SPACE'/) ENDIF LFLG = 0 DO 170 KODE = 1,2 DO 160 N = 1,NL N1 = N + 1 DO 150 NU = 1,NUL FNU = XNU(NU) DO 140 ICASE = 1,3 IRB = MIN(ICASE,2) DO 130 IR = IRB,3 C-------------- switch (icase) GO TO (50, 60, 70), ICASE 50 CONTINUE R = (EPS*(3-IR)+2.0E0*(IR-1))/2.0E0 GO TO 80 60 CONTINUE R = (2.0E0*(3-IR)+R2*(IR-1))/2.0E0 GO TO 80 70 CONTINUE IF (R2.GE.RM) GO TO 140 R = (R2*(3-IR)+RM*(IR-1))/2.0E0 80 CONTINUE C-------------- end switch DO 120 IT = 1,ITL CT = COS(T(IT)) ST = SIN(T(IT)) IF (ABS(CT).LT.ATOL) CT = 0.0E0 IF (ABS(ST).LT.ATOL) ST = 0.0E0 Z = CMPLX(R*CT,R*ST) IF (FNU.GE.2.0E0) THEN C------------------ Check for possible overflow condition CV = Z*(0.0E0,1.0E0) CALL CUOIK(CV, FNU, KODE, 2, N1, W, NZ2, TOL, * ELIM, ALIM) C------------------ Overflow detected? - skip test for this case IF (NZ2.EQ.(-1)) GO TO 120 CV = -CV CALL CUOIK(CV, FNU, KODE, 2, N1, W, NZ2, TOL, * ELIM, ALIM) C------------------ Overflow detected? - skip test for this case IF (NZ2.EQ.(-1)) GO TO 120 ENDIF C---------------- No overflow - calculate H1(Z,FNU) and H2(Z,FNU) CALL CBESH(Z, FNU, KODE, 1, N1, Y, NZ1, IERR) C---------------- Underflow? - skip test for this case IF (NZ1.NE.0) GO TO 120 CALL CBESH(Z, FNU, KODE, 2, N1, W, NZ2, IERR) C---------------- Underflow? - skip test for this case IF (NZ2.NE.0) GO TO 120 C----------------------------------------------------------------------- C Compare ZN/Z with the Wronskian of H1(Z,FNU) and H2(Z,FNU). C ZN = -4i/PI C----------------------------------------------------------------------- CV = ZN/Z MFLG = 0 DO 100 I = 1,N C----------------------------------------------------------------------- C Error relative to maximum term C----------------------------------------------------------------------- AW = ABS(W(I+1)) AY = ABS(Y(I)) AZ = LOG(AW) + LOG(AY) AZ = ABS(AZ) IF (AZ.LE.ALIM) THEN C-------------------- No scaling problem - do error analysis AV = ABS(CV) CW = W(I)*Y(I+1) CY = W(I+1)*Y(I) CY = CW - CY - CV ACY = AW*AY ACW = ABS(W(I))*ABS(Y(I+1)) AV = MAX(ACW,ACY,AV) ER = ABS(CY)/AV AER(I) = ER IF (ER.GT.ERTOL) THEN MFLG = 1 ENDIF ENDIF 100 CONTINUE IF (MFLG.NE.0) THEN IF (LFLG.EQ.0) THEN IF (KPRINT.GE.2) THEN WRITE (LUN,99995) ERTOL 99995 FORMAT (' CASES WHICH VIOLATE THE RELATIVE ', * 'ERROR TEST WITH ERTOL = ',E12.4/) WRITE (LUN,99994) 99994 FORMAT (' INPUT TO CBESH Z, FNU, KODE, N') ENDIF IF (KPRINT.GE.3) THEN WRITE (LUN,99993) 99993 FORMAT (' COMPARE -4i/(PI*Z) WITH WRONSKIAN OF', * ' H1(Z,FNU) AND H2(Z,FNU)') WRITE (LUN,99992) 99992 FORMAT (' RESULTS FROM CBESH FOR FUNCTION H1'/ * ' AND FUNCTION H2') WRITE (LUN,99991) 99991 FORMAT (' TEST CASE INDICES'/) ENDIF ENDIF LFLG = LFLG + 1 IF (KPRINT.GE.2) THEN WRITE (LUN,99990) Z, FNU, KODE, N 99990 FORMAT (' INPUT: Z=',2E12.4,4X,'FNU=',E12.4, * 4X,'KODE=',I3,4X,'N=',I3) ENDIF IF (KPRINT.GE.3) THEN WRITE (LUN,99989) (AER(K),K=1,N) 99989 FORMAT (' ERROR: AER(K)=',4E12.4) KK = MAX(NZ1,NZ2) + 1 KK = MIN(N,KK) WRITE (LUN,99988) NZ1, Y(KK), NZ2, W(KK) 99988 FORMAT (' RESULTS: NZ1=',I3,4X,'Y(KK)=',2E12.4/ * 11X,'NZ2=',I3,4X,'W(KK)=',2E12.4) WRITE (LUN,99987) IT, IR, ICASE 99987 FORMAT (' CASE: IT=',I3,4X,'IR=',I3,4X, * 'ICASE=',I3/) ENDIF ENDIF 120 CONTINUE 130 CONTINUE 140 CONTINUE 150 CONTINUE 160 CONTINUE 170 CONTINUE IF (KPRINT.GE.2) THEN IF (LFLG.EQ.0) THEN WRITE (LUN,99986) 99986 FORMAT (' QUICK CHECKS OK') ELSE WRITE (LUN,99985) LFLG 99985 FORMAT (' ***',I5,' FAILURE(S) FOR CBESH IN THE (Z,FNU)', * ' PLANE') ENDIF ENDIF IPASS = 0 IF (LFLG.EQ.0) THEN IPASS = 1 ENDIF IF (IPASS.EQ.1.AND.KPRINT.GE.2) THEN WRITE (LUN,99984) 99984 FORMAT (/' ****** CBESH PASSED ALL TESTS ******'/) ENDIF IF (IPASS.EQ.0.AND.KPRINT.GE.1) THEN WRITE (LUN,99983) 99983 FORMAT (/' ****** CBESH FAILED SOME TESTS ******'/) ENDIF RETURN END