@@ -27,7 +27,7 @@ subroutine func(n, x, fvec, iflag)
27
27
import :: wp
28
28
implicit none
29
29
integer , intent (in ) :: n ! ! the number of variables.
30
- real (wp), intent (in ) :: x(n) ! ! independant variable vector
30
+ real (wp), intent (in ) :: x(n) ! ! independent variable vector
31
31
real (wp), intent (out ) :: fvec(n) ! ! value of function at `x`
32
32
integer , intent (inout ) :: iflag ! ! set to <0 to terminate execution
33
33
end subroutine func
@@ -38,7 +38,7 @@ subroutine func2(m, n, x, fvec, iflag)
38
38
implicit none
39
39
integer , intent (in ) :: m ! ! the number of functions.
40
40
integer , intent (in ) :: n ! ! the number of variables.
41
- real (wp), intent (in ) :: x(n) ! ! independant variable vector
41
+ real (wp), intent (in ) :: x(n) ! ! independent variable vector
42
42
real (wp), intent (out ) :: fvec(m) ! ! value of function at `x`
43
43
integer , intent (inout ) :: iflag ! ! the value of iflag should not be changed unless
44
44
! ! the user wants to terminate execution of lmdif.
@@ -49,19 +49,19 @@ subroutine fcn_hybrj(n, x, fvec, fjac, ldfjac, iflag)
49
49
! ! user-supplied subroutine for [[hybrj]] and [[hybrj1]]
50
50
import :: wp
51
51
implicit none
52
- integer , intent (in ) :: n ! ! the number of variables.
53
- real (wp), dimension (n), intent (in ) :: x ! ! independant variable vector
54
- integer , intent (in ) :: ldfjac ! ! leading dimension of the array fjac.
55
- real (wp), dimension (n), intent (out ) :: fvec ! ! value of function at `x`
56
- real (wp), dimension (ldfjac, n), intent (out ) :: fjac ! ! jacobian matrix at `x`
57
- integer , intent (inout ) :: iflag ! ! if iflag = 1 calculate the functions at x and
58
- ! ! return this vector in fvec. do not alter fjac.
59
- ! ! if iflag = 2 calculate the jacobian at x and
60
- ! ! return this matrix in fjac. do not alter fvec.
61
- ! !
62
- ! ! the value of iflag should not be changed by fcn unless
63
- ! ! the user wants to terminate execution of hybrj.
64
- ! ! in this case set iflag to a negative integer.
52
+ integer , intent (in ) :: n ! ! the number of variables.
53
+ real (wp), dimension (n), intent (in ) :: x ! ! independent variable vector
54
+ integer , intent (in ) :: ldfjac ! ! leading dimension of the array fjac.
55
+ real (wp), dimension (n), intent (inout ) :: fvec ! ! value of function at `x`
56
+ real (wp), dimension (ldfjac, n), intent (inout ) :: fjac ! ! jacobian matrix at `x`
57
+ integer , intent (inout ) :: iflag ! ! if iflag = 1 calculate the functions at x and
58
+ ! ! return this vector in fvec. do not alter fjac.
59
+ ! ! if iflag = 2 calculate the jacobian at x and
60
+ ! ! return this matrix in fjac. do not alter fvec.
61
+ ! !
62
+ ! ! the value of iflag should not be changed by fcn unless
63
+ ! ! the user wants to terminate execution of hybrj.
64
+ ! ! in this case set iflag to a negative integer.
65
65
end subroutine fcn_hybrj
66
66
67
67
subroutine fcn_lmder (m , n , x , fvec , fjac , ldfjac , iflag )
@@ -79,7 +79,7 @@ subroutine fcn_lmder(m, n, x, fvec, fjac, ldfjac, iflag)
79
79
! ! the value of iflag should not be changed by fcn unless
80
80
! ! the user wants to terminate execution of lmder.
81
81
! ! in this case set iflag to a negative integer.
82
- real (wp), intent (in ) :: x(n) ! ! independant variable vector
82
+ real (wp), intent (in ) :: x(n) ! ! independent variable vector
83
83
real (wp), intent (inout ) :: fvec(m) ! ! value of function at `x`
84
84
real (wp), intent (inout ) :: fjac(ldfjac, n) ! ! jacobian matrix at `x`
85
85
end subroutine fcn_lmder
@@ -703,7 +703,7 @@ subroutine hybrd(fcn, n, x, Fvec, Xtol, Maxfev, Ml, Mu, Epsfcn, Diag, Mode, &
703
703
! determine the number of calls to fcn needed to compute
704
704
! the jacobian matrix.
705
705
706
- msum = min0 (Ml + Mu + 1 , n)
706
+ msum = min (Ml + Mu + 1 , n)
707
707
708
708
! initialize iteration counter and monitors.
709
709
@@ -3125,7 +3125,7 @@ subroutine qform(m, n, q, Ldq, Wa)
3125
3125
3126
3126
! zero out upper triangle of q in the first min(m,n) columns.
3127
3127
3128
- minmn = min0 (m, n)
3128
+ minmn = min (m, n)
3129
3129
if (minmn >= 2 ) then
3130
3130
do j = 2 , minmn
3131
3131
jm1 = j - 1
@@ -3240,7 +3240,7 @@ subroutine qrfac(m, n, a, Lda, Pivot, Ipvt, Lipvt, Rdiag, Acnorm, Wa)
3240
3240
3241
3241
! reduce a to r with householder transformations.
3242
3242
3243
- minmn = min0 (m, n)
3243
+ minmn = min (m, n)
3244
3244
do j = 1 , minmn
3245
3245
if (Pivot) then
3246
3246
@@ -3515,10 +3515,13 @@ subroutine r1mpyq(m, n, a, Lda, v, w)
3515
3515
if (nm1 >= 1 ) then
3516
3516
do nmj = 1 , nm1
3517
3517
j = n - nmj
3518
- if (abs (v(j)) > one) cos = one/ v(j)
3519
- if (abs (v(j)) > one) sin = sqrt (one - cos** 2 )
3520
- if (abs (v(j)) <= one) sin = v(j)
3521
- if (abs (v(j)) <= one) cos = sqrt (one - sin** 2 )
3518
+ if (abs (v(j)) > one) then
3519
+ cos = one/ v(j)
3520
+ sin = sqrt (one - cos** 2 )
3521
+ else
3522
+ sin = v(j)
3523
+ cos = sqrt (one - sin** 2 )
3524
+ end if
3522
3525
do i = 1 , m
3523
3526
temp = cos* a(i, j) - sin* a(i, n)
3524
3527
a(i, n) = sin* a(i, j) + cos* a(i, n)
0 commit comments