dcov.f 9.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273
  1. *DECK DCOV
  2. SUBROUTINE DCOV (FCN, IOPT, M, N, X, FVEC, R, LDR, INFO, WA1, WA2,
  3. + WA3, WA4)
  4. C***BEGIN PROLOGUE DCOV
  5. C***PURPOSE Calculate the covariance matrix for a nonlinear data
  6. C fitting problem. It is intended to be used after a
  7. C successful return from either DNLS1 or DNLS1E.
  8. C***LIBRARY SLATEC
  9. C***CATEGORY K1B1
  10. C***TYPE DOUBLE PRECISION (SCOV-S, DCOV-D)
  11. C***KEYWORDS COVARIANCE MATRIX, NONLINEAR DATA FITTING,
  12. C NONLINEAR LEAST SQUARES
  13. C***AUTHOR Hiebert, K. L., (SNLA)
  14. C***DESCRIPTION
  15. C
  16. C 1. Purpose.
  17. C
  18. C DCOV calculates the covariance matrix for a nonlinear data
  19. C fitting problem. It is intended to be used after a
  20. C successful return from either DNLS1 or DNLS1E. DCOV
  21. C and DNLS1 (and DNLS1E) have compatible parameters. The
  22. C required external subroutine, FCN, is the same
  23. C for all three codes, DCOV, DNLS1, and DNLS1E.
  24. C
  25. C 2. Subroutine and Type Statements.
  26. C
  27. C SUBROUTINE DCOV(FCN,IOPT,M,N,X,FVEC,R,LDR,INFO,
  28. C WA1,WA2,WA3,WA4)
  29. C INTEGER IOPT,M,N,LDR,INFO
  30. C DOUBLE PRECISION X(N),FVEC(M),R(LDR,N),WA1(N),WA2(N),WA3(N),WA4(M)
  31. C EXTERNAL FCN
  32. C
  33. C 3. Parameters. All TYPE REAL parameters are DOUBLE PRECISION
  34. C
  35. C FCN is the name of the user-supplied subroutine which calculates
  36. C the functions. If the user wants to supply the Jacobian
  37. C (IOPT=2 or 3), then FCN must be written to calculate the
  38. C Jacobian, as well as the functions. See the explanation
  39. C of the IOPT argument below.
  40. C If the user wants the iterates printed in DNLS1 or DNLS1E,
  41. C then FCN must do the printing. See the explanation of NPRINT
  42. C in DNLS1 or DNLS1E. FCN must be declared in an EXTERNAL
  43. C statement in the calling program and should be written as
  44. C follows.
  45. C
  46. C SUBROUTINE FCN(IFLAG,M,N,X,FVEC,FJAC,LDFJAC)
  47. C INTEGER IFLAG,LDFJAC,M,N
  48. C DOUBLE PRECISION X(N),FVEC(M)
  49. C ----------
  50. C FJAC and LDFJAC may be ignored , if IOPT=1.
  51. C DOUBLE PRECISION FJAC(LDFJAC,N) , if IOPT=2.
  52. C DOUBLE PRECISION FJAC(N) , if IOPT=3.
  53. C ----------
  54. C If IFLAG=0, the values in X and FVEC are available
  55. C for printing in DNLS1 or DNLS1E.
  56. C IFLAG will never be zero when FCN is called by DCOV.
  57. C The values of X and FVEC must not be changed.
  58. C RETURN
  59. C ----------
  60. C If IFLAG=1, calculate the functions at X and return
  61. C this vector in FVEC.
  62. C RETURN
  63. C ----------
  64. C If IFLAG=2, calculate the full Jacobian at X and return
  65. C this matrix in FJAC. Note that IFLAG will never be 2 unless
  66. C IOPT=2. FVEC contains the function values at X and must
  67. C not be altered. FJAC(I,J) must be set to the derivative
  68. C of FVEC(I) with respect to X(J).
  69. C RETURN
  70. C ----------
  71. C If IFLAG=3, calculate the LDFJAC-th row of the Jacobian
  72. C and return this vector in FJAC. Note that IFLAG will
  73. C never be 3 unless IOPT=3. FJAC(J) must be set to
  74. C the derivative of FVEC(LDFJAC) with respect to X(J).
  75. C RETURN
  76. C ----------
  77. C END
  78. C
  79. C
  80. C The value of IFLAG should not be changed by FCN unless the
  81. C user wants to terminate execution of DCOV. In this case, set
  82. C IFLAG to a negative integer.
  83. C
  84. C
  85. C IOPT is an input variable which specifies how the Jacobian will
  86. C be calculated. If IOPT=2 or 3, then the user must supply the
  87. C Jacobian, as well as the function values, through the
  88. C subroutine FCN. If IOPT=2, the user supplies the full
  89. C Jacobian with one call to FCN. If IOPT=3, the user supplies
  90. C one row of the Jacobian with each call. (In this manner,
  91. C storage can be saved because the full Jacobian is not stored.)
  92. C If IOPT=1, the code will approximate the Jacobian by forward
  93. C differencing.
  94. C
  95. C M is a positive integer input variable set to the number of
  96. C functions.
  97. C
  98. C N is a positive integer input variable set to the number of
  99. C variables. N must not exceed M.
  100. C
  101. C X is an array of length N. On input X must contain the value
  102. C at which the covariance matrix is to be evaluated. This is
  103. C usually the value for X returned from a successful run of
  104. C DNLS1 (or DNLS1E). The value of X will not be changed.
  105. C
  106. C FVEC is an output array of length M which contains the functions
  107. C evaluated at X.
  108. C
  109. C R is an output array. For IOPT=1 and 2, R is an M by N array.
  110. C For IOPT=3, R is an N by N array. On output, if INFO=1,
  111. C the upper N by N submatrix of R contains the covariance
  112. C matrix evaluated at X.
  113. C
  114. C LDR is a positive integer input variable which specifies
  115. C the leading dimension of the array R. For IOPT=1 and 2,
  116. C LDR must not be less than M. For IOPT=3, LDR must not
  117. C be less than N.
  118. C
  119. C INFO is an integer output variable. If the user has terminated
  120. C execution, INFO is set to the (negative) value of IFLAG. See
  121. C description of FCN. Otherwise, INFO is set as follows.
  122. C
  123. C INFO = 0 Improper input parameters (M.LE.0 or N.LE.0).
  124. C
  125. C INFO = 1 Successful return. The covariance matrix has been
  126. C calculated and stored in the upper N by N
  127. C submatrix of R.
  128. C
  129. C INFO = 2 The Jacobian matrix is singular for the input value
  130. C of X. The covariance matrix cannot be calculated.
  131. C The upper N by N submatrix of R contains the QR
  132. C factorization of the Jacobian (probably not of
  133. C interest to the user).
  134. C
  135. C WA1,WA2 are work arrays of length N.
  136. C and WA3
  137. C
  138. C WA4 is a work array of length M.
  139. C
  140. C***REFERENCES (NONE)
  141. C***ROUTINES CALLED DENORM, DFDJC3, DQRFAC, DWUPDT, XERMSG
  142. C***REVISION HISTORY (YYMMDD)
  143. C 810522 DATE WRITTEN
  144. C 890831 Modified array declarations. (WRB)
  145. C 891006 Cosmetic changes to prologue. (WRB)
  146. C 891006 REVISION DATE from Version 3.2
  147. C 891214 Prologue converted to Version 4.0 format. (BAB)
  148. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  149. C 900510 Fixed an error message. (RWC)
  150. C***END PROLOGUE DCOV
  151. C
  152. C REVISED 850601-1100
  153. C REVISED YYMMDD HHMM
  154. C
  155. INTEGER I,IDUM,IFLAG,INFO,IOPT,J,K,KP1,LDR,M,N,NM1,NROW
  156. DOUBLE PRECISION X(*),R(LDR,*),FVEC(*),WA1(*),WA2(*),WA3(*),
  157. 1 WA4(*)
  158. EXTERNAL FCN
  159. DOUBLE PRECISION ONE,SIGMA,TEMP,ZERO,DENORM
  160. LOGICAL SING
  161. SAVE ZERO, ONE
  162. DATA ZERO/0.D0/,ONE/1.D0/
  163. C***FIRST EXECUTABLE STATEMENT DCOV
  164. SING=.FALSE.
  165. IFLAG=0
  166. IF (M.LE.0 .OR. N.LE.0) GO TO 300
  167. C
  168. C CALCULATE SIGMA = (SUM OF THE SQUARED RESIDUALS) / (M-N)
  169. IFLAG=1
  170. CALL FCN(IFLAG,M,N,X,FVEC,R,LDR)
  171. IF (IFLAG.LT.0) GO TO 300
  172. TEMP=DENORM(M,FVEC)
  173. SIGMA=ONE
  174. IF (M.NE.N) SIGMA=TEMP*TEMP/(M-N)
  175. C
  176. C CALCULATE THE JACOBIAN
  177. IF (IOPT.EQ.3) GO TO 200
  178. C
  179. C STORE THE FULL JACOBIAN USING M*N STORAGE
  180. IF (IOPT.EQ.1) GO TO 100
  181. C
  182. C USER SUPPLIES THE JACOBIAN
  183. IFLAG=2
  184. CALL FCN(IFLAG,M,N,X,FVEC,R,LDR)
  185. GO TO 110
  186. C
  187. C CODE APPROXIMATES THE JACOBIAN
  188. 100 CALL DFDJC3(FCN,M,N,X,FVEC,R,LDR,IFLAG,ZERO,WA4)
  189. 110 IF (IFLAG.LT.0) GO TO 300
  190. C
  191. C COMPUTE THE QR DECOMPOSITION
  192. CALL DQRFAC(M,N,R,LDR,.FALSE.,IDUM,1,WA1,WA1,WA1)
  193. DO 120 I=1,N
  194. 120 R(I,I)=WA1(I)
  195. GO TO 225
  196. C
  197. C COMPUTE THE QR FACTORIZATION OF THE JACOBIAN MATRIX CALCULATED ONE
  198. C ROW AT A TIME AND STORED IN THE UPPER TRIANGLE OF R.
  199. C ( (Q TRANSPOSE)*FVEC IS ALSO CALCULATED BUT NOT USED.)
  200. 200 CONTINUE
  201. DO 210 J=1,N
  202. WA2(J)=ZERO
  203. DO 205 I=1,N
  204. R(I,J)=ZERO
  205. 205 CONTINUE
  206. 210 CONTINUE
  207. IFLAG=3
  208. DO 220 I=1,M
  209. NROW = I
  210. CALL FCN(IFLAG,M,N,X,FVEC,WA1,NROW)
  211. IF (IFLAG.LT.0) GO TO 300
  212. TEMP=FVEC(I)
  213. CALL DWUPDT(N,R,LDR,WA1,WA2,TEMP,WA3,WA4)
  214. 220 CONTINUE
  215. C
  216. C CHECK IF R IS SINGULAR.
  217. 225 CONTINUE
  218. DO 230 I=1,N
  219. IF (R(I,I).EQ.ZERO) SING=.TRUE.
  220. 230 CONTINUE
  221. IF (SING) GO TO 300
  222. C
  223. C R IS UPPER TRIANGULAR. CALCULATE (R TRANSPOSE) INVERSE AND STORE
  224. C IN THE UPPER TRIANGLE OF R.
  225. IF (N.EQ.1) GO TO 275
  226. NM1=N-1
  227. DO 270 K=1,NM1
  228. C
  229. C INITIALIZE THE RIGHT-HAND SIDE (WA1(*)) AS THE K-TH COLUMN OF THE
  230. C IDENTITY MATRIX.
  231. DO 240 I=1,N
  232. WA1(I)=ZERO
  233. 240 CONTINUE
  234. WA1(K)=ONE
  235. C
  236. R(K,K)=WA1(K)/R(K,K)
  237. KP1=K+1
  238. DO 260 I=KP1,N
  239. C
  240. C SUBTRACT R(K,I-1)*R(I-1,*) FROM THE RIGHT-HAND SIDE, WA1(*).
  241. DO 250 J=I,N
  242. WA1(J)=WA1(J)-R(K,I-1)*R(I-1,J)
  243. 250 CONTINUE
  244. R(K,I)=WA1(I)/R(I,I)
  245. 260 CONTINUE
  246. 270 CONTINUE
  247. 275 R(N,N)=ONE/R(N,N)
  248. C
  249. C CALCULATE R-INVERSE * (R TRANSPOSE) INVERSE AND STORE IN THE UPPER
  250. C TRIANGLE OF R.
  251. DO 290 I=1,N
  252. DO 290 J=I,N
  253. TEMP=ZERO
  254. DO 280 K=J,N
  255. TEMP=TEMP+R(I,K)*R(J,K)
  256. 280 CONTINUE
  257. R(I,J)=TEMP*SIGMA
  258. 290 CONTINUE
  259. INFO=1
  260. C
  261. 300 CONTINUE
  262. IF (M.LE.0 .OR. N.LE.0) INFO=0
  263. IF (IFLAG.LT.0) INFO=IFLAG
  264. IF (SING) INFO=2
  265. IF (INFO .LT. 0) CALL XERMSG ('SLATEC', 'DCOV',
  266. + 'EXECUTION TERMINATED BECAUSE USER SET IFLAG NEGATIVE.', 1, 1)
  267. IF (INFO .EQ. 0) CALL XERMSG ('SLATEC', 'DCOV',
  268. + 'INVALID INPUT PARAMETER.', 2, 1)
  269. IF (INFO .EQ. 2) CALL XERMSG ('SLATEC', 'DCOV',
  270. + 'SINGULAR JACOBIAN MATRIX, COVARIANCE MATRIX CANNOT BE ' //
  271. + 'CALCULATED.', 1, 1)
  272. RETURN
  273. END