dnls1e.f 21 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536
  1. *DECK DNLS1E
  2. SUBROUTINE DNLS1E (FCN, IOPT, M, N, X, FVEC, TOL, NPRINT, INFO,
  3. + IW, WA, LWA)
  4. C***BEGIN PROLOGUE DNLS1E
  5. C***PURPOSE An easy-to-use code which minimizes the sum of the squares
  6. C of M nonlinear functions in N variables by a modification
  7. C of the Levenberg-Marquardt algorithm.
  8. C***LIBRARY SLATEC
  9. C***CATEGORY K1B1A1, K1B1A2
  10. C***TYPE DOUBLE PRECISION (SNLS1E-S, DNLS1E-D)
  11. C***KEYWORDS EASY-TO-USE, LEVENBERG-MARQUARDT, 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 The purpose of DNLS1E is to minimize the sum of the squares of M
  19. C nonlinear functions in N variables by a modification of the
  20. C Levenberg-Marquardt algorithm. This is done by using the more
  21. C general least-squares solver DNLS1. The user must provide a
  22. C subroutine which calculates the functions. The user has the
  23. C option of how the Jacobian will be supplied. The user can
  24. C supply the full Jacobian, or the rows of the Jacobian (to avoid
  25. C storing the full Jacobian), or let the code approximate the
  26. C Jacobian by forward-differencing. This code is the combination
  27. C of the MINPACK codes (Argonne) LMDER1, LMDIF1, and LMSTR1.
  28. C
  29. C
  30. C 2. Subroutine and Type Statements.
  31. C
  32. C SUBROUTINE DNLS1E(FCN,IOPT,M,N,X,FVEC,TOL,NPRINT,
  33. C * INFO,IW,WA,LWA)
  34. C INTEGER IOPT,M,N,NPRINT,INFO,LWAC,IW(N)
  35. C DOUBLE PRECISION TOL,X(N),FVEC(M),WA(LWA)
  36. C EXTERNAL FCN
  37. C
  38. C
  39. C 3. Parameters. ALL TYPE REAL parameters are DOUBLE PRECISION
  40. C
  41. C Parameters designated as input parameters must be specified on
  42. C entry to DNLS1E and are not changed on exit, while parameters
  43. C designated as output parameters need not be specified on entry
  44. C and are set to appropriate values on exit from DNLS1E.
  45. C
  46. C FCN is the name of the user-supplied subroutine which calculates
  47. C the functions. If the user wants to supply the Jacobian
  48. C (IOPT=2 or 3), then FCN must be written to calculate the
  49. C Jacobian, as well as the functions. See the explanation
  50. C of the IOPT argument below.
  51. C If the user wants the iterates printed (NPRINT positive), then
  52. C FCN must do the printing. See the explanation of NPRINT
  53. C below. FCN must be declared in an EXTERNAL statement in the
  54. C calling program and should be written as follows.
  55. C
  56. C
  57. C SUBROUTINE FCN(IFLAG,M,N,X,FVEC,FJAC,LDFJAC)
  58. C INTEGER IFLAG,LDFJAC,M,N
  59. C DOUBLE PRECISION X(N),FVEC(M)
  60. C ----------
  61. C FJAC and LDFJAC may be ignored , if IOPT=1.
  62. C DOUBLE PRECISION FJAC(LDFJAC,N) , if IOPT=2.
  63. C DOUBLE PRECISION FJAC(N) , if IOPT=3.
  64. C ----------
  65. C If IFLAG=0, the values in X and FVEC are available
  66. C for printing. See the explanation of NPRINT below.
  67. C IFLAG will never be zero unless NPRINT is positive.
  68. C The values of X and FVEC must not be changed.
  69. C RETURN
  70. C ----------
  71. C If IFLAG=1, calculate the functions at X and return
  72. C this vector in FVEC.
  73. C RETURN
  74. C ----------
  75. C If IFLAG=2, calculate the full Jacobian at X and return
  76. C this matrix in FJAC. Note that IFLAG will never be 2 unless
  77. C IOPT=2. FVEC contains the function values at X and must
  78. C not be altered. FJAC(I,J) must be set to the derivative
  79. C of FVEC(I) with respect to X(J).
  80. C RETURN
  81. C ----------
  82. C If IFLAG=3, calculate the LDFJAC-th row of the Jacobian
  83. C and return this vector in FJAC. Note that IFLAG will
  84. C never be 3 unless IOPT=3. FVEC contains the function
  85. C values at X and must not be altered. FJAC(J) must be
  86. C set to the derivative of FVEC(LDFJAC) with respect to X(J).
  87. C RETURN
  88. C ----------
  89. C END
  90. C
  91. C
  92. C The value of IFLAG should not be changed by FCN unless the
  93. C user wants to terminate execution of DNLS1E. In this case,
  94. C set IFLAG to a negative integer.
  95. C
  96. C
  97. C IOPT is an input variable which specifies how the Jacobian will
  98. C be calculated. If IOPT=2 or 3, then the user must supply the
  99. C Jacobian, as well as the function values, through the
  100. C subroutine FCN. If IOPT=2, the user supplies the full
  101. C Jacobian with one call to FCN. If IOPT=3, the user supplies
  102. C one row of the Jacobian with each call. (In this manner,
  103. C storage can be saved because the full Jacobian is not stored.)
  104. C If IOPT=1, the code will approximate the Jacobian by forward
  105. C differencing.
  106. C
  107. C M is a positive integer input variable set to the number of
  108. C functions.
  109. C
  110. C N is a positive integer input variable set to the number of
  111. C variables. N must not exceed M.
  112. C
  113. C X is an array of length N. On input, X must contain an initial
  114. C estimate of the solution vector. On output, X contains the
  115. C final estimate of the solution vector.
  116. C
  117. C FVEC is an output array of length M which contains the functions
  118. C evaluated at the output X.
  119. C
  120. C TOL is a non-negative input variable. Termination occurs when
  121. C the algorithm estimates either that the relative error in the
  122. C sum of squares is at most TOL or that the relative error
  123. C between X and the solution is at most TOL. Section 4 contains
  124. C more details about TOL.
  125. C
  126. C NPRINT is an integer input variable that enables controlled
  127. C printing of iterates if it is positive. In this case, FCN is
  128. C called with IFLAG = 0 at the beginning of the first iteration
  129. C and every NPRINT iterations thereafter and immediately prior
  130. C to return, with X and FVEC available for printing. Appropriate
  131. C print statements must be added to FCN (see example) and
  132. C FVEC should not be altered. If NPRINT is not positive, no
  133. C special calls of FCN with IFLAG = 0 are made.
  134. C
  135. C INFO is an integer output variable. If the user has terminated
  136. C execution, INFO is set to the (negative) value of IFLAG. See
  137. C description of FCN and JAC. Otherwise, INFO is set as follows.
  138. C
  139. C INFO = 0 improper input parameters.
  140. C
  141. C INFO = 1 algorithm estimates that the relative error in the
  142. C sum of squares is at most TOL.
  143. C
  144. C INFO = 2 algorithm estimates that the relative error between
  145. C X and the solution is at most TOL.
  146. C
  147. C INFO = 3 conditions for INFO = 1 and INFO = 2 both hold.
  148. C
  149. C INFO = 4 FVEC is orthogonal to the columns of the Jacobian to
  150. C machine precision.
  151. C
  152. C INFO = 5 number of calls to FCN has reached 100*(N+1)
  153. C for IOPT=2 or 3 or 200*(N+1) for IOPT=1.
  154. C
  155. C INFO = 6 TOL is too small. No further reduction in the sum
  156. C of squares is possible.
  157. C
  158. C INFO = 7 TOL is too small. No further improvement in the
  159. C approximate solution X is possible.
  160. C
  161. C Sections 4 and 5 contain more details about INFO.
  162. C
  163. C IW is an INTEGER work array of length N.
  164. C
  165. C WA is a work array of length LWA.
  166. C
  167. C LWA is a positive integer input variable not less than
  168. C N*(M+5)+M for IOPT=1 and 2 or N*(N+5)+M for IOPT=3.
  169. C
  170. C
  171. C 4. Successful Completion.
  172. C
  173. C The accuracy of DNLS1E is controlled by the convergence parame-
  174. C ter TOL. This parameter is used in tests which make three types
  175. C of comparisons between the approximation X and a solution XSOL.
  176. C DNLS1E terminates when any of the tests is satisfied. If TOL is
  177. C less than the machine precision (as defined by the function
  178. C R1MACH(4)), then DNLS1E only attempts to satisfy the test
  179. C defined by the machine precision. Further progress is not usu-
  180. C ally possible. Unless high precision solutions are required,
  181. C the recommended value for TOL is the square root of the machine
  182. C precision.
  183. C
  184. C The tests assume that the functions are reasonably well behaved,
  185. C and, if the Jacobian is supplied by the user, that the functions
  186. C and the Jacobian are coded consistently. If these conditions
  187. C are not satisfied, then DNLS1E may incorrectly indicate conver-
  188. C gence. If the Jacobian is coded correctly or IOPT=1,
  189. C then the validity of the answer can be checked, for example, by
  190. C rerunning DNLS1E with tighter tolerances.
  191. C
  192. C First Convergence Test. If ENORM(Z) denotes the Euclidean norm
  193. C of a vector Z, then this test attempts to guarantee that
  194. C
  195. C ENORM(FVEC) .LE. (1+TOL)*ENORM(FVECS),
  196. C
  197. C where FVECS denotes the functions evaluated at XSOL. If this
  198. C condition is satisfied with TOL = 10**(-K), then the final
  199. C residual norm ENORM(FVEC) has K significant decimal digits and
  200. C INFO is set to 1 (or to 3 if the second test is also satis-
  201. C fied).
  202. C
  203. C Second Convergence Test. If D is a diagonal matrix (implicitly
  204. C generated by DNLS1E) whose entries contain scale factors for
  205. C the variables, then this test attempts to guarantee that
  206. C
  207. C ENORM(D*(X-XSOL)) .LE. TOL*ENORM(D*XSOL).
  208. C
  209. C If this condition is satisfied with TOL = 10**(-K), then the
  210. C larger components of D*X have K significant decimal digits and
  211. C INFO is set to 2 (or to 3 if the first test is also satis-
  212. C fied). There is a danger that the smaller components of D*X
  213. C may have large relative errors, but the choice of D is such
  214. C that the accuracy of the components of X is usually related to
  215. C their sensitivity.
  216. C
  217. C Third Convergence Test. This test is satisfied when FVEC is
  218. C orthogonal to the columns of the Jacobian to machine preci-
  219. C sion. There is no clear relationship between this test and
  220. C the accuracy of DNLS1E, and furthermore, the test is equally
  221. C well satisfied at other critical points, namely maximizers and
  222. C saddle points. Therefore, termination caused by this test
  223. C (INFO = 4) should be examined carefully.
  224. C
  225. C
  226. C 5. Unsuccessful Completion.
  227. C
  228. C Unsuccessful termination of DNLS1E can be due to improper input
  229. C parameters, arithmetic interrupts, or an excessive number of
  230. C function evaluations.
  231. C
  232. C Improper Input Parameters. INFO is set to 0 if IOPT .LT. 1
  233. C or IOPT .GT. 3, or N .LE. 0, or M .LT. N, or TOL .LT. 0.E0,
  234. C or for IOPT=1 or 2 LWA .LT. N*(M+5)+M, or for IOPT=3
  235. C LWA .LT. N*(N+5)+M.
  236. C
  237. C Arithmetic Interrupts. If these interrupts occur in the FCN
  238. C subroutine during an early stage of the computation, they may
  239. C be caused by an unacceptable choice of X by DNLS1E. In this
  240. C case, it may be possible to remedy the situation by not evalu-
  241. C ating the functions here, but instead setting the components
  242. C of FVEC to numbers that exceed those in the initial FVEC.
  243. C
  244. C Excessive Number of Function Evaluations. If the number of
  245. C calls to FCN reaches 100*(N+1) for IOPT=2 or 3 or 200*(N+1)
  246. C for IOPT=1, then this indicates that the routine is converging
  247. C very slowly as measured by the progress of FVEC, and INFO is
  248. C set to 5. In this case, it may be helpful to restart DNLS1E,
  249. C thereby forcing it to disregard old (and possibly harmful)
  250. C information.
  251. C
  252. C
  253. C 6. Characteristics of the Algorithm.
  254. C
  255. C DNLS1E is a modification of the Levenberg-Marquardt algorithm.
  256. C Two of its main characteristics involve the proper use of
  257. C implicitly scaled variables and an optimal choice for the cor-
  258. C rection. The use of implicitly scaled variables achieves scale
  259. C invariance of DNLS1E and limits the size of the correction in
  260. C any direction where the functions are changing rapidly. The
  261. C optimal choice of the correction guarantees (under reasonable
  262. C conditions) global convergence from starting points far from the
  263. C solution and a fast rate of convergence for problems with small
  264. C residuals.
  265. C
  266. C Timing. The time required by DNLS1E to solve a given problem
  267. C depends on M and N, the behavior of the functions, the accu-
  268. C racy requested, and the starting point. The number of arith-
  269. C metic operations needed by DNLS1E is about N**3 to process
  270. C each evaluation of the functions (call to FCN) and to process
  271. C each evaluation of the Jacobian DNLS1E takes M*N**2 for IOPT=2
  272. C (one call to JAC), M*N**2 for IOPT=1 (N calls to FCN) and
  273. C 1.5*M*N**2 for IOPT=3 (M calls to FCN). Unless FCN
  274. C can be evaluated quickly, the timing of DNLS1E will be
  275. C strongly influenced by the time spent in FCN.
  276. C
  277. C Storage. DNLS1E requires (M*N + 2*M + 6*N) for IOPT=1 or 2 and
  278. C (N**2 + 2*M + 6*N) for IOPT=3 single precision storage
  279. C locations and N integer storage locations, in addition to
  280. C the storage required by the program. There are no internally
  281. C declared storage arrays.
  282. C
  283. C *Long Description:
  284. C
  285. C 7. Example.
  286. C
  287. C The problem is to determine the values of X(1), X(2), and X(3)
  288. C which provide the best fit (in the least squares sense) of
  289. C
  290. C X(1) + U(I)/(V(I)*X(2) + W(I)*X(3)), I = 1, 15
  291. C
  292. C to the data
  293. C
  294. C Y = (0.14,0.18,0.22,0.25,0.29,0.32,0.35,0.39,
  295. C 0.37,0.58,0.73,0.96,1.34,2.10,4.39),
  296. C
  297. C where U(I) = I, V(I) = 16 - I, and W(I) = MIN(U(I),V(I)). The
  298. C I-th component of FVEC is thus defined by
  299. C
  300. C Y(I) - (X(1) + U(I)/(V(I)*X(2) + W(I)*X(3))).
  301. C
  302. C **********
  303. C
  304. C PROGRAM TEST
  305. C C
  306. C C Driver for DNLS1E example.
  307. C C
  308. C INTEGER I,IOPT,M,N,NPRINT,JNFO,LWA,NWRITE
  309. C INTEGER IW(3)
  310. C DOUBLE PRECISION TOL,FNORM,X(3),FVEC(15),WA(75)
  311. C DOUBLE PRECISION DENORM,D1MACH
  312. C EXTERNAL FCN
  313. C DATA NWRITE /6/
  314. C C
  315. C IOPT = 1
  316. C M = 15
  317. C N = 3
  318. C C
  319. C C The following starting values provide a rough fit.
  320. C C
  321. C X(1) = 1.E0
  322. C X(2) = 1.E0
  323. C X(3) = 1.E0
  324. C C
  325. C LWA = 75
  326. C NPRINT = 0
  327. C C
  328. C C Set TOL to the square root of the machine precision.
  329. C C Unless high precision solutions are required,
  330. C C this is the recommended setting.
  331. C C
  332. C TOL = SQRT(R1MACH(4))
  333. C C
  334. C CALL DNLS1E(FCN,IOPT,M,N,X,FVEC,TOL,NPRINT,
  335. C * INFO,IW,WA,LWA)
  336. C FNORM = ENORM(M,FVEC)
  337. C WRITE (NWRITE,1000) FNORM,INFO,(X(J),J=1,N)
  338. C STOP
  339. C 1000 FORMAT (5X,' FINAL L2 NORM OF THE RESIDUALS',E15.7 //
  340. C * 5X,' EXIT
  341. C * 5X,' FINAL APPROXIMATE SOLUTION' // 5X,3E15.7)
  342. C END
  343. C SUBROUTINE FCN(IFLAG,M,N,X,FVEC,DUM,IDUM)
  344. C C This is the form of the FCN routine if IOPT=1,
  345. C C that is, if the user does not calculate the Jacobian.
  346. C INTEGER I,M,N,IFLAG
  347. C DOUBLE PRECISION X(N),FVEC(M),Y(15)
  348. C DOUBLE PRECISION TMP1,TMP2,TMP3,TMP4
  349. C DATA Y(1),Y(2),Y(3),Y(4),Y(5),Y(6),Y(7),Y(8),
  350. C * Y(9),Y(10),Y(11),Y(12),Y(13),Y(14),Y(15)
  351. C * /1.4E-1,1.8E-1,2.2E-1,2.5E-1,2.9E-1,3.2E-1,3.5E-1,3.9E-1,
  352. C * 3.7E-1,5.8E-1,7.3E-1,9.6E-1,1.34E0,2.1E0,4.39E0/
  353. C C
  354. C IF (IFLAG .NE. 0) GO TO 5
  355. C C
  356. C C Insert print statements here when NPRINT is positive.
  357. C C
  358. C RETURN
  359. C 5 CONTINUE
  360. C DO 10 I = 1, M
  361. C TMP1 = I
  362. C TMP2 = 16 - I
  363. C TMP3 = TMP1
  364. C IF (I .GT. 8) TMP3 = TMP2
  365. C FVEC(I) = Y(I) - (X(1) + TMP1/(X(2)*TMP2 + X(3)*TMP3))
  366. C 10 CONTINUE
  367. C RETURN
  368. C END
  369. C
  370. C
  371. C Results obtained with different compilers or machines
  372. C may be slightly different.
  373. C
  374. C FINAL L2 NORM OF THE RESIDUALS 0.9063596E-01
  375. C
  376. C EXIT PARAMETER 1
  377. C
  378. C FINAL APPROXIMATE SOLUTION
  379. C
  380. C 0.8241058E-01 0.1133037E+01 0.2343695E+01
  381. C
  382. C
  383. C For IOPT=2, FCN would be modified as follows to also
  384. C calculate the full Jacobian when IFLAG=2.
  385. C
  386. C SUBROUTINE FCN(IFLAG,M,N,X,FVEC,FJAC,LDFJAC)
  387. C C
  388. C C This is the form of the FCN routine if IOPT=2,
  389. C C that is, if the user calculates the full Jacobian.
  390. C C
  391. C INTEGER I,LDFJAC,M,N,IFLAG
  392. C DOUBLE PRECISION X(N),FVEC(M),FJAC(LDFJAC,N),Y(15)
  393. C DOUBLE PRECISION TMP1,TMP2,TMP3,TMP4
  394. C DATA Y(1),Y(2),Y(3),Y(4),Y(5),Y(6),Y(7),Y(8),
  395. C * Y(9),Y(10),Y(11),Y(12),Y(13),Y(14),Y(15)
  396. C * /1.4E-1,1.8E-1,2.2E-1,2.5E-1,2.9E-1,3.2E-1,3.5E-1,3.9E-1,
  397. C * 3.7E-1,5.8E-1,7.3E-1,9.6E-1,1.34E0,2.1E0,4.39E0/
  398. C C
  399. C IF (IFLAG .NE. 0) GO TO 5
  400. C C
  401. C C Insert print statements here when NPRINT is positive.
  402. C C
  403. C RETURN
  404. C 5 CONTINUE
  405. C IF(IFLAG.NE.1) GO TO 20
  406. C DO 10 I = 1, M
  407. C TMP1 = I
  408. C TMP2 = 16 - I
  409. C TMP3 = TMP1
  410. C IF (I .GT. 8) TMP3 = TMP2
  411. C FVEC(I) = Y(I) - (X(1) + TMP1/(X(2)*TMP2 + X(3)*TMP3))
  412. C 10 CONTINUE
  413. C RETURN
  414. C C
  415. C C Below, calculate the full Jacobian.
  416. C C
  417. C 20 CONTINUE
  418. C C
  419. C DO 30 I = 1, M
  420. C TMP1 = I
  421. C TMP2 = 16 - I
  422. C TMP3 = TMP1
  423. C IF (I .GT. 8) TMP3 = TMP2
  424. C TMP4 = (X(2)*TMP2 + X(3)*TMP3)**2
  425. C FJAC(I,1) = -1.E0
  426. C FJAC(I,2) = TMP1*TMP2/TMP4
  427. C FJAC(I,3) = TMP1*TMP3/TMP4
  428. C 30 CONTINUE
  429. C RETURN
  430. C END
  431. C
  432. C
  433. C For IOPT = 3, FJAC would be dimensioned as FJAC(3,3),
  434. C LDFJAC would be set to 3, and FCN would be written as
  435. C follows to calculate a row of the Jacobian when IFLAG=3.
  436. C
  437. C SUBROUTINE FCN(IFLAG,M,N,X,FVEC,FJAC,LDFJAC)
  438. C C This is the form of the FCN routine if IOPT=3,
  439. C C that is, if the user calculates the Jacobian row by row.
  440. C INTEGER I,M,N,IFLAG
  441. C DOUBLE PRECISION X(N),FVEC(M),FJAC(N),Y(15)
  442. C DOUBLE PRECISION TMP1,TMP2,TMP3,TMP4
  443. C DATA Y(1),Y(2),Y(3),Y(4),Y(5),Y(6),Y(7),Y(8),
  444. C * Y(9),Y(10),Y(11),Y(12),Y(13),Y(14),Y(15)
  445. C * /1.4E-1,1.8E-1,2.2E-1,2.5E-1,2.9E-1,3.2E-1,3.5E-1,3.9E-1,
  446. C * 3.7E-1,5.8E-1,7.3E-1,9.6E-1,1.34E0,2.1E0,4.39E0/
  447. C C
  448. C IF (IFLAG .NE. 0) GO TO 5
  449. C C
  450. C C Insert print statements here when NPRINT is positive.
  451. C C
  452. C RETURN
  453. C 5 CONTINUE
  454. C IF( IFLAG.NE.1) GO TO 20
  455. C DO 10 I = 1, M
  456. C TMP1 = I
  457. C TMP2 = 16 - I
  458. C TMP3 = TMP1
  459. C IF (I .GT. 8) TMP3 = TMP2
  460. C FVEC(I) = Y(I) - (X(1) + TMP1/(X(2)*TMP2 + X(3)*TMP3))
  461. C 10 CONTINUE
  462. C RETURN
  463. C C
  464. C C Below, calculate the LDFJAC-th row of the Jacobian.
  465. C C
  466. C 20 CONTINUE
  467. C
  468. C I = LDFJAC
  469. C TMP1 = I
  470. C TMP2 = 16 - I
  471. C TMP3 = TMP1
  472. C IF (I .GT. 8) TMP3 = TMP2
  473. C TMP4 = (X(2)*TMP2 + X(3)*TMP3)**2
  474. C FJAC(1) = -1.E0
  475. C FJAC(2) = TMP1*TMP2/TMP4
  476. C FJAC(3) = TMP1*TMP3/TMP4
  477. C RETURN
  478. C END
  479. C
  480. C***REFERENCES Jorge J. More, The Levenberg-Marquardt algorithm:
  481. C implementation and theory. In Numerical Analysis
  482. C Proceedings (Dundee, June 28 - July 1, 1977, G. A.
  483. C Watson, Editor), Lecture Notes in Mathematics 630,
  484. C Springer-Verlag, 1978.
  485. C***ROUTINES CALLED DNLS1, XERMSG
  486. C***REVISION HISTORY (YYMMDD)
  487. C 800301 DATE WRITTEN
  488. C 890831 Modified array declarations. (WRB)
  489. C 891006 Cosmetic changes to prologue. (WRB)
  490. C 891006 REVISION DATE from Version 3.2
  491. C 891214 Prologue converted to Version 4.0 format. (BAB)
  492. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  493. C 920501 Reformatted the REFERENCES section. (WRB)
  494. C***END PROLOGUE DNLS1E
  495. IMPLICIT DOUBLE PRECISION (A-H,O-Z)
  496. INTEGER M,N,NPRINT,INFO,LWA,IOPT
  497. INTEGER INDEX,IW(*)
  498. DOUBLE PRECISION TOL
  499. DOUBLE PRECISION X(*),FVEC(*),WA(*)
  500. EXTERNAL FCN
  501. INTEGER MAXFEV,MODE,NFEV,NJEV
  502. DOUBLE PRECISION FACTOR,FTOL,GTOL,XTOL,ZERO,EPSFCN
  503. SAVE FACTOR, ZERO
  504. DATA FACTOR,ZERO /1.0D2,0.0D0/
  505. C***FIRST EXECUTABLE STATEMENT DNLS1E
  506. INFO = 0
  507. C
  508. C CHECK THE INPUT PARAMETERS FOR ERRORS.
  509. C
  510. IF (IOPT .LT. 1 .OR. IOPT .GT. 3 .OR.
  511. 1 N .LE. 0 .OR. M .LT. N .OR. TOL .LT. ZERO
  512. 2 .OR. LWA .LT. N*(N+5) + M) GO TO 10
  513. IF (IOPT .LT. 3 .AND. LWA .LT. N*(M+5) + M) GO TO 10
  514. C
  515. C CALL DNLS1.
  516. C
  517. MAXFEV = 100*(N + 1)
  518. IF (IOPT .EQ. 1) MAXFEV = 2*MAXFEV
  519. FTOL = TOL
  520. XTOL = TOL
  521. GTOL = ZERO
  522. EPSFCN = ZERO
  523. MODE = 1
  524. INDEX = 5*N+M
  525. CALL DNLS1(FCN,IOPT,M,N,X,FVEC,WA(INDEX+1),M,FTOL,XTOL,GTOL,
  526. 1 MAXFEV,EPSFCN,WA(1),MODE,FACTOR,NPRINT,INFO,NFEV,NJEV,
  527. 2 IW,WA(N+1),WA(2*N+1),WA(3*N+1),WA(4*N+1),WA(5*N+1))
  528. IF (INFO .EQ. 8) INFO = 4
  529. 10 CONTINUE
  530. IF (INFO .EQ. 0) CALL XERMSG ('SLATEC', 'DNLS1E',
  531. + 'INVALID INPUT PARAMETER.', 2, 1)
  532. RETURN
  533. C
  534. C LAST CARD OF SUBROUTINE DNLS1E.
  535. C
  536. END