26 #define mango_interface_string_length 256 
   32   use, 
intrinsic :: iso_c_binding
 
   72   type, 
bind(C) ::  mango_problem
 
   73      type(C_ptr), 
private :: object = c_null_ptr 
 
   87      function c_mango_problem_create(N_parameters, state_vector, objective_function) 
result(this) 
bind(C,name="mango_problem_create") 
   89        integer(C_int) :: n_parameters
 
   93        real(c_double) :: state_vector
 
   94        type(c_funptr), 
value :: objective_function 
 
   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") 
   98        integer(C_int) :: n_parameters, n_terms
 
  100        real(c_double) :: state_vector, targets, sigmas, best_residual_function
 
  101        type(c_funptr), 
value :: residual_function 
 
  102      end function c_mango_problem_create_least_squares
 
  103      subroutine c_mango_problem_destroy (this) 
bind(C,name="mango_problem_destroy") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  234        type(c_ptr), 
value :: this
 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  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") 
  298        type(c_ptr), 
value :: this
 
  299      end subroutine c_mango_set_n_line_search
 
  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
 
  321     type(c_ptr), 
value, 
intent(in) :: user_data
 
  338     integer(C_int), 
intent(in) :: N_parameters, N_terms
 
  339     real(C_double), 
intent(in) :: state_vector(N_parameters)
 
  341     real(C_double), 
intent(out) :: residuals(N_terms)
 
  342     integer(C_int), 
intent(out) :: failed
 
  344     type(c_ptr), 
value, 
intent(in) :: user_data
 
  371     integer, 
intent(in) :: N_parameters
 
  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)
 
  378     integer :: failed_temp = 0
 
  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)
 
  386     state_vector_copy = state_vector
 
  392     this%object = c_mango_problem_create(int(n_parameters,c_int), state_vector(1), c_funloc(objective_function))
 
  417     integer, 
intent(in) :: N_parameters, N_terms
 
  418     real(C_double), 
intent(in) :: state_vector(:), targets(:), sigmas(:), best_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))
 
  427     call c_mango_problem_destroy(this%object)
 
  428     this%object = c_null_ptr
 
  439     integer, 
intent(in) :: algorithm
 
  440     call c_mango_set_algorithm(this%object, int(algorithm,c_int))
 
  452     character(len=*), 
intent(in) :: algorithm_str
 
  453     character(C_char) :: algorithm_str_padded(mango_interface_string_length)
 
  455     algorithm_str_padded = char(0);
 
  456     if (len(algorithm_str) > mango_interface_string_length-1) stop 
"String is too long!"  
  457     do j = 1, len(algorithm_str)
 
  458        algorithm_str_padded(j) = algorithm_str(j:j)
 
  460     call c_mango_set_algorithm_from_string(this%object, algorithm_str_padded)
 
  471     character(len=*), 
intent(in) :: filename
 
  472     character(C_char) :: filename_padded(mango_interface_string_length)
 
  474     filename_padded = char(0);
 
  475     if (len(filename) > mango_interface_string_length-1) stop 
"String is too long!"  
  476     do j = 1, len(filename)
 
  477        filename_padded(j) = filename(j:j)
 
  479     call c_mango_read_input_file(this%object, filename_padded)
 
  489     character(len=*), 
intent(in) :: filename
 
  490     character(C_char) :: filename_padded(mango_interface_string_length)
 
  492     filename_padded = char(0);
 
  493     if (len(filename) > mango_interface_string_length-1) stop 
"String is too long!"  
  494     do j = 1, len(filename)
 
  495        filename_padded(j) = filename(j:j)
 
  497     call c_mango_set_output_filename(this%object, filename_padded)
 
  513     integer, 
intent(in) :: mpi_comm
 
  514     call c_mango_mpi_init(this%object, int(mpi_comm,c_int))
 
  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))
 
  537     integer, 
intent(in) :: N_worker_groups
 
  538     call c_mango_set_n_worker_groups(this%object, int(n_worker_groups,c_int))
 
  624     result = c_mango_get_proc0_world(this%object)
 
  625     if (result == 0) 
then 
  627     elseif (result == 1) 
then 
  630        stop 
"Error in mango_get_proc0_world" 
  642     result = c_mango_get_proc0_worker_groups(this%object)
 
  643     if (result == 0) 
then 
  645     elseif (result == 1) 
then 
  648        stop 
"Error in mango_get_proc0_worker_groups" 
  730     integer(C_int), 
intent(in) :: N
 
  731     call c_mango_set_max_function_evaluations(this%object, n)
 
  742     logical, 
intent(in) :: centered_differences
 
  743     integer(C_int) :: logical_to_int
 
  745     if (centered_differences) logical_to_int = 1
 
  746     call c_mango_set_centered_differences(this%object, logical_to_int)
 
  755     character(len=*), 
intent(in) :: algorithm_str
 
  757     integer :: j, result_int
 
  758     algorithm_str_padded = char(0);
 
  760     do j = 1, len(algorithm_str)
 
  761        algorithm_str_padded(j) = algorithm_str(j:j)
 
  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))
 
  788     double precision, 
intent(in) :: lower_bounds(:), upper_bounds(:)
 
  789     call c_mango_set_bound_constraints(this%object, lower_bounds(1), upper_bounds(1))
 
  799     integer, 
intent(in) :: verbose
 
  800     call c_mango_set_verbose(this%object, verbose)
 
  813     logical, 
intent(in) :: print_residuals_in_output_file
 
  814     integer(C_int) :: logical_to_int
 
  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)
 
  827     type(c_ptr), 
intent(in) :: user_data
 
  828     call c_mango_set_user_data(this%object, user_data)
 
  840     call c_mango_stop_workers(this%object)
 
  852     call c_mango_mobilize_workers(this%object)
 
  866     result = c_mango_continue_worker_loop(this%object)
 
  867     if (result == 0) 
then 
  869     elseif (result == 1) 
then 
  872        stop 
"Error in mango_continue_worker_loop" 
  883     character(len=*), 
intent(in) :: filename
 
  884     character(C_char) :: filename_padded(mango_interface_string_length)
 
  886     filename_padded = char(0);
 
  887     if (len(filename) > mango_interface_string_length-1) stop 
"String is too long!"  
  888     do j = 1, len(filename)
 
  889        filename_padded(j) = filename(j:j)
 
  891     call c_mango_mpi_partition_write(this%object, filename_padded)
 
  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)
 
  952     integer, 
intent(in) :: N_line_search
 
  953     call c_mango_set_n_line_search(this%object, n_line_search)