Skip to content

Commit d2466b0

Browse files
committed
refactoring and docstrings
1 parent 7a414a3 commit d2466b0

File tree

7 files changed

+1746
-2565
lines changed

7 files changed

+1746
-2565
lines changed

src/minpack.f90

Lines changed: 1699 additions & 2535 deletions
Large diffs are not rendered by default.

src/minpack_kinds.f90

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
!*****************************************************************************************
2+
!>
3+
! Kinds for Minpack
4+
5+
module minpack_kinds
6+
7+
use iso_fortran_env, only: real64
8+
9+
implicit none
10+
11+
private
12+
13+
integer,parameter,public :: wp = real64
14+
15+
!*****************************************************************************************
16+
end module minpack_kinds
17+
!*****************************************************************************************

test/file15.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ program test
4141
data nread , nwrite/5 , 6/
4242
!
4343
data one , ten/1.0d0 , 1.0d1/
44-
tol = dsqrt(dpmpar(1))
44+
tol = sqrt(dpmpar(1))
4545
lwa = 2660
4646
ic = 0
4747
n = 5
@@ -177,9 +177,9 @@ subroutine vecfcn(n,x,Fvec,Nprob)
177177
! POWELL SINGULAR FUNCTION.
178178
!
179179
Fvec(1) = x(1) + ten*x(2)
180-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
180+
Fvec(2) = sqrt(five)*(x(3)-x(4))
181181
Fvec(3) = (x(2)-two*x(3))**2
182-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
182+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
183183
case (3)
184184
!
185185
! POWELL BADLY SCALED FUNCTION.
@@ -204,7 +204,7 @@ subroutine vecfcn(n,x,Fvec,Nprob)
204204
temp1 = dsign(c7,x(2))
205205
if ( x(1)>zero ) temp1 = datan(x(2)/x(1))/tpi
206206
if ( x(1)<zero ) temp1 = datan(x(2)/x(1))/tpi + c8
207-
temp2 = dsqrt(x(1)**2+x(2)**2)
207+
temp2 = sqrt(x(1)**2+x(2)**2)
208208
Fvec(1) = ten*(x(3)-ten*temp1)
209209
Fvec(2) = ten*(temp2-one)
210210
Fvec(3) = x(3)

test/file16.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ program test
4242
data nread , nwrite/5 , 6/
4343
!
4444
data one , ten/1.0d0 , 1.0d1/
45-
tol = dsqrt(dpmpar(1))
45+
tol = sqrt(dpmpar(1))
4646
ldfjac = 40
4747
lwa = 1060
4848
ic = 0
@@ -195,11 +195,11 @@ subroutine vecjac(n,x,Fjac,Ldfjac,Nprob)
195195
enddo
196196
Fjac(1,1) = one
197197
Fjac(1,2) = ten
198-
Fjac(2,3) = dsqrt(five)
198+
Fjac(2,3) = sqrt(five)
199199
Fjac(2,4) = -Fjac(2,3)
200200
Fjac(3,2) = two*(x(2)-two*x(3))
201201
Fjac(3,3) = -two*Fjac(3,2)
202-
Fjac(4,1) = two*dsqrt(ten)*(x(1)-x(4))
202+
Fjac(4,1) = two*sqrt(ten)*(x(1)-x(4))
203203
Fjac(4,4) = -Fjac(4,1)
204204
case (3)
205205
!
@@ -237,7 +237,7 @@ subroutine vecjac(n,x,Fjac,Ldfjac,Nprob)
237237
tpi = eight*datan(one)
238238
temp = x(1)**2 + x(2)**2
239239
temp1 = tpi*temp
240-
temp2 = dsqrt(temp)
240+
temp2 = sqrt(temp)
241241
Fjac(1,1) = hundrd*x(2)/temp1
242242
Fjac(1,2) = -hundrd*x(1)/temp1
243243
Fjac(1,3) = ten
@@ -361,7 +361,7 @@ subroutine vecjac(n,x,Fjac,Ldfjac,Nprob)
361361
do j = 1 , n
362362
tj = dfloat(j)*h
363363
temp = three*(x(j)+tj+one)**2
364-
Fjac(k,j) = h*dmin1(tj*(one-tk),tk*(one-tj))*temp/two
364+
Fjac(k,j) = h*min(tj*(one-tk),tk*(one-tj))*temp/two
365365
enddo
366366
Fjac(k,k) = Fjac(k,k) + one
367367
enddo
@@ -653,9 +653,9 @@ subroutine vecfcn(n,x,Fvec,Nprob)
653653
! POWELL SINGULAR FUNCTION.
654654
!
655655
Fvec(1) = x(1) + ten*x(2)
656-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
656+
Fvec(2) = sqrt(five)*(x(3)-x(4))
657657
Fvec(3) = (x(2)-two*x(3))**2
658-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
658+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
659659
case (3)
660660
!
661661
! POWELL BADLY SCALED FUNCTION.
@@ -680,7 +680,7 @@ subroutine vecfcn(n,x,Fvec,Nprob)
680680
temp1 = dsign(c7,x(2))
681681
if ( x(1)>zero ) temp1 = datan(x(2)/x(1))/tpi
682682
if ( x(1)<zero ) temp1 = datan(x(2)/x(1))/tpi + c8
683-
temp2 = dsqrt(x(1)**2+x(2)**2)
683+
temp2 = sqrt(x(1)**2+x(2)**2)
684684
Fvec(1) = ten*(x(3)-ten*temp1)
685685
Fvec(2) = ten*(temp2-one)
686686
Fvec(3) = x(3)

