@@ -108,6 +108,15 @@ module nlesolver_module
108108 character (len= :),allocatable :: message ! ! latest status message
109109 integer :: istat = - 999 ! ! latest status message
110110
111+ integer :: bounds_mode = 0 ! ! how to handle the `x` variable bounds:
112+ ! !
113+ ! ! * 0 = ignore bounds.
114+ ! ! * 1 = use bounds (if specified) by adjusting the `x` vector
115+ ! ! at each function evaluation so that each individual `x`
116+ ! ! component is within its bounds.
117+ real (wp),dimension (:),allocatable :: xlow ! ! lower bounds for `x` (size is `n`). only used if `bounds_mode>0`.
118+ real (wp),dimension (:),allocatable :: xupp ! ! upper bounds for `x` (size is `n`). only used if `bounds_mode>0`.
119+
111120 procedure (func_func),pointer :: func = > null () ! ! user-supplied routine to compute the function
112121 procedure (export_func),pointer :: export_iteration = > null () ! ! user-supplied routine to export iterations
113122 procedure (wait_func),pointer :: user_input_check = > null () ! ! user-supplied routine to enable user to stop iterations
@@ -167,6 +176,7 @@ module nlesolver_module
167176 procedure ,public :: status = > get_status
168177
169178 procedure :: set_status
179+ procedure :: adjust_x_for_bounds
170180
171181 end type nlesolver_type
172182 ! *********************************************************
@@ -270,27 +280,14 @@ subroutine set_status(me,istat,string,i,r)
270280 integer ,intent (in ),optional :: i ! ! an integer value to append
271281 real (wp),intent (in ),optional :: r ! ! a real value to append
272282
273- character (len= 256 ) :: numstr ! ! for number fo string conversion
274283 character (len= :),allocatable :: message ! ! the full message to log
275284 integer :: iostat ! ! write `iostat` code
276285
277286 message = trim (string)
278- if (present (i)) then
279- numstr = ' '
280- write (numstr,fmt=* ,iostat= iostat) i
281- if (iostat/= 0 ) numstr = ' ****'
282- message = message// ' ' // trim (adjustl (numstr))
283- end if
284- if (present (r)) then
285- numstr = ' '
286- write (numstr,fmt=* ,iostat= iostat) r
287- if (iostat/= 0 ) numstr = ' ****'
288- message = message// ' ' // trim (adjustl (numstr))
289- end if
287+ if (present (i)) message = message// ' ' // int2str(i)
288+ if (present (r)) message = message// ' ' // real2str(r)
290289
291- if (me% verbose) then
292- write (me% iunit,' (A)' ,iostat= iostat) message
293- end if
290+ if (me% verbose) write (me% iunit,' (A)' ,iostat= iostat) message
294291
295292 ! store in the class:
296293 me% istat = istat
@@ -299,6 +296,42 @@ subroutine set_status(me,istat,string,i,r)
299296 end subroutine set_status
300297! *****************************************************************************************
301298
299+ ! *****************************************************************************************
300+ ! >
301+ ! Convert an integer to a string. Works for up to 256 digits.
302+
303+ function int2str (i ) result(s)
304+ integer , intent (in ) :: i ! ! integer to convert
305+ character (len= :),allocatable :: s ! ! string result
306+ character (len= 256 ) :: tmp ! ! temp string
307+ integer :: iostat ! ! write `iostat` code
308+ write (tmp,fmt=* ,iostat= iostat) i
309+ if (iostat/= 0 ) then
310+ s = ' ****'
311+ else
312+ s = trim (adjustl (tmp))
313+ end if
314+ end function int2str
315+ ! *****************************************************************************************
316+
317+ ! *****************************************************************************************
318+ ! >
319+ ! Convert a real to a string. Works for up to 256 digits.
320+
321+ function real2str (r ) result(s)
322+ real (wp), intent (in ) :: r ! ! real to convert
323+ character (len= :),allocatable :: s ! ! string result
324+ character (len= 256 ) :: tmp ! ! temp string
325+ integer :: iostat ! ! write `iostat` code
326+ write (tmp,fmt=* ,iostat= iostat) r
327+ if (iostat/= 0 ) then
328+ s = ' ****'
329+ else
330+ s = trim (adjustl (tmp))
331+ end if
332+ end function real2str
333+ ! *****************************************************************************************
334+
302335! *****************************************************************************************
303336! >
304337! Return the status code and message from the [[nlesolver_type]] class.
@@ -320,6 +353,7 @@ end subroutine set_status
320353! * -13 -- Error: backtracking linesearch tau must be in range (0, 1)
321354! * -14 -- Error: must specify grad_sparse, irow, and icol for sparsity_mode > 1
322355! * -15 -- Error: irow and icol must be the same length
356+ ! * -16 -- Error: xlow > xupp
323357! * -999 -- Error: class has not been initialized
324358! * 0 -- Class successfully initialized in [[nlesolver_type:initialize]]
325359! * 1 -- Required accuracy achieved
@@ -361,7 +395,8 @@ subroutine initialize_nlesolver_variables(me,&
361395 verbose ,iunit ,n_uphill_max ,n_intervals ,&
362396 sparsity_mode ,irow ,icol ,&
363397 atol ,btol ,conlim ,damp ,itnlim ,nout ,&
364- lusol_method ,localSize ,custom_solver_sparse )
398+ lusol_method ,localSize ,custom_solver_sparse ,&
399+ bounds_mode ,xlow ,xupp )
365400
366401 implicit none
367402
@@ -437,6 +472,16 @@ subroutine initialize_nlesolver_variables(me,&
437472 ! ! At most `min(m,n)` vectors will be allocated.
438473 procedure (sparse_solver_func),optional :: custom_solver_sparse ! ! for `sparsity_mode=5`, this is the
439474 ! ! user-provided linear solver.
475+ integer ,intent (in ),optional :: bounds_mode ! ! how to handle the `x` variable bounds:
476+ ! !
477+ ! ! * 0 = ignore bounds
478+ ! ! * 1 = use bounds (if specified) by adjusting the `x` vector
479+ ! ! at each step so that each individual `x` component is within
480+ ! ! the bounds
481+ real (wp),dimension (n),intent (in ),optional :: xlow ! ! lower bounds for `x` (size is `n`). only used if `bounds_mode>0` and
482+ ! ! both `xlow` and `xupp` are specified.
483+ real (wp),dimension (n),intent (in ),optional :: xupp ! ! upper bounds for `x` (size is `n`). only used if `bounds_mode>0` and
484+ ! ! both `xlow` and `xupp` are specified.
440485
441486 logical :: status_ok ! ! true if there were no errors
442487
@@ -453,6 +498,19 @@ subroutine initialize_nlesolver_variables(me,&
453498
454499 ! optional:
455500
501+ if (present (bounds_mode) .and. present (xlow) .and. present (xupp)) then
502+ if (any (xlow> xupp)) then ! check for consistency
503+ status_ok = .false.
504+ call me% set_status(istat = - 16 , string = ' Error: xlow > xupp' )
505+ return
506+ end if
507+ me% bounds_mode = bounds_mode
508+ me% xupp = xupp
509+ me% xlow = xlow
510+ else
511+ me% bounds_mode = 0 ! default
512+ end if
513+
456514 if (present (step_mode)) then
457515 select case (step_mode)
458516 case (1 ) ! = use the specified `alpha` (0,1]
@@ -672,6 +730,7 @@ subroutine nlesolver_solver(me,x)
672730 end if
673731
674732 ! evaluate the function:
733+ call me% adjust_x_for_bounds(x) ! if the guess is out of bounds it may also be adjusted first.
675734 call me% func(x,fvec)
676735 f = norm2(fvec)
677736
@@ -923,6 +982,35 @@ subroutine nlesolver_solver(me,x)
923982 end subroutine nlesolver_solver
924983! *****************************************************************************************
925984
985+ ! *****************************************************************************************
986+ ! >
987+ ! if necessary, adjust the `x` vector to be within the bounds.
988+
989+ subroutine adjust_x_for_bounds (me ,x )
990+
991+ implicit none
992+
993+ class(nlesolver_type),intent (inout ) :: me
994+ real (wp),dimension (me% n),intent (inout ) :: x ! ! the `x` vector to adjust
995+
996+ integer :: i ! ! counter
997+
998+ if (me% bounds_mode== 1 ) then
999+ ! x = min(max(x,me%xlow),me%xupp)
1000+ do i = 1 , me% n
1001+ if (x(i)<me% xlow(i)) then
1002+ x(i) = me% xlow(i)
1003+ if (me% verbose) write (me% iunit, ' (A)' ) ' x(' // int2str(i)// ' ) < xlow(i) : adjusting to lower bound'
1004+ else if (x(i)>me% xupp(i)) then
1005+ x(i) = me% xupp(i)
1006+ if (me% verbose) write (me% iunit, ' (A)' ) ' x(' // int2str(i)// ' ) > xupp(i) : adjusting to upper bound'
1007+ end if
1008+ end do
1009+ end if
1010+
1011+ end subroutine adjust_x_for_bounds
1012+ ! *****************************************************************************************
1013+
9261014! *****************************************************************************************
9271015! >
9281016! Destructor
@@ -1042,6 +1130,7 @@ subroutine simple_step(me,xold,p,x,f,fvec,fjac,fjac_sparse)
10421130 real (wp),dimension (:),intent (in ),optional :: fjac_sparse ! ! jacobian matrix [sparse]
10431131
10441132 x = xold + p * me% alpha
1133+ call me% adjust_x_for_bounds(x)
10451134
10461135 ! evaluate the function at the new point:
10471136 call me% func(x,fvec)
@@ -1115,6 +1204,7 @@ subroutine backtracking_linesearch(me,xold,p,x,f,fvec,fjac,fjac_sparse)
11151204 do
11161205
11171206 xtmp = xold + p * alpha
1207+ call me% adjust_x_for_bounds(xtmp)
11181208 call me% func(xtmp,fvectmp)
11191209 ftmp = norm2(fvectmp)
11201210
@@ -1183,6 +1273,7 @@ subroutine exact_linesearch(me,xold,p,x,f,fvec,fjac,fjac_sparse)
11831273 if (me% verbose) write (me% iunit,' (1P,*(A,1X,E16.6))' ) ' alpha_min = ' , alpha_min
11841274
11851275 x = xold + p * alpha_min
1276+ call me% adjust_x_for_bounds(x)
11861277 if (all (x== xnew)) then
11871278 ! already computed in the func
11881279 else
@@ -1198,6 +1289,7 @@ real(wp) function func_for_fmin(alpha)
11981289 real (wp),intent (in ) :: alpha ! ! indep variable
11991290
12001291 xnew = xold + p * alpha
1292+ call me% adjust_x_for_bounds(xnew)
12011293 call me% func(xnew,fvec)
12021294 func_for_fmin = norm2(fvec) ! return result
12031295
@@ -1260,6 +1352,7 @@ subroutine fixed_point_linesearch(me,xold,p,x,f,fvec,fjac,fjac_sparse)
12601352 do i = 1 , n_points
12611353
12621354 x_tmp = xold + p * alphas_to_try(i)
1355+ call me% adjust_x_for_bounds(x_tmp)
12631356
12641357 ! evaluate the function at tthis point:
12651358 call me% func(x_tmp,fvec_tmp)
0 commit comments