Skip to content
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.

Commit 62e156c

Browse files
committedFeb 5, 2022
Allow passing of user data for callback procedure
1 parent 8479bd3 commit 62e156c

File tree

6 files changed

+81
-57
lines changed

6 files changed

+81
-57
lines changed
 

‎src/minpack.f90

+70-51
Large diffs are not rendered by default.

‎test/test_hybrd.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -87,11 +87,12 @@ program test
8787
end do
8888
end program test
8989

90-
subroutine fcn(n,x,Fvec,Iflag)
90+
subroutine fcn(n,x,Fvec,Iflag,udata)
9191
implicit none
9292

9393
integer n , Iflag
9494
double precision x(n) , Fvec(n)
95+
class(*), optional :: udata
9596
! **********
9697
!
9798
! THE CALLING SEQUENCE OF FCN SHOULD BE IDENTICAL TO THE

‎test/test_hybrj.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -93,11 +93,12 @@ program test
9393
end do
9494
end program test
9595

96-
subroutine fcn(n,x,Fvec,Fjac,Ldfjac,Iflag)
96+
subroutine fcn(n,x,Fvec,Fjac,Ldfjac,Iflag,udata)
9797
implicit none
9898

9999
integer n , Ldfjac , Iflag
100100
double precision x(n) , Fvec(n) , Fjac(Ldfjac,n)
101+
class(*), optional :: udata
101102
! **********
102103
!
103104
! THE CALLING SEQUENCE OF FCN SHOULD BE IDENTICAL TO THE

‎test/test_lmder.f90

+3-2
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ program test
9494
! FUNCTION AND JACOBIAN SUBROUTINES SSQFCN AND SSQJAC WITH
9595
! THE APPROPRIATE VALUE OF PROBLEM NUMBER (NPROB).
9696

97-
subroutine fcn(m, n, x, Fvec, Fjac, Ldfjac, Iflag)
97+
subroutine fcn(m, n, x, Fvec, Fjac, Ldfjac, Iflag, udata)
9898

9999
implicit none
100100

@@ -112,6 +112,7 @@ subroutine fcn(m, n, x, Fvec, Fjac, Ldfjac, Iflag)
112112
real(wp), intent(in) :: x(n) !! independant variable vector
113113
real(wp), intent(inout) :: fvec(m) !! value of function at `x`
114114
real(wp), intent(inout) :: fjac(ldfjac, n) !! jacobian matrix at `x`
115+
class(*), intent(inout), optional :: udata
115116

116117
select case (iflag)
117118
case (1)
@@ -994,4 +995,4 @@ end subroutine ssqfcn
994995

995996
!*****************************************************************************************
996997
end program test
997-
!*****************************************************************************************
998+
!*****************************************************************************************

‎test/test_lmdif.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -96,11 +96,12 @@ program test
9696
end do
9797
end program test
9898

99-
subroutine fcn(m,n,x,Fvec,Iflag)
99+
subroutine fcn(m,n,x,Fvec,Iflag,udata)
100100
implicit none
101101

102102
integer m , n , Iflag
103103
double precision x(n) , Fvec(m)
104+
class(*), optional :: udata
104105
! **********
105106
!
106107
! THE CALLING SEQUENCE OF FCN SHOULD BE IDENTICAL TO THE

‎test/test_lmstr.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -103,11 +103,12 @@ program test
103103
end program test
104104

105105

106-
subroutine fcn(m,n,x,Fvec,Fjrow,Iflag)
106+
subroutine fcn(m,n,x,Fvec,Fjrow,Iflag,udata)
107107
implicit none
108108

109109
integer m , n , Iflag
110110
double precision x(n) , Fvec(m) , Fjrow(n)
111+
class(*), optional :: udata
111112
! **********
112113
!
113114
! THE CALLING SEQUENCE OF FCN SHOULD BE IDENTICAL TO THE

0 commit comments

Comments
 (0)
Please sign in to comment.