| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114 | *DECK FDJAC3      SUBROUTINE FDJAC3 (FCN, M, N, X, FVEC, FJAC, LDFJAC, IFLAG,     +   EPSFCN, WA)C***BEGIN PROLOGUE  FDJAC3C***SUBSIDIARYC***PURPOSE  Subsidiary to SNLS1 and SNLS1EC***LIBRARY   SLATECC***TYPE      SINGLE PRECISION (FDJAC3-S, DFDJC3-D)C***AUTHOR  (UNKNOWN)C***DESCRIPTIONCC     This subroutine computes a forward-difference approximationC     to the M by N Jacobian matrix associated with a specifiedC     problem of M functions in N variables.CC     The subroutine statement isCC       SUBROUTINE FDJAC3(FCN,M,N,X,FVEC,FJAC,LDFJAC,IFLAG,EPSFCN,WA)CC     whereCC       FCN is the name of the user-supplied subroutine whichC         calculates the functions. FCN must be declaredC         in an external statement in the user callingC         program, and should be written as follows.CC         SUBROUTINE FCN(IFLAG,M,N,X,FVEC,FJAC,LDFJAC)C         INTEGER LDFJAC,M,N,IFLAGC         REAL X(N),FVEC(M),FJAC(LDFJAC,N)C         ----------C         When IFLAG.EQ.1 calculate the functions at X andC         return this vector in FVEC.C         ----------C         RETURNC         ENDCC         The value of IFLAG should not be changed by FCN unlessC         the user wants to terminate execution of FDJAC3.C         In this case set IFLAG to a negative integer.CC       M is a positive integer input variable set to the numberC         of functions.CC       N is a positive integer input variable set to the numberC         of variables. N must not exceed M.CC       X is an input array of length N.CC       FVEC is an input array of length M which must contain theC         functions evaluated at X.CC       FJAC is an output M by N array which contains theC         approximation to the Jacobian matrix evaluated at X.CC       LDFJAC is a positive integer input variable not less than MC         which specifies the leading dimension of the array FJAC.CC       IFLAG is an integer variable which can be used to terminateC         THE EXECUTION OF FDJAC3. See description of FCN.CC       EPSFCN is an input variable used in determining a suitableC         step length for the forward-difference approximation. ThisC         approximation assumes that the relative errors in theC         functions are of the order of EPSFCN. If EPSFCN is lessC         than the machine precision, it is assumed that the relativeC         errors in the functions are of the order of the machineC         precision.CC       WA is a work array of length M.CC***SEE ALSO  SNLS1, SNLS1EC***ROUTINES CALLED  R1MACHC***REVISION HISTORY  (YYMMDD)C   800301  DATE WRITTENC   890531  Changed all specific intrinsics to generic.  (WRB)C   890831  Modified array declarations.  (WRB)C   891214  Prologue converted to Version 4.0 format.  (BAB)C   900326  Removed duplicate information from DESCRIPTION section.C           (WRB)C   900328  Added TYPE section.  (WRB)C***END PROLOGUE  FDJAC3      INTEGER M,N,LDFJAC,IFLAG      REAL EPSFCN      REAL X(*),FVEC(*),FJAC(LDFJAC,*),WA(*)      INTEGER I,J      REAL EPS,EPSMCH,H,TEMP,ZERO      REAL R1MACH      SAVE ZERO      DATA ZERO /0.0E0/C***FIRST EXECUTABLE STATEMENT  FDJAC3      EPSMCH = R1MACH(4)C      EPS = SQRT(MAX(EPSFCN,EPSMCH))C      SET IFLAG=1 TO INDICATE THAT FUNCTION VALUESC           ARE TO BE RETURNED BY FCN.      IFLAG = 1      DO 20 J = 1, N         TEMP = X(J)         H = EPS*ABS(TEMP)         IF (H .EQ. ZERO) H = EPS         X(J) = TEMP + H         CALL FCN(IFLAG,M,N,X,WA,FJAC,LDFJAC)         IF (IFLAG .LT. 0) GO TO 30         X(J) = TEMP         DO 10 I = 1, M            FJAC(I,J) = (WA(I) - FVEC(I))/H   10       CONTINUE   20    CONTINUE   30 CONTINUE      RETURNCC     LAST CARD OF SUBROUTINE FDJAC3.C      END
 |