test/file17.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ program test
4343
data nread , nwrite/5 , 6/
4444
!
4545
data one , ten/1.0d0 , 1.0d1/
46-
tol = dsqrt(dpmpar(1))
46+
tol = sqrt(dpmpar(1))
4747
ldfjac = 65
4848
lwa = 265
4949
ic = 0
@@ -232,7 +232,7 @@ subroutine ssqjac(m,n,x,Fjac,Ldfjac,Nprob)
232232
tpi = eight*datan(one)
233233
temp = x(1)**2 + x(2)**2
234234
tmp1 = tpi*temp
235-
tmp2 = dsqrt(temp)
235+
tmp2 = sqrt(temp)
236236
Fjac(1,1) = c100*x(2)/tmp1
237237
Fjac(1,2) = -c100*x(1)/tmp1
238238
Fjac(1,3) = ten
@@ -253,11 +253,11 @@ subroutine ssqjac(m,n,x,Fjac,Ldfjac,Nprob)
253253
enddo
254254
Fjac(1,1) = one
255255
Fjac(1,2) = ten
256-
Fjac(2,3) = dsqrt(five)
256+
Fjac(2,3) = sqrt(five)
257257
Fjac(2,4) = -Fjac(2,3)
258258
Fjac(3,2) = two*(x(2)-two*x(3))
259259
Fjac(3,3) = -two*Fjac(3,2)
260-
Fjac(4,1) = two*dsqrt(ten)*(x(1)-x(4))
260+
Fjac(4,1) = two*sqrt(ten)*(x(1)-x(4))
261261
Fjac(4,4) = -Fjac(4,1)
262262
case (7)
263263
!
@@ -817,7 +817,7 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
817817
tmp1 = dsign(zp25,x(2))
818818
if ( x(1)>zero ) tmp1 = datan(x(2)/x(1))/tpi
819819
if ( x(1)<zero ) tmp1 = datan(x(2)/x(1))/tpi + zp5
820-
tmp2 = dsqrt(x(1)**2+x(2)**2)
820+
tmp2 = sqrt(x(1)**2+x(2)**2)
821821
Fvec(1) = ten*(x(3)-ten*tmp1)
822822
Fvec(2) = ten*(tmp2-one)
823823
Fvec(3) = x(3)
@@ -826,9 +826,9 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
826826
! POWELL SINGULAR FUNCTION.
827827
!
828828
Fvec(1) = x(1) + ten*x(2)
829-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
829+
Fvec(2) = sqrt(five)*(x(3)-x(4))
830830
Fvec(3) = (x(2)-two*x(3))**2
831-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
831+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
832832
case (7)
833833
!
834834
! FREUDENSTEIN AND ROTH FUNCTION.

