dnsd.f

Go to the documentation of this file.
00001 C Work performed under the auspices of the U.S. Department of Energy
00002 C by Lawrence Livermore National Laboratory under contract number 
00003 C W-7405-Eng-48.
00004 C
00005       SUBROUTINE DNSD(X,Y,YPRIME,NEQ,RES,PDUM,WT,RPAR,IPAR,
00006      *   DUMSVR,DELTA,E,WM,IWM,CJ,DUMS,DUMR,DUME,EPCON,
00007      *   S,CONFAC,TOLNEW,MULDEL,MAXIT,IRES,IDUM,IERNEW)
00008 C
00009 C***BEGIN PROLOGUE  DNSD
00010 C***REFER TO  DDASPK
00011 C***DATE WRITTEN   891219   (YYMMDD)
00012 C***REVISION DATE  900926   (YYMMDD)
00013 C***REVISION DATE  950126   (YYMMDD)
00014 C
00015 C
00016 C-----------------------------------------------------------------------
00017 C***DESCRIPTION
00018 C
00019 C     DNSD solves a nonlinear system of
00020 C     algebraic equations of the form
00021 C     G(X,Y,YPRIME) = 0 for the unknown Y.
00022 C
00023 C     The method used is a modified Newton scheme.
00024 C
00025 C     The parameters represent
00026 C
00027 C     X         -- Independent variable.
00028 C     Y         -- Solution vector.
00029 C     YPRIME    -- Derivative of solution vector.
00030 C     NEQ       -- Number of unknowns.
00031 C     RES       -- External user-supplied subroutine
00032 C                  to evaluate the residual.  See RES description
00033 C                  in DDASPK prologue.
00034 C     PDUM      -- Dummy argument.
00035 C     WT        -- Vector of weights for error criterion.
00036 C     RPAR,IPAR -- Real and integer arrays used for communication
00037 C                  between the calling program and external user
00038 C                  routines.  They are not altered within DASPK.
00039 C     DUMSVR    -- Dummy argument.
00040 C     DELTA     -- Work vector for DNSD of length NEQ.
00041 C     E         -- Error accumulation vector for DNSD of length NEQ.
00042 C     WM,IWM    -- Real and integer arrays storing
00043 C                  matrix information such as the matrix
00044 C                  of partial derivatives, permutation
00045 C                  vector, and various other information.
00046 C     CJ        -- Parameter always proportional to 1/H (step size).
00047 C     DUMS      -- Dummy argument.
00048 C     DUMR      -- Dummy argument.
00049 C     DUME      -- Dummy argument.
00050 C     EPCON     -- Tolerance to test for convergence of the Newton
00051 C                  iteration.
00052 C     S         -- Used for error convergence tests.
00053 C                  In the Newton iteration: S = RATE/(1 - RATE),
00054 C                  where RATE is the estimated rate of convergence
00055 C                  of the Newton iteration.
00056 C                  The calling routine passes the initial value
00057 C                  of S to the Newton iteration.
00058 C     CONFAC    -- A residual scale factor to improve convergence.
00059 C     TOLNEW    -- Tolerance on the norm of Newton correction in
00060 C                  alternative Newton convergence test.
00061 C     MULDEL    -- A flag indicating whether or not to multiply
00062 C                  DELTA by CONFAC.
00063 C                  0  ==> do not scale DELTA by CONFAC.
00064 C                  1  ==> scale DELTA by CONFAC.
00065 C     MAXIT     -- Maximum allowed number of Newton iterations.
00066 C     IRES      -- Error flag returned from RES.  See RES description
00067 C                  in DDASPK prologue.  If IRES = -1, then IERNEW
00068 C                  will be set to 1.
00069 C                  If IRES < -1, then IERNEW will be set to -1.
00070 C     IDUM      -- Dummy argument.
00071 C     IERNEW    -- Error flag for Newton iteration.
00072 C                   0  ==> Newton iteration converged.
00073 C                   1  ==> recoverable error inside Newton iteration.
00074 C                  -1  ==> unrecoverable error inside Newton iteration.
00075 C
00076 C     All arguments with "DUM" in their names are dummy arguments
00077 C     which are not used in this routine.
00078 C-----------------------------------------------------------------------
00079 C
00080 C***ROUTINES CALLED
00081 C   DSLVD, DDWNRM, RES
00082 C
00083 C***END PROLOGUE  DNSD
00084 C
00085 C
00086       IMPLICIT DOUBLE PRECISION(A-H,O-Z)
00087       DIMENSION Y(*),YPRIME(*),WT(*),DELTA(*),E(*)
00088       DIMENSION WM(*),IWM(*), RPAR(*),IPAR(*)
00089       EXTERNAL  RES
00090 C
00091       PARAMETER (LNRE=12, LNNI=19)
00092 C
00093 C     Initialize Newton counter M and accumulation vector E. 
00094 C
00095       M = 0
00096       DO 100 I=1,NEQ
00097 100     E(I)=0.0D0
00098 C
00099 C     Corrector loop.
00100 C
00101 300   CONTINUE
00102       IWM(LNNI) = IWM(LNNI) + 1
00103 C
00104 C     If necessary, multiply residual by convergence factor.
00105 C
00106       IF (MULDEL .EQ. 1) THEN
00107          DO 320 I = 1,NEQ
00108 320        DELTA(I) = DELTA(I) * CONFAC
00109         ENDIF
00110 C
00111 C     Compute a new iterate (back-substitution).
00112 C     Store the correction in DELTA.
00113 C
00114       CALL DSLVD(NEQ,DELTA,WM,IWM)
00115 C
00116 C     Update Y, E, and YPRIME.
00117 C
00118       DO 340 I=1,NEQ
00119          Y(I)=Y(I)-DELTA(I)
00120          E(I)=E(I)-DELTA(I)
00121 340      YPRIME(I)=YPRIME(I)-CJ*DELTA(I)
00122 C
00123 C     Test for convergence of the iteration.
00124 C
00125       DELNRM=DDWNRM(NEQ,DELTA,WT,RPAR,IPAR)
00126       IF (DELNRM .LE. TOLNEW) GO TO 370
00127       IF (M .EQ. 0) THEN
00128         OLDNRM = DELNRM
00129       ELSE
00130         RATE = (DELNRM/OLDNRM)**(1.0D0/M)
00131         IF (RATE .GT. 0.9D0) GO TO 380
00132         S = RATE/(1.0D0 - RATE)
00133       ENDIF
00134       IF (S*DELNRM .LE. EPCON) GO TO 370
00135 C
00136 C     The corrector has not yet converged.
00137 C     Update M and test whether the
00138 C     maximum number of iterations have
00139 C     been tried.
00140 C
00141       M=M+1
00142       IF(M.GE.MAXIT) GO TO 380
00143 C
00144 C     Evaluate the residual,
00145 C     and go back to do another iteration.
00146 C
00147       IWM(LNRE)=IWM(LNRE)+1
00148       CALL RES(X,Y,YPRIME,CJ,DELTA,IRES,RPAR,IPAR)
00149       IF (IRES .LT. 0) GO TO 380
00150       GO TO 300
00151 C
00152 C     The iteration has converged.
00153 C
00154 370   RETURN
00155 C
00156 C     The iteration has not converged.  Set IERNEW appropriately.
00157 C
00158 380   CONTINUE
00159       IF (IRES .LE. -2 ) THEN
00160          IERNEW = -1
00161       ELSE
00162          IERNEW = 1
00163       ENDIF
00164       RETURN
00165 C
00166 C
00167 C------END OF SUBROUTINE DNSD-------------------------------------------
00168       END
 All Classes Files Functions Variables Typedefs Enumerations Enumerator Friends Defines