- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello fellow Fortranners,For two evenings I have been struggling to debug the following error:
/home/ipribec/nlopt/test/t_modern_fortran.f90(215): error #7062: The characteristics of dummy argument 2 of the associated actual procedure differ from the characteristics of dummy argument 2 of the dummy procedure. [MSQUARE]
call myopt%set_min_objective(msquare,f_data,ires)
-------------------------------------^
According to other posts (see here) I could find on the forum, this error shows up when the INTENT descriptors (or other characteristics) of the actual and dummy argument do not match. Now for a bit more background on my specific problem.
I am writing a Fortran wrapper for the nonlinear optimization package NLopt written in C. Like in the C++ wrapper I am aiming for an object-oriented API, that behind the scene makes calls to the individual C routines using the iso_c_binding module for interfacing. Ideally, the application developer in Fortran would be completely free from the iso_c_binding module. For passing functions I have came up with two different options, one is a "functor" pattern where the user must extend an abstract type with a deferred function argument (any parameters can be stored in the derived type), and the other is to pass a function that accepts an extended type in case any parameters are needed by the function (this approach is used in the Fortran interface to the GNU Scientific library - FGSL). Both solutions are a bit verbose, but are meant to guarantee type safety.
A shortened version of the wrapper module is shown below:
module nlopt use, intrinsic :: iso_c_binding use nlopt_c_interface ! the C binding is stored here ! ... imports from a few other modules ... implicit none private ! ... bunch of public statements ... ! Exposed for the user to extend! type, abstract, public :: nlopt_void end type public :: user_func_interface abstract interface real(c_double) function user_func_interface(n,x,grad,data) import c_int, c_double, nlopt_void integer(c_int), intent(in), value :: n real(c_double), intent(in) :: x(n) real(c_double), intent(out), optional :: grad(n) class(nlopt_void) :: data end function end interface ! ... other type declarations ... type, public :: opt private type(c_ptr) :: o = c_null_ptr ! the "nlopt_opt" object on the C side integer(c_int) :: last_result = NLOPT_FAILURE real(c_double) :: last_optf = huge(1._c_double) integer(c_int) :: forced_stop_reason = NLOPT_FORCED_STOP type(adaptor), pointer :: objective => null() ! keep handle to objective function on Fortran side ! ... other stuff for book-keeping the constraints ... contains procedure, private :: set_min_objective_oo procedure, private :: set_min_objective_new generic, public :: set_min_objective => set_min_objective_oo, & set_min_objective_new ! ... other functions and subroutines defined by the C API ... end type contains subroutine set_min_objective_new(this,user_func,user_func_data,ires) class(opt), intent(inout) :: this procedure(user_func_interface) :: user_func class(nlopt_void), target :: user_func_data integer(c_int), intent(out), optional :: ires integer(c_int) :: ret type(c_ptr) :: c_handle type(c_funptr) :: c_fun_handle if (associated(this%objective_handle)) then nullify(this%objective_handle) end if allocate(this%objective_handle) this%objective_handle%func => user_func this%objective_handle%data => user_func_data c_handle = c_loc(this%objective_handle) c_fun_handle = c_funloc(nlopt_function_poly_c) ret = nlopt_set_min_objective(this%o,c_fun_handle,c_handle) ! C function call if (present(ires)) ires = ret end subroutine ! ... all the other type-bound procedure ... end module
What I am using here is an adaptor pattern, where the user function and parameters are passed to the C function as a void* along with an adaptor function "nlopt_function_poly_c" that then evaluates the user function with the passed data. This way the user need not worry about making the calls to c_loc and c_funloc himself.
A simple driver program then looks something like this:
module new_mod use, intrinsic :: iso_c_binding, only: c_int, c_double use nlopt, only: nlopt_void, user_func_interface implicit none private public :: msquare type, extends(nlopt_void), public :: my_void ! any data needed to parametrize the user function end type contains real(c_double) function msquare(n,x,grad,data) implicit none integer(c_int), intent(in), value :: n real(c_double), intent(in) :: x(n) real(c_double), intent(out), optional :: grad(n) class(nlopt_void) :: data select type(data) class is (my_void) if (present(grad)) then grad(1) = 0.0_c_double grad(2) = 0.5_c_double/sqrt(x(2)) end if msquare = sqrt(x(2)) class default stop "[msquare] incorrect extension of nlopt_void" end select end function end module program main use iso_c_binding use nlopt, only: algorithm_name, nlopt_version, opt, nlopt_void use nlopt_enum, only : NLOPT_LD_MMA use new_mod implicit none call new_example contains subroutine new_example() use nlopt, only: user_func_interface implicit none integer(c_int), parameter :: n = 2 procedure(user_func_interface), pointer :: p_msquare => msquare type(opt) :: myopt ! ... other declarations ... type(my_void) :: f_data print *, "========= NEW EXAMPLE ==========" myopt = opt(a=NLOPT_LD_MMA,n=n) call myopt%set_min_objective(msquare,f_data,ires) ! does not work !call myopt%set_min_objective(p_msquare,f_data,ires) ! works ! ... rest of the program ... end subroutine end program
If I compile the code with the Intel Fortran Compiler (Version 19.0.1.144) I get the error shown at the beginning. Surprisingly, if instead of passing the function I pass a pointer to the function (p_msquare), and "force" the routine to comply with the required interface, then the program works. The gfortran/gcc compiler is also able to compile the example normally.
My confusion goes even further, when I tried create a minimal working example that would reproduce this error, the code compiled just fine! The minimal example:
module test_mod use, intrinsic :: iso_c_binding implicit none public :: nlopt_void, nlopt_opt type, abstract :: nlopt_void end type abstract interface real(c_double) function user_func_interface(n,x,grad,data) import c_int, c_double, nlopt_void integer(c_int), intent(in), value :: n real(c_double), intent(in) :: x(n) real(c_double), intent(out), optional :: grad(n) class(nlopt_void) :: data end function end interface type nlopt_opt contains procedure, public :: set_objective procedure, public :: set_min_objective_new generic, public :: set_min_objective => set_min_objective_new end type contains subroutine set_objective(this,func,func_data) class(nlopt_opt), intent(inout) :: this procedure(user_func_interface) :: func class(nlopt_void), target :: func_data integer(c_int), parameter :: n = 5 real(c_double) :: x(n) x = [1.,2.,3.,4.,5.] print *, func(n,x,data=func_data) end subroutine subroutine set_min_objective_new(this,user_func,user_func_data,ires) ! implicit none class(nlopt_opt), intent(inout) :: this procedure(user_func_interface) :: user_func class(nlopt_void), target :: user_func_data integer(c_int), intent(out), optional :: ires integer(c_int) :: ret type(c_ptr) :: c_handle type(c_funptr) :: c_fun_handle print *, "hello" end subroutine end module module func_mod use iso_c_binding use test_mod, only: nlopt_void implicit none private public :: msquare type, extends(nlopt_void), public :: my_void ! real(c_double) :: a,b,c end type contains real(c_double) function msquare(n,x,grad,data) integer(c_int), intent(in), value :: n real(c_double), intent(in) :: x(n) real(c_double), intent(out), optional :: grad(n) class(nlopt_void) :: data select type(data) class is (my_void) if (present(grad)) then grad(1) = 0.0_c_double grad(2) = 0.5_c_double/sqrt(x(2)) end if msquare = sqrt(x(2)) class default stop "[msquare] incorrect extension of nlopt_void" end select end function end module program test_mod_main use, intrinsic :: iso_c_binding, only: c_double use test_mod use func_mod, only: msquare, my_void implicit none type(nlopt_opt) :: opt type(my_void) :: my_func_data ! my_func_data = my_void(1.,2.,3.) call opt%set_objective(my_func,my_func_data) ! works call opt%set_min_objective(msquare,my_func_data) ! works contains real(c_double) function my_func(n,x,grad,data) integer(c_int), intent(in), value :: n real(c_double), intent(in) :: x(n) real(c_double), intent(out), optional :: grad(n) class(nlopt_void) :: data my_func = sum(x) end function end program
In case you would like to test it, the entire code can be found on the "simple" branch of my fork of NLopt. To compile with Intel Fortran it is necessary to uncomment the lines 21, 22, and 234 in CMake file and choose the correct the directory address of the ifort and icc compilers. I can also upload the entire source code if needed.
I would be grateful for any ideas on what is causing this error to show up, even if the interfaces seem to be correct (after all gfortran compiles normally and just by passing a procedure pointer instead of the function makes the program work!?).
Best,
Ivan
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It would be nice to include the actual module with the bind C definitions that one needs to compile the first example. I think you should also make user_func_interface a bind(C) routine. I think in our code we are always using these kinds of things as procedure pointers.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Juergen R. wrote:It would be nice to include the actual module with the bind C definitions that one needs to compile the first example. I think you should also make user_func_interface a bind(C) routine. I think in our code we are always using these kinds of things as procedure pointers.
As far as I can remember the user_func_interface cannot have the bind(C) attribute since it takes a non-interoperable argument of class(nlopt_void). But indeed the ifort compiler required the bind(C) attribute for the function nlopt_function_poly_c used in the type-bound procedure set_min_objective_new that actually gets called in the C code. (gfortran was able to compile even without it)
I will attach the actual modules as soon as possible.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This looks like a bug in Intel Fortran compiler especially considering your attempt at a minimal working example, which closely your actual case, works. You may want to submit a support request at Intel Online Center (OSC) with your full example as the case: https://supporttickets.intel.com/?lang=en-US
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The modules and test example are in the attached tar archive.
My compilation steps and output:
00:04:48 ipribec@ThinkPad: ~/nlopt/mwe$ ifort -c nlopt_enum.f90 nlopt_c_interface.f90 nlopt.f90 t_modern_fortran.f90
t_modern_fortran.f90(215): error #7062: The characteristics of dummy argument 2 of the associated actual procedure differ from the characteristics of dummy argument 2 of the dummy procedure. [MSQUARE]
call myopt%set_min_objective(msquare,f_data,ires)
-------------------------------------^
t_modern_fortran.f90(215): error #7063: The characteristics of dummy argument 3 of the associated actual procedure differ from the characteristics of dummy argument 3 of the dummy procedure. [MSQUARE]
call myopt%set_min_objective(msquare,f_data,ires)
-------------------------------------^
compilation aborted for t_modern_fortran.f90 (code 1)
00:05:01 ipribec@ThinkPad: ~/nlopt/mwe$ nano t_modern_fortran.f90 # replace msquare with p_msquare in line 215
00:05:25 ipribec@ThinkPad: ~/nlopt/mwe$ ifort -c t_modern_fortran.f90
To create an executable than requires linking against the NLopt library in C (https://github.com/stevengj/nlopt).
The minimal working example I tried creating to isolate the error:
00:08:19 ipribec@ThinkPad: ~/nlopt/mwe$ ifort minimal_example.f90
00:15:55 ipribec@ThinkPad: ~/nlopt/mwe$ ./a.out
15.0000000000000
hello
I will look into submitting a support request. Thank you.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Before filing a bug report, please consider the following errors/extensions in the code that you posted as an attachment to #5.
1. An argument to a BIND(C) procedure should not be OPTIONAL (several places).
2. You have used the function NLOPT_GET_DIMENSION in several specification expressions.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you mecej4 for these concerns.
Regarding point #1 I thought this is allowed according to the Fortran 2018 standard? In section 21.2 Optional arguments (page 397) in the chapter "Fortran 2018 enhancements to interoperability with C" of Modern Fortran Explained, 2nd edition, Metcalf, Reid, and Cohen (2018) it says "... Fortran 2018 adopts this idiom for permitting Fortran interoperable procedures to have optional arguments. ... In a call from Fortran, when the actual argument is absent, a null pointer will be passed to the C procedure." This is exactly what I need, because for minimization algorithms that do not require the gradient calculation, a null pointer will be passed instead.
Regarding point #2, I do not think this is a violation as the procedure NLOPT_GET_DIMENSION is declared pure. I have committed however a minor crime here as I know this procedure is pure only from inspecting the C code and not because the Fortran compiler could inspect the body of this function. A perhaps safer solution would be for me to store a copy of the integer dimension variable in my derived type OPT. In the C++ wrapper they have made use of exceptions to warn the user to initialize the OPT instance, before allowing any objective or constraint functions to be specified.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I see your standpoint, but the 19.0.2 compiler does not seem to accept it yet:
$ ifort -stand -warn stderrors -c nlopt_c_interface.f90 nlopt_c_interface.f90(9): error #8809: An OPTIONAL or EXTERNAL dummy argument to a BIND(C) procedure is not interoperable. [GRADIENT] real(c_double) function nlopt_func(n,x,gradient,func_data) bind(c) -----------------------------------------------^ nlopt_c_interface.f90(17): error #8809: An OPTIONAL or EXTERNAL dummy argument to a BIND(C) procedure is not interoperable. [GRADIENT] subroutine nlopt_mfunc(m,result,n,x,gradient,func_data) bind(c) --------------------------------------------^ compilation aborted for nlopt_c_interface.f90 (code 1)
NOTE: One of the delightful features of the forum software is that you have to copy/paste the lines with "error #8809" into an editor before you can see something meaningful. Sorry!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I see. With the 19.01 compiler and flag "-warn all" these errors are not displayed and the code ends up working like it's supposed to (besides from the error 7062), as far as I've tested.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
mecej4 wrote:I see your standpoint, but the 19.0.2 compiler does not seem to accept it yet:
$ ifort -stand -warn stderrors -c nlopt_c_interface.f90
mecej4, the ifort option -stand without any argument according to the help menu specificies the standard as f08, so indeed the optional argument should be flagged as an error. -stand f18 should let it pass.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
As a separate issue, I happen to have noticed this in post #1:
if (associated(this%objective_handle)) then nullify(this%objective_handle) end if allocate(this%objective_handle)
The above implies a memory leak should this%objective_handle be associated to begin with. Assuming the handle hadn;t been deallocated elsewhere.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Juergen R. wrote:mecej4, the ifort option -stand without any argument according to the help menu specificies the standard as f08, so indeed the optional argument should be flagged as an error. -stand f18 should let it pass.
Thanks, Juergen. You are correct on both points. However, did IvanP specify -stand f18 (or equivalent), or any option related to language version, when he compiled and ran his tests?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you Jim for this observation. I had the feeling a deallocation statement was missing.
In fact there are other memory leaks I am aware of. The problem is that I am passing Fortran routines for the objective functions and minimization constraints to the C side. If I do not keep a handle on the Fortran side, I am risking a memory leak if the user decides to specify a different objective function or remove the constraints and apply new ones, because the C routines that perform this cleanup cannot deallocate the memory allocated on the Fortran side. My planned solution is to maintain a linked list of the constraint functions in the Fortran object with a finalizer routine, that will deallocate any memory, before calling the original C routine. This is my first project building a C wrapper from Fortran and I've learned a lot :)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think he didn't specify such a flag, and according to him he didn't see the error message. ifort as a default should accept all implemented features from the newest published standard, when I remember correctly.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
mecej4 wrote:Quote:
Juergen R. wrote:
mecej4, the ifort option -stand without any argument according to the help menu specificies the standard as f08, so indeed the optional argument should be flagged as an error. -stand f18 should let it pass.
Thanks, Juergen. You are correct on both points. However, did IvanP specify -stand f18 (or equivalent), or any option related to language version, when he compiled and ran his tests?
I can answer this point instead. Indeed, I was not specifying any particular language standard and just running with the defaults. I will add these points to my documentation, that the code assumes a Fortran 2018 compliant compiler.
EDIT: Juergen was faster to answer.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I filed a support request for this issue.
The next compiler update release (out in 3 to 6 weeks) seems to fix the interface issue and compile my example without errors.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page