test/file19.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ program test
4242
data nread , nwrite/5 , 6/
4343
!
4444
data one , ten/1.0d0 , 1.0d1/
45-
tol = dsqrt(dpmpar(1))
45+
tol = sqrt(dpmpar(1))
4646
lwa = 2865
4747
ic = 0
4848
n = 40
@@ -281,7 +281,7 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
281281
tmp1 = dsign(zp25,x(2))
282282
if ( x(1)>zero ) tmp1 = datan(x(2)/x(1))/tpi
283283
if ( x(1)<zero ) tmp1 = datan(x(2)/x(1))/tpi + zp5
284-
tmp2 = dsqrt(x(1)**2+x(2)**2)
284+
tmp2 = sqrt(x(1)**2+x(2)**2)
285285
Fvec(1) = ten*(x(3)-ten*tmp1)
286286
Fvec(2) = ten*(tmp2-one)
287287
Fvec(3) = x(3)
@@ -290,9 +290,9 @@ subroutine ssqfcn(m,n,x,Fvec,Nprob)
290290
! POWELL SINGULAR FUNCTION.
291291
!
292292
Fvec(1) = x(1) + ten*x(2)
293-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
293+
Fvec(2) = sqrt(five)*(x(3)-x(4))
294294
Fvec(3) = (x(2)-two*x(3))**2
295-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
295+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
296296
case (7)
297297
!
298298
! FREUDENSTEIN AND ROTH FUNCTION.

test/file20.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -165,11 +165,11 @@ subroutine errjac(n,x,Fjac,Ldfjac,Nprob)
165165
enddo
166166
Fjac(1,1) = one
167167
Fjac(1,2) = ten
168-
Fjac(2,3) = dsqrt(five)
168+
Fjac(2,3) = sqrt(five)
169169
Fjac(2,4) = -Fjac(2,3)
170170
Fjac(3,2) = two*(x(2)-two*x(3))
171171
Fjac(3,3) = two*Fjac(3,2)
172-
Fjac(4,1) = two*dsqrt(ten)*(x(1)-x(4))
172+
Fjac(4,1) = two*sqrt(ten)*(x(1)-x(4))
173173
Fjac(4,4) = -Fjac(4,1)
174174
case (3)
175175
!
@@ -209,7 +209,7 @@ subroutine errjac(n,x,Fjac,Ldfjac,Nprob)
209209
tpi = eight*datan(one)
210210
temp = x(1)**2 + x(2)**2
211211
temp1 = tpi*temp
212-
temp2 = dsqrt(temp)
212+
temp2 = sqrt(temp)
213213
Fjac(1,1) = hundrd*x(2)/temp1
214214
Fjac(1,2) = -hundrd*x(1)/temp1
215215
Fjac(1,3) = ten
@@ -336,7 +336,7 @@ subroutine errjac(n,x,Fjac,Ldfjac,Nprob)
336336
do j = 1 , n
337337
tj = dfloat(j)*h
338338
temp = three*(x(j)+tj+one)**2
339-
Fjac(k,j) = h*dmin1(tj*(one-tk),tk*(one-tj))*temp/two
339+
Fjac(k,j) = h*min(tj*(one-tk),tk*(one-tj))*temp/two
340340
enddo
341341
Fjac(k,k) = Fjac(k,k) - one
342342
enddo
@@ -631,9 +631,9 @@ subroutine vecfcn(n,x,Fvec,Nprob)
631631
! POWELL SINGULAR FUNCTION.
632632
!
633633
Fvec(1) = x(1) + ten*x(2)
634-
Fvec(2) = dsqrt(five)*(x(3)-x(4))
634+
Fvec(2) = sqrt(five)*(x(3)-x(4))
635635
Fvec(3) = (x(2)-two*x(3))**2
636-
Fvec(4) = dsqrt(ten)*(x(1)-x(4))**2
636+
Fvec(4) = sqrt(ten)*(x(1)-x(4))**2
637637
case (3)
638638
!
639639
! POWELL BADLY SCALED FUNCTION.
@@ -658,7 +658,7 @@ subroutine vecfcn(n,x,Fvec,Nprob)
658658
temp1 = dsign(c7,x(2))
659659
if ( x(1)>zero ) temp1 = datan(x(2)/x(1))/tpi
660660
if ( x(1)<zero ) temp1 = datan(x(2)/x(1))/tpi + c8
661-
temp2 = dsqrt(x(1)**2+x(2)**2)
661+
temp2 = sqrt(x(1)**2+x(2)**2)
662662
Fvec(1) = ten*(x(3)-ten*temp1)
663663
Fvec(2) = ten*(temp2-one)
664664
Fvec(3) = x(3)

0 commit comments

Comments
 (0)