mango.F90
Go to the documentation of this file.
1 ! Copyright 2019, University of Maryland and the MANGO development team.
2 !
3 ! This file is part of MANGO.
4 !
5 ! MANGO is free software: you can redistribute it and/or modify it
6 ! under the terms of the GNU Lesser General Public License as
7 ! published by the Free Software Foundation, either version 3 of the
8 ! License, or (at your option) any later version.
9 !
10 ! MANGO is distributed in the hope that it will be useful, but
11 ! WITHOUT ANY WARRANTY; without even the implied warranty of
12 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
13 ! Lesser General Public License for more details.
14 !
15 ! You should have received a copy of the GNU Lesser General Public
16 ! License along with MANGO. If not, see
17 ! <https://www.gnu.org/licenses/>.
18 
19 ! If the module name is "mango", doxygen gets confused and combines the contents with the "mango" C++ namespace.
20 ! Therefore I'll use a longer name for the module name.
21 
22 !> This Fortran module provides the Fortran API for calling MANGO from outside applications.
23 module mango_mod
24 
25 ! The value in the next line must match the corresponding value in mango.F90
26 #define mango_interface_string_length 256
27 
28  ! Modeled after
29  ! https://modelingguru.nasa.gov/docs/DOC-2642
30  ! http://fortranwiki.org/fortran/show/Fortran+and+Cpp+objects
31 
32  use, intrinsic :: iso_c_binding
33  implicit none
34 
35 ! private
36 ! public :: mango_problem, objective_function_interface
37 ! public :: mango_problem_create, mango_problem_create_least_squares, &
38 ! mango_problem_destroy, &
39 ! mango_set_algorithm, mango_set_algorithm_from_string, mango_read_input_file, mango_set_output_filename, &
40 ! mango_mpi_init, mango_mpi_partition_set_custom, mango_optimize, &
41 ! mango_get_mpi_rank_world, mango_get_mpi_rank_worker_groups, mango_get_mpi_rank_group_leaders, &
42 ! mango_get_N_procs_world, mango_get_N_procs_worker_groups, mango_get_N_procs_group_leaders, &
43 ! mango_get_proc0_world, mango_get_proc0_worker_groups, &
44 ! mango_get_mpi_comm_world, mango_get_mpi_comm_worker_groups, mango_get_mpi_comm_group_leaders, &
45 ! mango_get_N_parameters, mango_get_N_terms, &
46 ! mango_get_worker_group, mango_get_best_function_evaluation, &
47 ! mango_get_function_evaluations, mango_set_max_function_evaluations, mango_set_centered_differences, &
48 ! mango_does_algorithm_exist, mango_set_finite_difference_step_size, mango_set_bound_constraints, &
49 ! mango_set_verbose, mango_set_print_residuals_in_output_file, &
50 ! mango_set_user_data, &
51 ! mango_stop_workers, mango_mobilize_workers, mango_continue_worker_loop, mango_mpi_partition_write, &
52 ! mango_set_relative_bound_constraints
53 
54 ! private :: C_mango_problem_create, C_mango_problem_create_least_squares, &
55 ! C_mango_problem_destroy, &
56 ! C_mango_set_algorithm, C_mango_set_algorithm_from_string, C_mango_read_input_file, C_mango_set_output_filename, &
57 ! C_mango_mpi_init, C_mango_mpi_partition_set_custom, C_mango_optimize, &
58 ! C_mango_get_mpi_rank_world, C_mango_get_mpi_rank_worker_groups, C_mango_get_mpi_rank_group_leaders, &
59 ! C_mango_get_N_procs_world, C_mango_get_N_procs_worker_groups, C_mango_get_N_procs_group_leaders, &
60 ! C_mango_get_proc0_world, C_mango_get_proc0_worker_groups, &
61 ! C_mango_get_mpi_comm_world, C_mango_get_mpi_comm_worker_groups, C_mango_get_mpi_comm_group_leaders, &
62 ! C_mango_get_N_parameters, C_mango_get_N_terms, &
63 ! C_mango_get_worker_group, C_mango_get_best_function_evaluation, &
64 ! C_mango_get_function_evaluations, C_mango_set_max_function_evaluations, C_mango_set_centered_differences, &
65 ! C_mango_does_algorithm_exist, C_mango_set_finite_difference_step_size, C_mango_set_bound_constraints, &
66 ! C_mango_set_verbose, C_mango_set_print_residuals_in_output_file, &
67 ! C_mango_set_user_data, &
68 ! C_mango_stop_workers, C_mango_mobilize_workers, C_mango_continue_worker_loop, C_mango_mpi_partition_write, &
69 ! C_mango_set_relative_bound_constraints
70 
71  !> An object that represents an optimization problem.
72  type, bind(C) :: mango_problem
73  type(C_ptr), private :: object = c_null_ptr ! This pointer points to a C++ mango::Problem object.
74  end type mango_problem
75 
76  interface
77 ! function C_mango_problem_create(N_parameters) result(this) bind(C,name="mango_problem_create")
78 ! import
79 ! integer(C_int) :: N_parameters
80 ! type(C_ptr) :: this
81 ! end function C_mango_problem_create
82 ! function C_mango_problem_create_least_squares(N_parameters,N_terms) result(this) bind(C,name="mango_problem_create_least_squares")
83 ! import
84 ! integer(C_int) :: N_parameters, N_terms
85 ! type(C_ptr) :: this
86 ! end function C_mango_problem_create_least_squares
87  function c_mango_problem_create(N_parameters, state_vector, objective_function) result(this) bind(C,name="mango_problem_create")
88  import
89  integer(C_int) :: n_parameters
90  type(c_ptr) :: this
91  !real(C_double) :: state_vector(:)
92  !real(C_double) :: state_vector(N_parameters)
93  real(c_double) :: state_vector
94  type(c_funptr), value :: objective_function ! The "value" attribute is critical; otherwise a pointer to the pointer is passed instead of the pointer.
95  end function c_mango_problem_create
96  function c_mango_problem_create_least_squares(N_parameters, state_vector, N_terms, targets, sigmas, best_residual_function, residual_function) result(this) bind(C,name="mango_problem_create_least_squares")
97  import
98  integer(C_int) :: n_parameters, n_terms
99  type(c_ptr) :: this
100  real(c_double) :: state_vector, targets, sigmas, best_residual_function
101  type(c_funptr), value :: residual_function ! The "value" attribute is critical; otherwise a pointer to the pointer is passed instead of the pointer.
102  end function c_mango_problem_create_least_squares
103  subroutine c_mango_problem_destroy (this) bind(C,name="mango_problem_destroy")
104  import
105  type(c_ptr), value :: this
106  end subroutine c_mango_problem_destroy
107  subroutine c_mango_set_algorithm (this, algorithm) bind(C,name="mango_set_algorithm")
108  import
109  integer(C_int) :: algorithm
110  type(c_ptr), value :: this
111  end subroutine c_mango_set_algorithm
112  subroutine c_mango_set_algorithm_from_string (this, algorithm_str) bind(C,name="mango_set_algorithm_from_string")
113  import
114  type(c_ptr), value :: this
115  character(C_char) :: algorithm_str(mango_interface_string_length)
116  end subroutine c_mango_set_algorithm_from_string
117  subroutine c_mango_read_input_file(this, filename) bind(C,name="mango_read_input_file")
118  import
119  type(c_ptr), value :: this
120  character(C_char) :: filename(mango_interface_string_length)
121  end subroutine c_mango_read_input_file
122  subroutine c_mango_set_output_filename(this, filename) bind(C,name="mango_set_output_filename")
123  import
124  type(c_ptr), value :: this
125  character(C_char) :: filename(mango_interface_string_length)
126  end subroutine c_mango_set_output_filename
127  subroutine c_mango_mpi_init (this, mpi_comm) bind(C,name="mango_mpi_init")
128  import
129  integer(C_int) :: mpi_comm
130  type(c_ptr), value :: this
131  end subroutine c_mango_mpi_init
132  subroutine c_mango_mpi_partition_set_custom(this, comm1, comm2, comm3) bind(C,name="mango_mpi_partition_set_custom")
133  import
134  integer(C_int) :: comm1, comm2, comm3
135  type(c_ptr), value :: this
136  end subroutine c_mango_mpi_partition_set_custom
137  subroutine c_mango_set_n_worker_groups(this, N) bind(C,name="mango_set_N_worker_groups")
138  import
139  integer(C_int) :: N
140  type(c_ptr), value :: this
141  end subroutine c_mango_set_n_worker_groups
142  function c_mango_get_n_worker_groups(this) result(N) bind(C,name="mango_get_N_worker_groups")
143  import
144  integer(C_int) :: n
145  type(c_ptr), value :: this
146  end function c_mango_get_n_worker_groups
147  function c_mango_optimize(this) result(optimum) bind(C,name="mango_optimize")
148  import
149  type(c_ptr), value :: this
150  real(c_double) :: optimum
151  end function c_mango_optimize
152  function c_mango_get_mpi_rank_world(this) result(mpi_rank) bind(C,name="mango_get_mpi_rank_world")
153  import
154  integer(C_int) :: mpi_rank
155  type(c_ptr), value :: this
156  end function c_mango_get_mpi_rank_world
157  function c_mango_get_mpi_rank_worker_groups(this) result(mpi_rank) bind(C,name="mango_get_mpi_rank_worker_groups")
158  import
159  integer(C_int) :: mpi_rank
160  type(c_ptr), value :: this
161  end function c_mango_get_mpi_rank_worker_groups
162  function c_mango_get_mpi_rank_group_leaders(this) result(mpi_rank) bind(C,name="mango_get_mpi_rank_group_leaders")
163  import
164  integer(C_int) :: mpi_rank
165  type(c_ptr), value :: this
166  end function c_mango_get_mpi_rank_group_leaders
167  function c_mango_get_n_procs_world(this) result(N_procs) bind(C,name="mango_get_N_procs_world")
168  import
169  integer(C_int) :: n_procs
170  type(c_ptr), value :: this
171  end function c_mango_get_n_procs_world
172  function c_mango_get_n_procs_worker_groups(this) result(N_procs) bind(C,name="mango_get_N_procs_worker_groups")
173  import
174  integer(C_int) :: n_procs
175  type(c_ptr), value :: this
176  end function c_mango_get_n_procs_worker_groups
177  function c_mango_get_n_procs_group_leaders(this) result(N_procs) bind(C,name="mango_get_N_procs_group_leaders")
178  import
179  integer(C_int) :: n_procs
180  type(c_ptr), value :: this
181  end function c_mango_get_n_procs_group_leaders
182  function c_mango_get_proc0_world(this) result(proc0) bind(C,name="mango_get_proc0_world")
183  import
184  integer(C_int) :: proc0
185  type(c_ptr), value :: this
186  end function c_mango_get_proc0_world
187  function c_mango_get_proc0_worker_groups(this) result(proc0) bind(C,name="mango_get_proc0_worker_groups")
188  import
189  integer(C_int) :: proc0
190  type(c_ptr), value :: this
191  end function c_mango_get_proc0_worker_groups
192  function c_mango_get_mpi_comm_world(this) result(comm) bind(C,name="mango_get_mpi_comm_world")
193  import
194  integer(C_int) :: comm
195  type(c_ptr), value :: this
196  end function c_mango_get_mpi_comm_world
197  function c_mango_get_mpi_comm_worker_groups(this) result(comm) bind(C,name="mango_get_mpi_comm_worker_groups")
198  import
199  integer(C_int) :: comm
200  type(c_ptr), value :: this
201  end function c_mango_get_mpi_comm_worker_groups
202  function c_mango_get_mpi_comm_group_leaders(this) result(comm) bind(C,name="mango_get_mpi_comm_group_leaders")
203  import
204  integer(C_int) :: comm
205  type(c_ptr), value :: this
206  end function c_mango_get_mpi_comm_group_leaders
207  function c_mango_get_n_parameters(this) result(N) bind(C,name="mango_get_N_parameters")
208  import
209  integer(C_int) :: n
210  type(c_ptr), value :: this
211  end function c_mango_get_n_parameters
212  function c_mango_get_n_terms(this) result(N) bind(C,name="mango_get_N_terms")
213  import
214  integer(C_int) :: n
215  type(c_ptr), value :: this
216  end function c_mango_get_n_terms
217  function c_mango_get_worker_group(this) result(N) bind(C,name="mango_get_worker_group")
218  import
219  integer(C_int) :: n
220  type(c_ptr), value :: this
221  end function c_mango_get_worker_group
222  function c_mango_get_best_function_evaluation(this) result(N) bind(C,name="mango_get_best_function_evaluation")
223  import
224  integer(C_int) :: n
225  type(c_ptr), value :: this
226  end function c_mango_get_best_function_evaluation
227  function c_mango_get_function_evaluations(this) result(N) bind(C,name="mango_get_function_evaluations")
228  import
229  integer(C_int) :: n
230  type(c_ptr), value :: this
231  end function c_mango_get_function_evaluations
232  subroutine c_mango_set_max_function_evaluations(this, N) bind(C,name="mango_set_max_function_evaluations")
233  import
234  type(c_ptr), value :: this
235  integer(C_int) :: N
236  end subroutine c_mango_set_max_function_evaluations
237  subroutine c_mango_set_centered_differences(this, centered_differences_int) bind(C,name="mango_set_centered_differences")
238  import
239  type(c_ptr), value :: this
240  integer(C_int) :: centered_differences_int
241  end subroutine c_mango_set_centered_differences
242  function c_mango_does_algorithm_exist(algorithm_str) result(temp_int) bind(C,name="mango_does_algorithm_exist")
243  import
244  character(C_char) :: algorithm_str(mango_interface_string_length)
245  integer(C_int) :: temp_int
246  end function c_mango_does_algorithm_exist
247  subroutine c_mango_set_finite_difference_step_size (this, step) bind(C,name="mango_set_finite_difference_step_size")
248  import
249  real(C_double) :: step
250  type(c_ptr), value :: this
251  end subroutine c_mango_set_finite_difference_step_size
252  subroutine c_mango_set_bound_constraints(this, lower_bounds, upper_bounds) bind(C,name="mango_set_bound_constraints")
253  import
254  real(C_double) :: lower_bounds, upper_bounds
255  type(c_ptr), value :: this
256  end subroutine c_mango_set_bound_constraints
257  subroutine c_mango_set_verbose (this, verbose) bind(C,name="mango_set_verbose")
258  import
259  integer(C_int) :: verbose
260  type(c_ptr), value :: this
261  end subroutine c_mango_set_verbose
262  subroutine c_mango_set_print_residuals_in_output_file(this, print_residuals_in_output_file_int) bind(C,name="mango_set_print_residuals_in_output_file")
263  import
264  type(c_ptr), value :: this
265  integer(C_int) :: print_residuals_in_output_file_int
266  end subroutine c_mango_set_print_residuals_in_output_file
267  subroutine c_mango_set_user_data(this, user_data) bind(C,name="mango_set_user_data")
268  import
269  type(c_ptr), value :: this, user_data
270  end subroutine c_mango_set_user_data
271  subroutine c_mango_stop_workers(this) bind(C,name="mango_stop_workers")
272  import
273  type(c_ptr), value :: this
274  end subroutine c_mango_stop_workers
275  subroutine c_mango_mobilize_workers(this) bind(C,name="mango_mobilize_workers")
276  import
277  type(c_ptr), value :: this
278  end subroutine c_mango_mobilize_workers
279  function c_mango_continue_worker_loop(this) result(N) bind(C,name="mango_continue_worker_loop")
280  import
281  integer(C_int) :: n
282  type(c_ptr), value :: this
283  end function c_mango_continue_worker_loop
284  subroutine c_mango_mpi_partition_write(this, filename) bind(C,name="mango_mpi_partition_write")
285  import
286  type(c_ptr), value :: this
287  character(C_char) :: filename(mango_interface_string_length)
288  end subroutine c_mango_mpi_partition_write
289  subroutine c_mango_set_relative_bound_constraints(this, min_factor, max_factor, min_radius, preserve_sign) bind(C,name="mango_set_relative_bound_constraints")
290  import
291  type(c_ptr), value :: this
292  real(C_double) :: min_factor, max_factor, min_radius
293  integer(C_int) :: preserve_sign
294  end subroutine c_mango_set_relative_bound_constraints
295  subroutine c_mango_set_n_line_search (this, N) bind(C,name="mango_set_N_line_search")
296  import
297  integer(C_int) :: N
298  type(c_ptr), value :: this
299  end subroutine c_mango_set_n_line_search
300  end interface
301 
302  abstract interface
303 
304  !> Format for the user-supplied subroutine that computes the objective function for a general (non least-squares) optimization problem
305  !>
306  !> @param N_parameters The number of independent variables, i.e. the dimension of the search space.
307  !> @param state_vector An array of size <span class="paramname">N_parameters</span> containing the values of the indpendent variables.
308  !> @param objective_value The subroutine must set this variable to the value of the objective function.
309  !> @param failed Set the value pointed to by this variable to 1 if the calculation of the objective function fails for some reason.
310  !> Otherwise the value should be 0.
311  !> @param problem A pointer to the class representing this optimization problem. This pointer can be useful for
312  !> getting information about the MPI communicators.
313  !> @param user_data Pointer to user-supplied data, which can be set by mango_set_user_data().
314  subroutine objective_function_interface(N_parameters, state_vector, objective_value, failed, problem, user_data) bind(C)
315  import
316  integer(C_int), intent(in) :: N_parameters
317  real(C_double), intent(in) :: state_vector(N_parameters)
318  real(C_double), intent(out) :: objective_value
319  integer(C_int), intent(out) :: failed
320  type(mango_problem), value, intent(in) :: problem
321  type(c_ptr), value, intent(in) :: user_data
322  end subroutine objective_function_interface
323 
324  !> Format for the user-supplied subroutine that computes the residuals for a least-squares optimization problem
325  !>
326  !> @param N_parameters The number of independent variables, i.e. the dimension of the search space.
327  !> @param state_vector An array of size <span class="paramname">N_parameters</span> containing the values of the indpendent variables.
328  !> @param N_terms The number of least-squares terms that are summed in the total objective function, i.e. the number of residuals.
329  !> @param residuals An array of size <span class="paramname">N_terms</span> which must be set to the residuals, denoted \f$ R_j \f$
330  !> on @ref concepts.
331  !> @param failed Set the value pointed to by this variable to 1 if the calculation of the residuals fails for some reason.
332  !> Otherwise the value should be 0.
333  !> @param problem A pointer to the class representing this optimization problem. This pointer can be useful for
334  !> getting information about the MPI communicators.
335  !> @param user_data Pointer to user-supplied data, which can be set by mango_set_user_data().
336  subroutine vector_function_interface(N_parameters, state_vector, N_terms, residuals, failed, problem, user_data) bind(C)
337  import
338  integer(C_int), intent(in) :: N_parameters, N_terms
339  real(C_double), intent(in) :: state_vector(N_parameters)
340  !double precision, intent(in) :: state_vector(:)
341  real(C_double), intent(out) :: residuals(N_terms)
342  integer(C_int), intent(out) :: failed
343  type(mango_problem), value, intent(in) :: problem
344  type(c_ptr), value, intent(in) :: user_data
345  end subroutine vector_function_interface
346  end interface
347 
348 contains
349 
350 ! subroutine mango_problem_create(this, N_parameters)
351 ! type(mango_problem), intent(out) :: this
352 ! integer :: N_parameters
353 ! this%object = C_mango_problem_create(N_parameters)
354 ! end subroutine mango_problem_create
355 !
356 ! subroutine mango_problem_create_least_squares(this, N_parameters, N_terms)
357 ! type(mango_problem), intent(out) :: this
358 ! integer :: N_parameters, N_terms
359 ! this%object = C_mango_problem_create(N_parameters)
360 ! end subroutine mango_problem_create_least_squares
361 
362  !> Create a standard (i.e. non-least-squares) optimization problem.
363  !> @param this An object storing the created optimization problem.
364  !> @param N_parameters The number of independent variables.
365  !> @param state_vector An array of size N_parameters, which will be used to store the initial condition.
366  !> You can set the values of this array either before or after calling this routine,
367  !> as long as they are set before calling \ref mango_optimize.
368  !> @param objective_function A reference to the objective function that will be minimized.
369  subroutine mango_problem_create(this, N_parameters, state_vector, objective_function)
370  type(mango_problem), intent(out) :: this
371  integer, intent(in) :: N_parameters
372  !double precision, intent(in) :: state_vector(:)
373  real(C_double), intent(in) :: state_vector(:)
374  double precision, dimension(2) :: x = (/ 3.0, 4.0 /)
375  double precision :: f
376  real(C_double) :: state_vector_copy(N_parameters)
377  procedure(objective_function_interface) :: objective_function
378  integer :: failed_temp = 0
379  !external objective_function
380 
381  if (size(state_vector) .ne. n_parameters) then
382  print *,"Error! N_parameters does not equal size(state_vector)."
383  print *,"N_parameters:",n_parameters," size(state_vector):",size(state_vector)
384  stop
385  end if
386  state_vector_copy = state_vector
387 
388  !this%object = C_mango_problem_create(int(N_parameters,C_int), real(state_vector,C_double), C_funloc(objective_function))
389  !this%object = C_mango_problem_create(int(N_parameters,C_int), c_loc(state_vector(1)), C_funloc(objective_function))
390  !this%object = C_mango_problem_create(int(N_parameters,C_int), state_vector_copy(1), int(dummy,C_int), C_funloc(objective_function))
391  !this%object = C_mango_problem_create(int(N_parameters,C_int), state_vector(1), int(dummy,C_int), C_funloc(objective_function))
392  this%object = c_mango_problem_create(int(n_parameters,c_int), state_vector(1), c_funloc(objective_function))
393 
394  ! For info on passing function pointers, see
395  ! https://gcc.gnu.org/onlinedocs/gcc-4.6.1/gfortran/C_005fFUNLOC.html#C_005fFUNLOC
396  !print *,"mango.F90 subroutine mango_problem_create: C_funloc(objective_function)=",C_funloc(objective_function)
397  !print *,"state_vector size in mango.F90:",size(state_vector_copy)
398  !print *,"state_vector in mango.F90:",state_vector_copy
399  !call objective_function(2, x, f, failed_temp, this)
400  !print *,"Done calling objective fn from mango.F90. f=",f
401  end subroutine mango_problem_create
402 
403  !> Create a least-squares optimization problem.
404  !> @param this An object storing the created optimization problem.
405  !> @param N_parameters The number of independent variables.
406  !> @param state_vector An array of size N_parameters, which will be used to store the initial condition.
407  !> You can set the values of this array either before or after calling this routine,
408  !> as long as they are set before calling \ref mango_optimize.
409  !> @param N_terms The number of terms that are summed in the objective function, i.e. the number of elements in the residual vector.
410  !> @param targets An array of size N_terms, storing the target values of each residual function.
411  !> @param sigmas An array of size N_terms, storing the scaling factors for each term in the residual function.
412  !> @param best_residual_function An array of size N_terms. When \ref mango_optimize concludes successfully, this array will store
413  !> the values of the residuals for the optimum point.
414  !> @param residual_function A reference to the subroutine that computes the residuals.
415  subroutine mango_problem_create_least_squares(this, N_parameters, state_vector, N_terms, targets, sigmas, best_residual_function, residual_function)
416  type(mango_problem), intent(out) :: this
417  integer, intent(in) :: N_parameters, N_terms
418  real(C_double), intent(in) :: state_vector(:), targets(:), sigmas(:), best_residual_function(:)
419  procedure(vector_function_interface) :: residual_function
420  this%object = c_mango_problem_create_least_squares(int(n_parameters,c_int), state_vector(1), int(n_terms,c_int), targets(1), sigmas(1), best_residual_function(1), c_funloc(residual_function))
422 
423  !> Delete an optimization problem, freeing memory used internally by MANGO.
424  !> @param this The optimization problem to destroy.
425  subroutine mango_problem_destroy(this)
426  type(mango_problem), intent(inout) :: this
427  call c_mango_problem_destroy(this%object)
428  this%object = c_null_ptr
429  end subroutine mango_problem_destroy
430 
431  !> Sets the optimization algorithm
432  !>
433  !> Note the related subroutine \ref mango_set_algorithm_from_string.
434  !> @param this The optimization problem to modify.
435  !> @param algorithm One of the enumerated constants representing optimization algorithms.
436  !> If the integer supplied is too large or too small, a C++ exception will be thrown.
437  subroutine mango_set_algorithm(this,algorithm)
438  type(mango_problem), intent(in) :: this
439  integer, intent(in) :: algorithm
440  call c_mango_set_algorithm(this%object, int(algorithm,c_int))
441  end subroutine mango_set_algorithm
442 
443  !> Sets the optimization algorithm
444  !>
445  !> Note the related subroutine \ref mango_set_algorithm.
446  !> @param this The optimization problem to modify.
447  !> @param algorithm_str A lowercase string containing one of the available algorithms, e.g. "petsc_nm".
448  !> If the string supplied does not match any of the available algorithms, a C++ exception will be thrown.
449  subroutine mango_set_algorithm_from_string(this,algorithm_str)
450  ! Passing strings between fortran and C is fraught, so I opted to pass fixed-size character arrays instead.
451  type(mango_problem), intent(in) :: this
452  character(len=*), intent(in) :: algorithm_str
453  character(C_char) :: algorithm_str_padded(mango_interface_string_length)
454  integer :: j
455  algorithm_str_padded = char(0);
456  if (len(algorithm_str) > mango_interface_string_length-1) stop "String is too long!" ! -1 because C expects strings to be terminated with char(0);
457  do j = 1, len(algorithm_str)
458  algorithm_str_padded(j) = algorithm_str(j:j)
459  end do
460  call c_mango_set_algorithm_from_string(this%object, algorithm_str_padded)
461  end subroutine mango_set_algorithm_from_string
462 
463  !> Reads in the number of worker groups and algorithm from a file.
464  !>
465  !> This subroutine is used in the examples, so the testing framework can vary the number of worker groups and optimization algorithm.
466  !> @param this The optimization problem.
467  !> @param filename The filename of the file to read.
468  subroutine mango_read_input_file(this,filename)
469  ! Passing strings between fortran and C is fraught, so I opted to pass fixed-size character arrays instead.
470  type(mango_problem), intent(in) :: this
471  character(len=*), intent(in) :: filename
472  character(C_char) :: filename_padded(mango_interface_string_length)
473  integer :: j
474  filename_padded = char(0);
475  if (len(filename) > mango_interface_string_length-1) stop "String is too long!" ! -1 because C expects strings to be terminated with char(0);
476  do j = 1, len(filename)
477  filename_padded(j) = filename(j:j)
478  end do
479  call c_mango_read_input_file(this%object, filename_padded)
480  end subroutine mango_read_input_file
481 
482  !> Sets the name of the output file that will record values of the objective function at each evaluation.
483  !>
484  !> @param this The optimization problem
485  !> @param filename A string giving the filename to use for the output file. If the file already exists, it will be over-written.
486  subroutine mango_set_output_filename(this,filename)
487  ! Passing strings between fortran and C is fraught, so I opted to pass fixed-size character arrays instead.
488  type(mango_problem), intent(in) :: this
489  character(len=*), intent(in) :: filename
490  character(C_char) :: filename_padded(mango_interface_string_length)
491  integer :: j
492  filename_padded = char(0);
493  if (len(filename) > mango_interface_string_length-1) stop "String is too long!" ! -1 because C expects strings to be terminated with char(0);
494  do j = 1, len(filename)
495  filename_padded(j) = filename(j:j)
496  end do
497  call c_mango_set_output_filename(this%object, filename_padded)
498  end subroutine mango_set_output_filename
499 
500  !> Initialize MANGO's internal MPI data that describes the partitioning of the processes into worker groups.
501  !>
502  !> This subroutine divides up the available MPI processes into worker groups, after checking to see
503  !> if the selected optimization algorithm supports concurrent function evaluations.
504  !> Do not confuse this subroutine with MPI_Init, the routine from MPI that initializes MPI itself!
505  !> mango_mpi_init must be called by the driver code after the call to MPI_Init.
506  !> This subroutine should be called after setting N_worker_groups and setting the optimization algorithm.
507  !> This way, MANGO can change N_worker_groups to 1 if an algorithm is chosen that does not support concurrent function evaluations.
508  !> @param this The optimization problem.
509  !> @param mpi_comm The MPI communicator to use for the optimization. Usually this is MPI_COMM_WORLD. However,
510  !> if you want to run the optimization on a subset of MPI_COMM_WORLD, you can supply the appropriate communicator instead.
511  subroutine mango_mpi_init(this,mpi_comm)
512  type(mango_problem), intent(in) :: this
513  integer, intent(in) :: mpi_comm
514  call c_mango_mpi_init(this%object, int(mpi_comm,c_int))
515  end subroutine mango_mpi_init
516 
517  !> Use a user-supplied partitioning of the MPI processes into worker groups.
518  !>
519  !> Use either this subroutine or \ref mango_mpi_init, not both.
520  !> @param this The optimization problem for which you want to set the MPI structures.
521  !> @param comm_world An MPI communicator consisting of all the processors that will participate in the optimization in any way.
522  !> @param comm_group_leaders An MPI communicator consisting only of the group leaders.
523  !> @param comm_worker_groups An MPI communicator containing all the processors of comm_world, but with a separate "color" for each worker group. The processes with rank 0 in this communicator must be the same as the processes in comm_group_leaders.
524  subroutine mango_mpi_partition_set_custom(this, comm_world, comm_group_leaders, comm_worker_groups)
525  type(mango_problem), intent(in) :: this
526  integer, intent(in) :: comm_world, comm_group_leaders, comm_worker_groups
527  call c_mango_mpi_partition_set_custom(this%object, int(comm_world,c_int), int(comm_group_leaders,c_int), int(comm_worker_groups,c_int))
528  end subroutine mango_mpi_partition_set_custom
529 
530  !> Set the number of worker groups
531  !>
532  !> This subroutine (or mango_read_input_file) should be called before mango_mpi_init.
533  !> @param this The optimization problem.
534  !> @param N_worker_groups The requested number of worker groups.
535  subroutine mango_set_n_worker_groups(this, N_worker_groups)
536  type(mango_problem), intent(in) :: this
537  integer, intent(in) :: N_worker_groups
538  call c_mango_set_n_worker_groups(this%object, int(n_worker_groups,c_int))
539  end subroutine mango_set_n_worker_groups
540 
541  !> Get the number of worker groups.
542  !>
543  !> @param this The optimization problem.
544  !> @return The number worker groups.
545  integer function mango_get_n_worker_groups(this)
546  type(mango_problem), intent(in) :: this
547  mango_get_n_worker_groups = c_mango_get_n_worker_groups(this%object)
548  end function mango_get_n_worker_groups
549 
550  !> Carry out the optimization.
551  !>
552  !> This is the main computationally demanding step.
553  !> @param this The optimization problem.
554  !> @return The minimum value found for the objective function.
555  double precision function mango_optimize(this)
556  type(mango_problem), intent(in) :: this
557  mango_optimize = c_mango_optimize(this%object)
558  end function mango_optimize
559 
560  !> Get the MPI rank of this processor in MANGO's world communicator.
561  !>
562  !> @param this The optimization problem.
563  !> @return The MPI rank of this processor in MANGO's world communicator.
564  integer function mango_get_mpi_rank_world(this)
565  type(mango_problem), intent(in) :: this
566  mango_get_mpi_rank_world = c_mango_get_mpi_rank_world(this%object)
567  end function mango_get_mpi_rank_world
568 
569  !> Get the MPI rank of this processor in MANGO's "worker groups" communicator.
570  !>
571  !> @param this The optimization problem.
572  !> @return The MPI rank of this processor in MANGO's "worker groups" communicator.
573  integer function mango_get_mpi_rank_worker_groups(this)
574  type(mango_problem), intent(in) :: this
575  mango_get_mpi_rank_worker_groups = c_mango_get_mpi_rank_worker_groups(this%object)
577 
578  !> Get the MPI rank of this processor in MANGO's "group leaders" communicator.
579  !>
580  !> @param this The optimization problem.
581  !> @return The MPI rank of this processor in MANGO's "group leaders" communicator.
582  !> A value of -1 is returned on any processor that is not a group leader.
583  integer function mango_get_mpi_rank_group_leaders(this)
584  type(mango_problem), intent(in) :: this
585  mango_get_mpi_rank_group_leaders = c_mango_get_mpi_rank_group_leaders(this%object)
587 
588  !> Get the number of MPI processors in MANGO's world communicator.
589  !>
590  !> @param this The optimization problem.
591  !> @return The number of MPI processors in MANGO's world communicator.
592  integer function mango_get_n_procs_world(this)
593  type(mango_problem), intent(in) :: this
594  mango_get_n_procs_world = c_mango_get_n_procs_world(this%object)
595  end function mango_get_n_procs_world
596 
597  !> Get the number of MPI processors in the worker group that this processor belongs to.
598  !>
599  !> @param this The optimization problem.
600  !> @return The number of MPI processors in the worker group that this processor belongs to.
601  integer function mango_get_n_procs_worker_groups(this)
602  type(mango_problem), intent(in) :: this
603  mango_get_n_procs_worker_groups = c_mango_get_n_procs_worker_groups(this%object)
605 
606  !> Get the number of MPI processors in the "group leaders" communicator.
607  !>
608  !> @param this The optimization problem.
609  !> @return The number of MPI processors in the "group leaders" communicator.
610  !> On a processor that is a group leader, this number will be the same as the number of worker groups.
611  !> On a processor that is not a group leader, this function will return -1.
612  integer function mango_get_n_procs_group_leaders(this)
613  type(mango_problem), intent(in) :: this
614  mango_get_n_procs_group_leaders = c_mango_get_n_procs_group_leaders(this%object)
616 
617  !> Determine whether this MPI processor has rank=0 in MANGO's world communicator.
618  !>
619  !> @param this The optimization problem.
620  !> @return .true. if this MPI processor has rank=0 in MANGO's world communicator, .false. otherwise.
621  logical function mango_get_proc0_world(this)
622  type(mango_problem), intent(in) :: this
623  integer :: result
624  result = c_mango_get_proc0_world(this%object)
625  if (result == 0) then
626  mango_get_proc0_world = .false.
627  elseif (result == 1) then
628  mango_get_proc0_world = .true.
629  else
630  stop "Error in mango_get_proc0_world"
631  end if
632  end function mango_get_proc0_world
633 
634  !> Determine whether this MPI processor has rank=0 in MANGO's "worker groups" communicator.
635  !>
636  !> @param this The optimization problem.
637  !> @return .true. if this MPI processor has rank=0 in MANGO's "worker groups" communicator, .false. otherwise.
638  !> In other words, the return value is .true. for group leaders.
639  logical function mango_get_proc0_worker_groups(this)
640  type(mango_problem), intent(in) :: this
641  integer :: result
642  result = c_mango_get_proc0_worker_groups(this%object)
643  if (result == 0) then
645  elseif (result == 1) then
647  else
648  stop "Error in mango_get_proc0_worker_groups"
649  end if
650  end function mango_get_proc0_worker_groups
651 
652  !> Get MANGO's "world" MPI communicator.
653  !>
654  !> @param this The optimization problem.
655  !> @return MANGO's "world" MPI communicator.
656  integer function mango_get_mpi_comm_world(this)
657  type(mango_problem), intent(in) :: this
658  mango_get_mpi_comm_world = c_mango_get_mpi_comm_world(this%object)
659  end function mango_get_mpi_comm_world
660 
661  !> Get MANGO's "worker groups" MPI communicator.
662  !>
663  !> @param this The optimization problem.
664  !> @return MANGO's "worker groups" MPI communicator.
665  integer function mango_get_mpi_comm_worker_groups(this)
666  type(mango_problem), intent(in) :: this
667  mango_get_mpi_comm_worker_groups = c_mango_get_mpi_comm_worker_groups(this%object)
669 
670  !> Get MANGO's "group leaders" MPI communicator.
671  !>
672  !> @param this The optimization problem.
673  !> @return MANGO's "group leaders" MPI communicator.
674  integer function mango_get_mpi_comm_group_leaders(this)
675  type(mango_problem), intent(in) :: this
676  mango_get_mpi_comm_group_leaders = c_mango_get_mpi_comm_group_leaders(this%object)
678 
679  !> Get the number of independent variables for an optimization problem.
680  !> @param this The mango_problem object to query.
681  !> @return The number of independent variables, i.e. the dimensionality of the parameter space.
682  integer function mango_get_n_parameters(this)
683  type(mango_problem), intent(in) :: this
684  mango_get_n_parameters = c_mango_get_n_parameters(this%object)
685  end function mango_get_n_parameters
686 
687  !> For least-squares optimization problems, get the number of terms that are summed in the objective function.
688  !> @param this The mango_problem object to query.
689  !> @return The number of terms that are summed in the objective function.
690  integer function mango_get_n_terms(this)
691  type(mango_problem), intent(in) :: this
692  mango_get_n_terms = c_mango_get_n_terms(this%object)
693  end function mango_get_n_terms
694 
695  !> Determine which worker group this MPI process belongs to.
696  !> @param this The mango_problem object to query.
697  !> @return An integer indicating the worker group to which this MPI process belongs.
698  integer function mango_get_worker_group(this)
699  type(mango_problem), intent(in) :: this
700  mango_get_worker_group = c_mango_get_worker_group(this%object)
701  end function mango_get_worker_group
702 
703  !> For an optimization problem that has already been solved, return the index of the function evaluation corresponding to the optimum.
704  !>
705  !> @param this The optimization problem.
706  !> @return The index of the function evaluation corresponding to the optimum.
707  !> If \ref mango_optimize has not yet been called, a value of -1 will be returned.
708  integer function mango_get_best_function_evaluation(this)
709  type(mango_problem), intent(in) :: this
710  mango_get_best_function_evaluation = c_mango_get_best_function_evaluation(this%object)
712 
713  !> For an optimization problem that has already been solved, return the number of times the objective function was evaluated.
714  !>
715  !> @param this The optimization problem.
716  !> @return The number of times the objective function was evaluated.
717  !> If \ref mango_optimize has not yet been called, a value of 0 will be returned.
718  integer function mango_get_function_evaluations(this)
719  type(mango_problem), intent(in) :: this
720  mango_get_function_evaluations = c_mango_get_function_evaluations(this%object)
721  end function mango_get_function_evaluations
722 
723  !> Set the maximum number of evaluations of the objective function that will be allowed before the optimization is terminated.
724  !>
725  !> @param this The optimization problem.
726  !> @param N The maximum number of evaluations of the objective function that will be allowed before the optimization is terminated.
727  !> If this number is less than 1, a C++ exception will be thrown.
728  subroutine mango_set_max_function_evaluations(this, N)
729  type(mango_problem), intent(in) :: this
730  integer(C_int), intent(in) :: N
731  call c_mango_set_max_function_evaluations(this%object, n)
733 
734  !> Control whether 1-sided or centered finite differences will be used to compute derivatives of the objective function.
735  !>
736  !> @param this The optimization problem.
737  !> @param centered_differences If .true., centered differences will be used. If .false., 1-sided differences will be used.
738  !> Centered differences are more accurate, but require more function evaluations (2*N_parameters) compared to
739  !> 1-sided differences (which require N_parameters+1 evaluations).
740  subroutine mango_set_centered_differences(this, centered_differences)
741  type(mango_problem), intent(in) :: this
742  logical, intent(in) :: centered_differences
743  integer(C_int) :: logical_to_int
744  logical_to_int = 0
745  if (centered_differences) logical_to_int = 1
746  call c_mango_set_centered_differences(this%object, logical_to_int)
747  end subroutine mango_set_centered_differences
748 
749  !> Determine whether MANGO has an optimization algorithm corresponding to the provided string.
750  !>
751  !> @param algorithm_str A string to examine.
752  !> @return .true. if algorithm_str corresponds to one of the optimization algorithms known by MANGO, .false. otherwise.
753  logical function mango_does_algorithm_exist(algorithm_str)
754  ! Passing strings between fortran and C is fraught, so I opted to pass fixed-size character arrays instead.
755  character(len=*), intent(in) :: algorithm_str
756  character(C_char) :: algorithm_str_padded(mango_interface_string_length)
757  integer :: j, result_int
758  algorithm_str_padded = char(0);
759  if (len(algorithm_str) > mango_interface_string_length-1) stop "String is too long!" ! -1 because C expects strings to be terminated with char(0);
760  do j = 1, len(algorithm_str)
761  algorithm_str_padded(j) = algorithm_str(j:j)
762  end do
763  mango_does_algorithm_exist = (c_mango_does_algorithm_exist(algorithm_str_padded) == 1)
764  end function mango_does_algorithm_exist
765 
766  !> Set an absolute step size for finite difference derivatives.
767  !>
768  !> @param this The optimization problem
769  !> @param finite_difference_step_size An absolute step size to use for finite difference derivatives.
770  subroutine mango_set_finite_difference_step_size(this,finite_difference_step_size)
771  type(mango_problem), intent(in) :: this
772  double precision, intent(in) :: finite_difference_step_size
773  call c_mango_set_finite_difference_step_size(this%object, real(finite_difference_step_size,c_double))
775 
776  !> Impose bound constraints on an optimization problem.
777  !>
778  !> Note that not every optimization algorithm allows bound constraints. If bound constraints
779  !> have been turned on with this subroutine and \ref mango_optimize is called,
780  !> MANGO will check whether the selected algorithm supports bound constraints. If not,
781  !> a warning message will be printed to stdout, and the optimization will proceed,
782  !> ignoring the bound constraints.
783  !> @param this The optimization problem to modify
784  !> @param lower_bounds An array of size N_parameters, giving the lower bound for each independent variable.
785  !> @param upper_bounds An array of size N_parameters, giving the upper bound for each independent variable.
786  subroutine mango_set_bound_constraints(this, lower_bounds, upper_bounds)
787  type(mango_problem), intent(in) :: this
788  double precision, intent(in) :: lower_bounds(:), upper_bounds(:)
789  call c_mango_set_bound_constraints(this%object, lower_bounds(1), upper_bounds(1))
790  end subroutine mango_set_bound_constraints
791 
792  !> Control how much diagnostic information is printed by MANGO.
793  !>
794  !> This diagnostic information may be helpful for debugging.
795  !> @param this The optimization problem to control
796  !> @param verbose If <= 0, no diagnostic information will be printed. If >0, diagnostic information will be printed.
797  subroutine mango_set_verbose(this, verbose)
798  type(mango_problem), intent(in) :: this
799  integer, intent(in) :: verbose
800  call c_mango_set_verbose(this%object, verbose)
801  end subroutine mango_set_verbose
802 
803  !> For least-squares problems, control whether or not to print each individual residual in the MANGO output file.
804  !>
805  !> You may wish to print this information to see the relative magnitude of each term
806  !> in the objective function. On the other hand, for problems with many terms, you may
807  !> wish to suppress this information to make the file more readable.
808  !> @param this The optimization problem to control. If the problem is not a least-squares problem,
809  !> something bad is likely to happen, like a segmentation fault.
810  !> @param print_residuals_in_output_file Whether or not to print every residual term in the output file.
811  subroutine mango_set_print_residuals_in_output_file(this, print_residuals_in_output_file)
812  type(mango_problem), intent(in) :: this
813  logical, intent(in) :: print_residuals_in_output_file
814  integer(C_int) :: logical_to_int
815  logical_to_int = 0
816  if (print_residuals_in_output_file) logical_to_int = 1
817  call c_mango_set_print_residuals_in_output_file(this%object, logical_to_int)
819 
820  !> Pass a data structure to the objective function whenever it is called.
821  !>
822  !> @param this The optimization problem to modify.
823  !> @param user_data A pointer to the variable or data structure you want to pass to the objective function.
824  !> To find this pointer, apply the C_LOC function to your variable. C_LOC is available in the standard ISO_C_BINDING module.
825  subroutine mango_set_user_data(this, user_data)
826  type(mango_problem), intent(in) :: this
827  type(c_ptr), intent(in) :: user_data
828  call c_mango_set_user_data(this%object, user_data)
829  end subroutine mango_set_user_data
830 
831  !> Tell the worker MPI processes (i.e. those that are not group leaders) that the optimization problem is complete.
832  !>
833  !> This subroutine should only be called by group leaders.
834  !> This subroutine is typically called immediately after \ref mango_optimize.
835  !> You can see typical usage of this subroutine in the examples. However you are also free to
836  !> use your own approach to stopping the worker processes instead of this subroutine.
837  !> @param this The optimization problem.
838  subroutine mango_stop_workers(this)
839  type(mango_problem), intent(in) :: this
840  call c_mango_stop_workers(this%object)
841  end subroutine mango_stop_workers
842 
843  !> Tell the worker MPI processes (i.e. those that are not group leaders) to begin an evaluation of the objective function.
844  !>
845  !> This subroutine should only be called by group leaders.
846  !> This subroutine is typically called at the beginning of the user-supplied subroutine for the objective function.
847  !> You can see typical usage of this subroutine in the examples. However you are also free to
848  !> use your own approach to controlling the worker processes instead of this subroutine.
849  !> @param this The optimization problem.
850  subroutine mango_mobilize_workers(this)
851  type(mango_problem), intent(in) :: this
852  call c_mango_mobilize_workers(this%object)
853  end subroutine mango_mobilize_workers
854 
855  !> For an MPI worker, determine whether to carry out another evaluation of the objective function or exit.
856  !>
857  !> This subroutine should only be called on MPI processors that are not group leaders.
858  !> You can see typical usage of this subroutine in the examples. However you are also free to
859  !> use your own approach to controlling the worker processes instead of this subroutine.
860  !> @param this The optimization problem.
861  !> @return If .true., this processor should help to evaluate the objective function. If .false., the optimization has been completed,
862  !> so this processor can move on.
863  logical function mango_continue_worker_loop(this)
864  type(mango_problem), intent(in) :: this
865  integer :: result
866  result = c_mango_continue_worker_loop(this%object)
867  if (result == 0) then
869  elseif (result == 1) then
871  else
872  stop "Error in mango_continue_worker_loop"
873  end if
874  end function mango_continue_worker_loop
875 
876  !> Write a file showing the worker group assignments and rank of each process in each MPI communicator.
877  !>
878  !> @param this The optimization problem
879  !> @param filename The name of the file to write. If this file already exists, it will be over-written.
880  subroutine mango_mpi_partition_write(this,filename)
881  ! Passing strings between fortran and C is fraught, so I opted to pass fixed-size character arrays instead.
882  type(mango_problem), intent(in) :: this
883  character(len=*), intent(in) :: filename
884  character(C_char) :: filename_padded(mango_interface_string_length)
885  integer :: j
886  filename_padded = char(0);
887  if (len(filename) > mango_interface_string_length-1) stop "String is too long!" ! -1 because C expects strings to be terminated with char(0);
888  do j = 1, len(filename)
889  filename_padded(j) = filename(j:j)
890  end do
891  call c_mango_mpi_partition_write(this%object, filename_padded)
892  end subroutine mango_mpi_partition_write
893 
894  !> Impose bound constraints on an optimization problem, with the bounds chosen as multiples of the initial state vector.
895  !>
896  !> To use this subroutine, you must first call \ref mango_set_bound_constraints, so MANGO has pointers to the
897  !> arrays allocted by the user for lower and upper bounds. mango_set_relative_bound_constraints will overwrite the entries of these arrays.
898  !>
899  !> There are two possible methods of determining the bound constraints using this subroutine, depending
900  !> on the parameter preserve_sign.
901  !>
902  !> If preserve_sign is false, the bounds will be symmetric about 0, given by the value
903  !> of the initial condition multiplied by max_factor, expanded to be at least min_radius different from
904  !> the initial condition. Thus, for independent
905  !> variable \f$ x_j \f$, the bounds will be \f$ x_j \in [-R_j, R_j] \f$, where
906  !> \f$ R_j = \max(\mathtt{min\_radius}, |x_j| \mathtt{max\_factor})\f$.
907  !> Note that the parameter min_factor is not used in this case.
908  !>
909  !> If preserve_sign is true, the lower and upper bounds for a given independent variable
910  !> will have the same sign as the corresponding element of state_vector (the initial condition supplied to the constructor).
911  !> The bounds are determined by multiplying each independent variable by min_factor and max_factor, keeping
912  !> both bounds at least min_radius from the initial condition (while not crossing 0).
913  !> Thus, if independent variable \f$ x_j \f$ is positive, the bounds will be \f$ x_j \in [L_j, R_j] \f$ where
914  !> \f$ L_j = \max(0, \min(x_j - \mathtt{min\_radius}, x_j \, \mathtt{min\_factor})) \f$ and
915  !> \f$ R_j = \max(x_j + \mathtt{min\_radius}, x_j \, \mathtt{max\_factor}) \f$.
916  !> If independent variable \f$ x_j \f$ is negative, the bounds will be \f$ x_j \in [L_j, R_j] \f$ where
917  !> \f$ L_j = \min(x_j - \mathtt{min\_radius}, x_j \, \mathtt{max\_factor}) \f$ and
918  !> \f$ R_j = \min(0, \max(x_j + \mathtt{min\_radius}, x_j \, \mathtt{min\_factor})) \f$.
919  !> For the special case \f$x_j=0\f$, then the bounds are \f$ x_j \in [-\mathtt{min\_radius}, \mathtt{min\_radius}] \f$.
920  !>
921  !> Note that not every optimization algorithm allows bound constraints. If bound constraints
922  !> have been turned on with this subroutine and \ref mango_optimize is called,
923  !> MANGO will check whether the selected algorithm supports bound constraints. If not,
924  !> a warning message will be printed to stdout, and the optimization will proceed,
925  !> ignoring the bound constraints.
926  !> @param this The optimization problem to modify
927  !> @param min_factor See description above. The value must lie in [0,1] or else a C++ exception will be thrown.
928  !> @param max_factor See description above. The value must be \f$ \ge 1 \f$, or else a C++ expection will be thrown.
929  !> @param min_radius See description above. The value must be \f$ \ge 0 \f$, or else a C++ exception will be thrown.
930  !> @param preserve_sign See description above.
931  subroutine mango_set_relative_bound_constraints(this, min_factor, max_factor, min_radius, preserve_sign)
932  type(mango_problem), intent(in) :: this
933  real(C_double), intent(in) :: min_factor, max_factor, min_radius
934  logical, intent(in) :: preserve_sign
935  integer(C_int) :: preserve_sign_int
936  preserve_sign_int = 0
937  if (preserve_sign) preserve_sign_int = 1
938  call c_mango_set_relative_bound_constraints(this%object, min_factor, max_factor, min_radius, preserve_sign_int)
940 
941  !> Sets the number of points considered as a set for parallel line searches
942  !>
943  !> The default value is 0.
944  !> If the value is \f$\le 0\f$, the number will be set to the number of worker groups.
945  !> Normally this default is the best choice, in terms of load balancing. However you may occasionally
946  !> wish to set the number of points in a line search to some other value, particularly for tests
947  !> involving parallelization.
948  !> @param this The optimization problem to control
949  !> @param N_line_search The number of points considered as a set for parallel line searches.
950  subroutine mango_set_n_line_search(this, N_line_search)
951  type(mango_problem), intent(in) :: this
952  integer, intent(in) :: N_line_search
953  call c_mango_set_n_line_search(this%object, n_line_search)
954  end subroutine mango_set_n_line_search
955 
956 end module mango_mod
mango_mod::mango_get_n_parameters
integer function mango_get_n_parameters(this)
Get the number of independent variables for an optimization problem.
Definition: mango.F90:683
mango_mpi_partition_write
void mango_mpi_partition_write(mango::Problem *This, char filename[mango_interface_string_length])
Definition: interface.cpp:235
mango_mod::mango_get_n_terms
integer function mango_get_n_terms(this)
For least-squares optimization problems, get the number of terms that are summed in the objective fun...
Definition: mango.F90:691
mango_set_algorithm_from_string
void mango_set_algorithm_from_string(mango::Problem *This, char algorithm_name[mango_interface_string_length])
Definition: interface.cpp:78
mango_get_mpi_comm_worker_groups
int mango_get_mpi_comm_worker_groups(mango::Problem *This)
Definition: interface.cpp:148
mango_get_function_evaluations
int mango_get_function_evaluations(mango::Problem *This)
Definition: interface.cpp:172
mango_set_bound_constraints
void mango_set_bound_constraints(mango::Problem *This, double *lower_bounds, double *upper_bounds)
Definition: interface.cpp:200
mango_mod::vector_function_interface
Format for the user-supplied subroutine that computes the residuals for a least-squares optimization ...
Definition: mango.F90:336
mango_interface_string_length
#define mango_interface_string_length
Definition: interface.cpp:26
mango_read_input_file
void mango_read_input_file(mango::Problem *This, char filename[mango_interface_string_length])
Definition: interface.cpp:82
mango_set_output_filename
void mango_set_output_filename(mango::Problem *This, char filename[mango_interface_string_length])
Definition: interface.cpp:86
mango_set_verbose
void mango_set_verbose(mango::Problem *This, int *verbose)
Definition: interface.cpp:204
mango_set_centered_differences
void mango_set_centered_differences(mango::Problem *This, int *centered_differences_int)
Definition: interface.cpp:180
mango_mod::mango_problem
An object that represents an optimization problem.
Definition: mango.F90:72
mango_mpi_partition_set_custom
void mango_mpi_partition_set_custom(mango::Problem *This, MPI_Fint *comm_world, MPI_Fint *comm_group_leaders, MPI_Fint *comm_worker_groups)
Definition: interface.cpp:96
mango_stop_workers
void mango_stop_workers(mango::Problem *This)
Definition: interface.cpp:222
mango_set_relative_bound_constraints
void mango_set_relative_bound_constraints(mango::Problem *This, double *min_factor, double *max_factor, double *min_radius, int *preserve_sign)
Definition: interface.cpp:239
mango_mod::mango_get_n_procs_worker_groups
integer function mango_get_n_procs_worker_groups(this)
Get the number of MPI processors in the worker group that this processor belongs to.
Definition: mango.F90:602
mango_get_mpi_rank_world
int mango_get_mpi_rank_world(mango::Problem *This)
Definition: interface.cpp:112
mango_get_mpi_rank_group_leaders
int mango_get_mpi_rank_group_leaders(mango::Problem *This)
Definition: interface.cpp:120
mango_set_finite_difference_step_size
void mango_set_finite_difference_step_size(mango::Problem *This, double *step)
Definition: interface.cpp:196
mango_mod::mango_get_n_procs_world
integer function mango_get_n_procs_world(this)
Get the number of MPI processors in MANGO's world communicator.
Definition: mango.F90:593
mango_set_user_data
void mango_set_user_data(mango::Problem *This, void *user_data)
Definition: interface.cpp:218
mango_get_proc0_worker_groups
int mango_get_proc0_worker_groups(mango::Problem *This)
Definition: interface.cpp:140
mango_mod::objective_function_interface
Format for the user-supplied subroutine that computes the objective function for a general (non least...
Definition: mango.F90:314
mango_problem_create
mango::Problem * mango_problem_create(int *N_parameters, double *state_vector, mango::objective_function_type objective_function)
Definition: interface.cpp:43
mango_problem_destroy
void mango_problem_destroy(mango::Problem *This)
Definition: interface.cpp:70
mango_get_best_function_evaluation
int mango_get_best_function_evaluation(mango::Problem *This)
Definition: interface.cpp:168
mango_continue_worker_loop
int mango_continue_worker_loop(mango::Problem *This)
Definition: interface.cpp:230
mango_mod::mango_set_n_line_search
subroutine mango_set_n_line_search(this, N_line_search)
Sets the number of points considered as a set for parallel line searches.
Definition: mango.F90:951
mango_mod::mango_get_n_procs_group_leaders
integer function mango_get_n_procs_group_leaders(this)
Get the number of MPI processors in the "group leaders" communicator.
Definition: mango.F90:613
mango_set_max_function_evaluations
void mango_set_max_function_evaluations(mango::Problem *This, int *N)
Definition: interface.cpp:176
mango_problem_create_least_squares
mango::Least_squares_problem * mango_problem_create_least_squares(int *N_parameters, double *state_vector, int *N_terms, double *targets, double *sigmas, double *best_residual_function, mango::vector_function_type residual_function)
Definition: interface.cpp:64
mango_mod::mango_set_n_worker_groups
subroutine mango_set_n_worker_groups(this, N_worker_groups)
Set the number of worker groups.
Definition: mango.F90:536
mango_get_mpi_comm_world
int mango_get_mpi_comm_world(mango::Problem *This)
Definition: interface.cpp:144
mango_does_algorithm_exist
int mango_does_algorithm_exist(char algorithm_name[mango_interface_string_length])
Definition: interface.cpp:190
mango_get_mpi_comm_group_leaders
int mango_get_mpi_comm_group_leaders(mango::Problem *This)
Definition: interface.cpp:152
mango_get_mpi_rank_worker_groups
int mango_get_mpi_rank_worker_groups(mango::Problem *This)
Definition: interface.cpp:116
mango_set_print_residuals_in_output_file
void mango_set_print_residuals_in_output_file(mango::Least_squares_problem *This, int *print_residuals_in_output_file_int)
Definition: interface.cpp:208
mango_get_worker_group
int mango_get_worker_group(mango::Problem *This)
Definition: interface.cpp:164
mango_mod::mango_get_n_worker_groups
integer function mango_get_n_worker_groups(this)
Get the number of worker groups.
Definition: mango.F90:546
mango_mobilize_workers
void mango_mobilize_workers(mango::Problem *This)
Definition: interface.cpp:226
mango_get_proc0_world
int mango_get_proc0_world(mango::Problem *This)
Definition: interface.cpp:136
mango_mod
This Fortran module provides the Fortran API for calling MANGO from outside applications.
Definition: mango.F90:23
mango_set_algorithm
void mango_set_algorithm(mango::Problem *This, mango::algorithm_type *algorithm)
Definition: interface.cpp:74
mango_optimize
double mango_optimize(mango::Problem *This)
Definition: interface.cpp:108
mango_mpi_init
void mango_mpi_init(mango::Problem *This, MPI_Fint *comm)
Definition: interface.cpp:92