Skip to content

Commit f3324e6

Browse files
committed
readme updates
minor refactoring
1 parent 4bcb75c commit f3324e6

File tree

3 files changed

+11
-11
lines changed

3 files changed

+11
-11
lines changed

README.md

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,4 +33,6 @@ The Minpack source code and related files and documentation are distributed unde
3333
### References
3434
* Original sourcecode from: [Netlib](https://www.netlib.org/minpack/)
3535
* J. J. Moré, B. S. Garbow, and K. E. Hillstrom, [User Guide for MINPACK-1](http://cds.cern.ch/record/126569/files/CM-P00068642.pdf), Argonne National Laboratory Report ANL-80-74, Argonne, Ill., 1980.
36-
* J. J. Moré, D. C. Sorensen, K. E. Hillstrom, and B. S. Garbow, The MINPACK Project, in Sources and Development of Mathematical Software, W. J. Cowell, ed., Prentice-Hall, pages 88-111, 1984.
36+
* J. J. Moré, D. C. Sorensen, K. E. Hillstrom, and B. S. Garbow, The MINPACK Project, in Sources and Development of Mathematical Software, W. J. Cowell, ed., Prentice-Hall, pages 88-111, 1984.
37+
* M. J. D. Powell, A Hybrid Method for Nonlinear Equations. Numerical Methods for Nonlinear Algebraic Equations, P. Rabinowitz, editor. Gordon and Breach, 1970.
38+
* Jorge J. More, The Levenberg-Marquardt Algorithm, Implementation and Theory. Numerical Analysis, G. A. Watson, editor. Lecture Notes in Mathematics 630, Springer-Verlag, 1977.

test/test_lmder.f90

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,6 @@
1-
21
program test
32
use minpack_module
43
implicit none
5-
64
! **********
75
!
86
! THIS PROGRAM TESTS CODES FOR THE LEAST-SQUARES SOLUTION OF
@@ -34,7 +32,7 @@ program test
3432
double precision factor , fnorm1 , fnorm2 , one , ten , tol
3533
double precision fjac(65,40) , fnm(60) , fvec(65) , wa(265) , &
3634
& x(40)
37-
external fcn
35+
external fcn
3836
common /refnum/ NPRob , NFEv , NJEv
3937
!
4038
! LOGICAL INPUT UNIT IS ASSUMED TO BE NUMBER 5.

test/test_lmstr.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ program test
4545
data nread , nwrite/5 , 6/
4646
!
4747
data one , ten/1.0d0 , 1.0d1/
48-
tol = dsqrt(dpmpar(1))
48+
tol = sqrt(dpmpar(1))
4949
ldfjac = 40
5050
lwa = 265
5151
ic = 0
@@ -249,7 +249,7 @@ subroutine ssqjac(m,n,x,Fjac,Ldfjac,Nprob)
249249
tpi = eight*datan(one)
250250
temp = x(1)**2 + x(2)**2
251251
tmp1 = tpi*temp
252-
tmp2 = dsqrt(temp)
252+
tmp2 = sqrt(temp)
253253
Fjac(1,1) = c100*x(2)/tmp1
254254
Fjac(1,2) = -c100*x(1)/tmp1
255255
Fjac(1,3) = ten
@@ -270,11 +270,11 @@ subroutine ssqjac(m,n,x,Fjac,Ldfjac,Nprob)
270270
enddo
271271
Fjac(1,1) = one
272272
Fjac(1,2) = ten
273-
Fjac(2,3) = dsqrt(five)
273+
Fjac(2,3) = sqrt(five)
274274
Fjac(2,4) = -Fjac(2,3)
275275
Fjac(3,2) = two*(x(2)-two*x(3))
276276
Fjac(3,3) = -two*Fjac(3,2)
277-
Fjac(4,1) = two*dsqrt(ten)*(x(1)-x(4))
277+
Fjac(4,1) = two*sqrt(ten)*(x(1)-x(4))
278278
Fjac(4,4) = -Fjac(4,1)
279279
case (7)
280280
!
@@ -834,7 +834,7 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
834834
tmp1 = dsign(zp25,x(2))
835835
if ( x(1)>zero ) tmp1 = datan(x(2)/x(1))/tpi
836836
if ( x(1)<zero ) tmp1 = datan(x(2)/x(1))/tpi + zp5
837-
tmp2 = dsqrt(x(1)**2+x(2)**2)
837+
tmp2 = sqrt(x(1)**2+x(2)**2)
838838
Fvec(1) = ten*(x(3)-ten*tmp1)
839839
Fvec(2) = ten*(tmp2-one)
840840
Fvec(3) = x(3)
@@ -843,9 +843,9 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
843843
! POWELL SINGULAR FUNCTION.
844844
!
845845
Fvec(1) = x(1) + ten*x(2)
846-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
846+
Fvec(2) = sqrt(five)*(x(3)-x(4))
847847
Fvec(3) = (x(2)-two*x(3))**2
848-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
848+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
849849
case (7)
850850
!
851851
! FREUDENSTEIN AND ROTH FUNCTION.

0 commit comments

Comments
 (0)