| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236 | *DECK QAWO      SUBROUTINE QAWO (F, A, B, OMEGA, INTEGR, EPSABS, EPSREL, RESULT,     +   ABSERR, NEVAL, IER, LENIW, MAXP1, LENW, LAST, IWORK, WORK)C***BEGIN PROLOGUE  QAWOC***PURPOSE  Calculate an approximation to a given definite integralC             I = Integral of F(X)*W(X) over (A,B), whereC                   W(X) = COS(OMEGA*X)C                or W(X) = SIN(OMEGA*X),C            hopefully satisfying the following claim for accuracyC                ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I)).C***LIBRARY   SLATEC (QUADPACK)C***CATEGORY  H2A2A1C***TYPE      SINGLE PRECISION (QAWO-S, DQAWO-D)C***KEYWORDS  AUTOMATIC INTEGRATOR, CLENSHAW-CURTIS METHOD,C             EXTRAPOLATION, GLOBALLY ADAPTIVE,C             INTEGRAND WITH OSCILLATORY COS OR SIN FACTOR, QUADPACK,C             QUADRATURE, SPECIAL-PURPOSEC***AUTHOR  Piessens, RobertC             Applied Mathematics and Programming DivisionC             K. U. LeuvenC           de Doncker, EliseC             Applied Mathematics and Programming DivisionC             K. U. LeuvenC***DESCRIPTIONCC        Computation of oscillatory integralsC        Standard fortran subroutineC        Real versionCC        PARAMETERSC         ON ENTRYC            F      - RealC                     Function subprogram defining the functionC                     F(X).  The actual name for F needs to beC                     declared E X T E R N A L in the driver program.CC            A      - RealC                     Lower limit of integrationCC            B      - RealC                     Upper limit of integrationCC            OMEGA  - RealC                     Parameter in the integrand weight functionCC            INTEGR - IntegerC                     Indicates which of the weight functions is usedC                     INTEGR = 1      W(X) = COS(OMEGA*X)C                     INTEGR = 2      W(X) = SIN(OMEGA*X)C                     If INTEGR.NE.1.AND.INTEGR.NE.2, the routine willC                     end with IER = 6.CC            EPSABS - RealC                     Absolute accuracy requestedC            EPSREL - RealC                     Relative accuracy requestedC                     If EPSABS.LE.0 andC                     EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),C                     the routine will end with IER = 6.CC         ON RETURNC            RESULT - RealC                     Approximation to the integralCC            ABSERR - RealC                     Estimate of the modulus of the absolute error,C                     which should equal or exceed ABS(I-RESULT)CC            NEVAL  - IntegerC                     Number of  integrand evaluationsCC            IER    - IntegerC                     IER = 0 Normal and reliable termination of theC                             routine. It is assumed that the requestedC                             accuracy has been achieved.C                   - IER.GT.0 Abnormal termination of the routine.C                             The estimates for integral and error areC                             less reliable. It is assumed that theC                             requested accuracy has not been achieved.C            ERROR MESSAGESC                     IER = 1 Maximum number of subdivisions allowedC                             has been achieved(= LENIW/2). One canC                             allow more subdivisions by increasing theC                             value of LENIW (and taking the accordingC                             dimension adjustments into account).C                             However, if this yields no improvement itC                             is advised to analyze the integrand inC                             order to determine the integrationC                             difficulties. If the position of a localC                             difficulty can be determined (e.g.C                             SINGULARITY, DISCONTINUITY within theC                             interval) one will probably gain fromC                             splitting up the interval at this pointC                             and calling the integrator on theC                             subranges. If possible, an appropriateC                             special-purpose integrator should be usedC                             which is designed for handling the type ofC                             difficulty involved.C                         = 2 The occurrence of roundoff error isC                             detected, which prevents the requestedC                             tolerance from being achieved.C                             The error may be under-estimated.C                         = 3 Extremely bad integrand behaviour occursC                             at some interior points of theC                             integration interval.C                         = 4 The algorithm does not converge.C                             Roundoff error is detected in theC                             extrapolation table. It is presumed thatC                             the requested tolerance cannot be achievedC                             due to roundoff in the extrapolationC                             table, and that the returned result isC                             the best which can be obtained.C                         = 5 The integral is probably divergent, orC                             slowly convergent. It must be noted thatC                             divergence can occur with any other valueC                             of IER.C                         = 6 The input is invalid, becauseC                             (EPSABS.LE.0 andC                              EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28))C                             or (INTEGR.NE.1 AND INTEGR.NE.2),C                             or LENIW.LT.2 OR MAXP1.LT.1 orC                             LENW.LT.LENIW*2+MAXP1*25.C                             RESULT, ABSERR, NEVAL, LAST are set toC                             zero. Except when LENIW, MAXP1 or LENW areC                             invalid, WORK(LIMIT*2+1), WORK(LIMIT*3+1),C                             IWORK(1), IWORK(LIMIT+1) are set to zero,C                             WORK(1) is set to A and WORK(LIMIT+1) toC                             B.CC         DIMENSIONING PARAMETERSC            LENIW  - IntegerC                     Dimensioning parameter for IWORK.C                     LENIW/2 equals the maximum number of subintervalsC                     allowed in the partition of the given integrationC                     interval (A,B), LENIW.GE.2.C                     If LENIW.LT.2, the routine will end with IER = 6.CC            MAXP1  - IntegerC                     Gives an upper bound on the number of ChebyshevC                     moments which can be stored, i.e. for theC                     intervals of lengths ABS(B-A)*2**(-L),C                     L=0,1, ..., MAXP1-2, MAXP1.GE.1C                     If MAXP1.LT.1, the routine will end with IER = 6.CC            LENW   - IntegerC                     Dimensioning parameter for WORKC                     LENW must be at least LENIW*2+MAXP1*25.C                     If LENW.LT.(LENIW*2+MAXP1*25), the routine willC                     end with IER = 6.CC            LAST   - IntegerC                     On return, LAST equals the number of subintervalsC                     produced in the subdivision process, whichC                     determines the number of significant elementsC                     actually in the WORK ARRAYS.CC         WORK ARRAYSC            IWORK  - IntegerC                     Vector of dimension at least LENIWC                     on return, the first K elements of which containC                     pointers to the error estimates over theC                     subintervals, such that WORK(LIMIT*3+IWORK(1)), ..C                     WORK(LIMIT*3+IWORK(K)) form a decreasingC                     sequence, with LIMIT = LENW/2 , and K = LASTC                     if LAST.LE.(LIMIT/2+2), and K = LIMIT+1-LASTC                     otherwise.C                     Furthermore, IWORK(LIMIT+1), ..., IWORK(LIMIT+C                     LAST) indicate the subdivision levels of theC                     subintervals, such that IWORK(LIMIT+I) = L meansC                     that the subinterval numbered I is of lengthC                     ABS(B-A)*2**(1-L).CC            WORK   - RealC                     Vector of dimension at least LENWC                     On returnC                     WORK(1), ..., WORK(LAST) contain the leftC                      end points of the subintervals in theC                      partition of (A,B),C                     WORK(LIMIT+1), ..., WORK(LIMIT+LAST) containC                      the right end points,C                     WORK(LIMIT*2+1), ..., WORK(LIMIT*2+LAST) containC                      the integral approximations over theC                      subintervals,C                     WORK(LIMIT*3+1), ..., WORK(LIMIT*3+LAST)C                      contain the error estimates.C                     WORK(LIMIT*4+1), ..., WORK(LIMIT*4+MAXP1*25)C                      Provide space for storing the Chebyshev moments.C                     Note that LIMIT = LENW/2.CC***REFERENCES  (NONE)C***ROUTINES CALLED  QAWOE, XERMSGC***REVISION HISTORY  (YYMMDD)C   800101  DATE WRITTENC   890831  Modified array declarations.  (WRB)C   890831  REVISION DATE from Version 3.2C   891214  Prologue converted to Version 4.0 format.  (BAB)C   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)C***END PROLOGUE  QAWOC       REAL A,ABSERR,B,EPSABS,EPSREL,F,OMEGA,RESULT       INTEGER IER,INTEGR,LENIW,LVL,L1,L2,L3,L4,MAXP1,MOMCOM,NEVALC       DIMENSION IWORK(*),WORK(*)C       EXTERNAL FCC         CHECK VALIDITY OF LENIW, MAXP1 AND LENW.CC***FIRST EXECUTABLE STATEMENT  QAWO      IER = 6      NEVAL = 0      LAST = 0      RESULT = 0.0E+00      ABSERR = 0.0E+00      IF(LENIW.LT.2.OR.MAXP1.LT.1.OR.LENW.LT.(LENIW*2+MAXP1*25))     1  GO TO 10CC         PREPARE CALL FOR QAWOEC      LIMIT = LENIW/2      L1 = LIMIT+1      L2 = LIMIT+L1      L3 = LIMIT+L2      L4 = LIMIT+L3      CALL QAWOE(F,A,B,OMEGA,INTEGR,EPSABS,EPSREL,LIMIT,1,MAXP1,RESULT,     1  ABSERR,NEVAL,IER,LAST,WORK(1),WORK(L1),WORK(L2),WORK(L3),     2  IWORK(1),IWORK(L1),MOMCOM,WORK(L4))CC         CALL ERROR HANDLER IF NECESSARYC      LVL = 010    IF(IER.EQ.6) LVL = 1      IF (IER .NE. 0) CALL XERMSG ('SLATEC', 'QAWO',     +   'ABNORMAL RETURN', IER, LVL)      RETURN      END
 |