| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273 | *DECK DSOS      SUBROUTINE DSOS (FNC, NEQ, X, RTOLX, ATOLX, TOLF, IFLAG, RW, LRW,     +   IW, LIW)C***BEGIN PROLOGUE  DSOSC***PURPOSE  Solve a square system of nonlinear equations.C***LIBRARY   SLATECC***CATEGORY  F2AC***TYPE      DOUBLE PRECISION (SOS-S, DSOS-D)C***KEYWORDS  BROWN'S METHOD, NEWTON'S METHOD, NONLINEAR EQUATIONS,C             ROOTS, SOLUTIONSC***AUTHOR  Watts, H. A., (SNLA)C***DESCRIPTIONCC     DSOS solves a system of NEQ simultaneous nonlinear equations inC     NEQ unknowns.  That is, it solves the problem   F(X)=0C     where X is a vector with components  X(1),...,X(NEQ)  and  FC     is a vector of nonlinear functions.  Each equation is of the formCC               F (X(1),...,X(NEQ))=0     for K=1,...,NEQ.C                KCC     The algorithm is based on an iterative method which is aC     variation of Newton's method using Gaussian eliminationC     in a manner similar to the Gauss-Seidel process.  ConvergenceC     is roughly quadratic.  All partial derivatives required byC     the algorithm are approximated by first difference quotients.C     The convergence behavior of this code is affected by theC     ordering of the equations, and it is advantageous to place linearC     and mildly nonlinear equations first in the ordering.CC     Actually, DSOS is merely an interfacing routine forC     calling subroutine DSOSEQ which embodies the solutionC     algorithm.  The purpose of this is to add greaterC     flexibility and ease of use for the prospective user.CC     DSOSEQ calls the accompanying routine DSOSSL which solves specialC     triangular linear systems by back-substitution.CC     The user must supply a function subprogram which evaluates theC     K-th equation only (K specified by DSOSEQ) for each callC     to the subprogram.CC     DSOS represents an implementation of the mathematical algorithmC     described in the references below.  It is a modification of theC     code SOSNLE written by H. A. Watts in 1973.CC **********************************************************************C   -Input-CC     FNC -Name of the function program which evaluates the equations.C          This name must be in an EXTERNAL statement in the callingC          program.  The user must supply FNC in the form FNC(X,K),C          where X is the solution vector (which must be dimensionedC          in FNC) and FNC returns the value of the K-th function.CC     NEQ -Number of equations to be solved.CC     X   -Solution vector.  Initial guesses must be supplied.CC     RTOLX -Relative error tolerance used in the convergence criteria.C          Each solution component X(I) is checked by an accuracy testC          of the form   ABS(X(I)-XOLD(I)) .LE. RTOLX*ABS(X(I))+ATOLX,C          where XOLD(I) represents the previous iteration value.C          RTOLX must be non-negative.CC     ATOLX -Absolute error tolerance used in the convergence criteria.C          ATOLX must be non-negative.  If the user suspects someC          solution component may be zero, he should set ATOLX to anC          appropriate (depends on the scale of the remaining variables)C          positive value for better efficiency.CC     TOLF -Residual error tolerance used in the convergence criteria.C          Convergence will be indicated if all residuals (values of theC          functions or equations) are not bigger than TOLF inC          magnitude.  Note that extreme care must be given in assigningC          an appropriate value for TOLF because this convergence testC          is dependent on the scaling of the equations.  AnC          inappropriate value can cause premature termination of theC          iteration process.CC     IFLAG -Optional input indicator.  You must set  IFLAG=-1  if youC          want to use any of the optional input items listed below.C          Otherwise set it to zero.CC     RW  -A DOUBLE PRECISION work array which is split apart by DSOSC          and used internally by DSOSEQ.CC     LRW -Dimension of the RW array.  LRW must be at leastC                    1 + 6*NEQ + NEQ*(NEQ+1)/2CC     IW  -An INTEGER work array which is split apart by DSOS and usedC          internally by DSOSEQ.CC     LIW -Dimension of the IW array. LIW must be at least  3 + NEQ.CC   -Optional Input-CC     IW(1) -Internal printing parameter.  You must set  IW(1)=-1  ifC          you want the intermediate solution iterates to be printed.CC     IW(2) -Iteration limit.  The maximum number of allowableC          iterations can be specified, if desired.  To override theC          default value of 50, set IW(2) to the number wanted.CC     Remember, if you tell the code that you are using one of theC               options (by setting IFLAG=-1), you must supply valuesC               for both IW(1) and IW(2).CC **********************************************************************C   -Output-CC     X   -Solution vector.CC     IFLAG -Status indicatorCC                         *** Convergence to a Solution ***CC          1 Means satisfactory convergence to a solution was achieved.C            Each solution component X(I) satisfies the error toleranceC            test   ABS(X(I)-XOLD(I)) .LE. RTOLX*ABS(X(I))+ATOLX.CC          2 Means procedure converged to a solution such that allC            residuals are at most TOLF in magnitude,C            ABS(FNC(X,I)) .LE. TOLF.CC          3 Means that conditions for both IFLAG=1 and IFLAG=2 hold.CC          4 Means possible numerical convergence.  Behavior indicatesC            limiting precision calculations as a result of user askingC            for too much accuracy or else convergence is very slow.C            Residual norms and solution increment norms haveC            remained roughly constant over several consecutiveC            iterations.CC                         *** Task Interrupted ***CC          5 Means the allowable number of iterations has been metC            without obtaining a solution to the specified accuracy.C            Very slow convergence may be indicated.  Examine theC            approximate solution returned and see if the errorC            tolerances seem appropriate.CC          6 Means the allowable number of iterations has been met andC            the iterative process does not appear to be converging.C            A local minimum may have been encountered or there may beC            limiting precision difficulties.CC          7 Means that the iterative scheme appears to be diverging.C            Residual norms and solution increment norms haveC            increased over several consecutive iterations.CC                         *** Task Cannot Be Continued ***CC          8 Means that a Jacobian-related matrix was singular.CC          9 Means improper input parameters.CC          *** IFLAG should be examined after each call to   ***C          *** DSOS with the appropriate action being taken. ***CCC     RW(1) -Contains a norm of the residual.CC     IW(3) -Contains the number of iterations used by the process.CC **********************************************************************CC***REFERENCES  K. M. Brown, Solution of simultaneous nonlinearC                 equations, Algorithm 316, Communications of theC                 A.C.M. 10, (1967), pp. 728-729.C               K. M. Brown, A quadratically convergent Newton-likeC                 method based upon Gaussian elimination, SIAM JournalC                 on Numerical Analysis 6, (1969), pp. 560-569.C***ROUTINES CALLED  DSOSEQ, XERMSGC***REVISION HISTORY  (YYMMDD)C   801001  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   900510  Convert XERRWV calls to XERMSG calls, change PrologueC           comments to agree with SOS.  (RWC)C   920501  Reformatted the REFERENCES section.  (WRB)C***END PROLOGUE  DSOS      INTEGER IFLAG, INPFLG, IPRINT, IW(*), K1, K2, K3, K4, K5, K6,     1     LIW, LRW, MXIT, NC, NCJS, NEQ, NSRI, NSRRC      DOUBLE PRECISION ATOLX, FNC, RTOLX, RW(*), TOLF, X(*)      CHARACTER*8 XERN1      CHARACTER*16 XERN3, XERN4      EXTERNAL FNCC***FIRST EXECUTABLE STATEMENT  DSOS      INPFLG = IFLAGCC     CHECK FOR VALID INPUTC      IF (NEQ .LE. 0) THEN         WRITE (XERN1, '(I8)') NEQ         CALL XERMSG ('SLATEC', 'DSOS', 'THE NUMBER OF EQUATIONS ' //     *      'MUST BE A POSITIVE INTEGER.  YOU HAVE CALLED THE ' //     *      'CODE WITH NEQ = ' // XERN1, 1, 1)         IFLAG = 9      ENDIFC      IF (RTOLX .LT. 0.0D0 .OR. ATOLX .LT. 0.0D0) THEN         WRITE (XERN3, '(1PE15.6)') ATOLX         WRITE (XERN4, '(1PE15.6)') RTOLX         CALL XERMSG ('SLATEC', 'DSOS', 'THE ERROR TOLERANCES FOR ' //     *      'THE SOLUTION ITERATES CANNOT BE NEGATIVE. YOU HAVE ' //     *      'CALLED THE CODE WITH  RTOLX = ' // XERN3 //     *      ' AND ATOLX = ' // XERN4,2, 1)            IFLAG = 9      ENDIFC      IF (TOLF .LT. 0.0D0) THEN         WRITE (XERN3, '(1PE15.6)') TOLF         CALL XERMSG ('SLATEC', 'DSOS', 'THE RESIDUAL ERROR ' //     *      'TOLERANCE MUST BE NON-NEGATIVE.  YOU HAVE CALLED THE ' //     *      'CODE WITH TOLF = ' // XERN3, 3, 1)            IFLAG = 9      ENDIFC      IPRINT = 0      MXIT = 50      IF (INPFLG .EQ. (-1)) THEN         IF (IW(1) .EQ. (-1)) IPRINT = -1         MXIT = IW(2)         IF (MXIT .LE. 0) THEN            WRITE (XERN1, '(I8)') MXIT            CALL XERMSG ('SLATEC', 'DSOS', 'YOU HAVE TOLD THE CODE ' //     *         'TO USE OPTIONAL INPUT ITEMS BY SETTING IFLAG=-1. ' //     *         'HOWEVER YOU HAVE CALLED THE CODE WITH THE MAXIMUM ' //     *         'ALLOWABLE NUMBER OF ITERATIONS SET TO IW(2) = ' //     *         XERN1, 4, 1)            IFLAG = 9         ENDIF      ENDIFC      NC = (NEQ*(NEQ+1))/2      IF (LRW .LT. 1 + 6*NEQ + NC) THEN         WRITE (XERN1, '(I8)') LRW         CALL XERMSG ('SLATEC', 'DSOS', 'DIMENSION OF THE RW ARRAY ' //     *      'MUST BE AT LEAST 1 + 6*NEQ + NEQ*(NEQ+1)/2 .  YOU HAVE ' //     *      'CALLED THE CODE WITH LRW = ' // XERN1, 5, 1)         IFLAG = 9      ENDIFC      IF (LIW .LT. 3 + NEQ) THEN         WRITE (XERN1, '(I8)') LIW         CALL XERMSG ('SLATEC', 'DSOS', 'DIMENSION OF THE IW ARRAY ' //     *      'MUST BE AT LEAST 3 + NEQ.  YOU HAVE CALLED THE CODE ' //     *      'WITH  LIW = ' // XERN1, 6, 1)         IFLAG = 9      ENDIFC      IF (IFLAG .NE. 9) THEN         NCJS = 6         NSRRC = 4         NSRI = 5C         K1 = NC + 2         K2 = K1 + NEQ         K3 = K2 + NEQ         K4 = K3 + NEQ         K5 = K4 + NEQ         K6 = K5 + NEQC         CALL DSOSEQ(FNC, NEQ, X, RTOLX, ATOLX, TOLF, IFLAG, MXIT, NCJS,     1               NSRRC, NSRI, IPRINT, RW(1), RW(2), NC, RW(K1),     2               RW(K2), RW(K3), RW(K4), RW(K5), RW(K6), IW(4))C         IW(3) = MXIT      ENDIF      RETURN      END
 |