Skip to content

Commit ecb91cd

Browse files
committed
test: in lmder test, only consider the ones where original minpack passed
minor formatting mods
1 parent 737890e commit ecb91cd

File tree

4 files changed

+17
-12
lines changed

4 files changed

+17
-12
lines changed

test/test_hybrd.f90

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
21
!*****************************************************************************************
32
!>
43
! This program tests codes for the solution of n nonlinear
@@ -11,7 +10,7 @@
1110
! sequences used by the function subroutines in the various
1211
! nonlinear equation solvers.
1312

14-
program test
13+
program test_hybrd
1514

1615
use minpack_module
1716
use iso_fortran_env, only: output_unit
@@ -663,5 +662,5 @@ end subroutine initpt
663662
!*****************************************************************************************
664663

665664
!*****************************************************************************************
666-
end program test
665+
end program test_hybrd
667666
!*****************************************************************************************

test/test_lmder.f90

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@
1010
! Forms of calling sequences used by the function and jacobian
1111
! Subroutines in the various nonlinear least-squares solvers.
1212

13-
program test
13+
program test_lmder
1414

1515
use minpack_module
1616
use iso_fortran_env, only: output_unit
@@ -24,7 +24,11 @@ program test
2424
integer,dimension(ncases),parameter :: ms = [10,50,10,50,10,50,2,3,4,2,15,11,16,31,31,31,10,10,20,8,8,9,10,10,30,40,33,65]
2525
integer,dimension(ncases),parameter :: ntriess = [1,1,1,1,1,1,3,3,3,3,3,3,2,3,3,3,1,1,3,3,1,1,1,3,1,1,1,1]
2626

27-
integer :: i, ic, info, k, ldfjac, lwa, m, n, NFEv, NJEv, NPRob, ntries, icase
27+
integer,dimension(*),parameter :: info_original = [3,3,1,1,1,1,4,2,2,2,2,2,4,4,4,1,1,1,1,1,1,&
28+
1,1,5,2,5,1,1,1,3,1,3,3,3,2,2,1,1,1,1,4,1,&
29+
1,1,2,1,2,2,2,2,2,1,1] !! original `info` from the original minpack
30+
31+
integer :: i, ic, info, k, ldfjac, lwa, m, n, NFEv, NJEv, NPRob, ntries, icase, iunit
2832
real(wp) :: factor, fnorm1, fnorm2
2933
integer :: ma(60), na(60), nf(60), nj(60), np(60), nx(60)
3034
real(wp) :: fnm(60)
@@ -93,7 +97,8 @@ program test
9397
factor = ten*factor
9498

9599
! compare with previously generated solutions:
96-
if (any(abs( solution(ic) - x)>tol .and. &
100+
if ( info_original(ic)<5 .and. & ! ignore any where the original minpack failed
101+
any(abs( solution(ic) - x)>tol .and. &
97102
abs((solution(ic) - x)/(solution(ic))) > solution_reltol)) then
98103
write(nwrite,'(A)') 'Failed case'
99104
write(nwrite, '(//5x, a//(5x, 5d15.7))') 'Expected x: ', solution(ic)
@@ -1162,5 +1167,5 @@ end subroutine ssqfcn
11621167
!*****************************************************************************************
11631168

11641169
!*****************************************************************************************
1165-
end program test
1170+
end program test_lmder
11661171
!*****************************************************************************************

test/test_lmdif.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
21
!*****************************************************************************************
32
!>
43
! This program tests codes for the least-squares solution of
@@ -11,7 +10,8 @@
1110
! forms of calling sequences used by the function and jacobian
1211
! subroutines in the various nonlinear least-squares solvers.
1312

14-
program test
13+
program test_lmdif
14+
1515
use minpack_module
1616
use iso_fortran_env, only: nwrite => output_unit
1717

@@ -721,5 +721,5 @@ end subroutine initpt
721721
!*****************************************************************************************
722722

723723
!*****************************************************************************************
724-
end program test
724+
end program test_lmdif
725725
!*****************************************************************************************

test/test_lmstr.f90

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,8 @@
1010
! forms of calling sequences used by the function and jacobian
1111
! subroutines in the various nonlinear least-squares solvers.
1212

13-
program test
13+
program test_lmstr
14+
1415
use minpack_module
1516
use iso_fortran_env, only: nwrite => output_unit
1617

@@ -1029,5 +1030,5 @@ end subroutine ssqfcn
10291030
!*****************************************************************************************
10301031

10311032
!*****************************************************************************************
1032-
end program test
1033+
end program test_lmstr
10331034
!*****************************************************************************************

0 commit comments

Comments
 (0)