Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Binding to C char * function

Jacob_Williams
New Contributor I
781 Views

Consider the following example code. I want to call a C function that is returning a char* (in the example, this is dlerror). What I have here seems to work OK. I'm wondering about memory leaks though. In the c_to_fortran_string function (which is based on something I found on the internet), there is some C_F_POINTER voodoo to get the result into a Fortran deferred length string. Is this the best way to do this? Do I need to worry about memory leaks here? I notice that I can deallocate STRING_ARRAY, but if I try to deallocate STRING, I get a "double free or corruption" error. Not sure what that means or if it's something I need to worry about. Any help is appreciated!

program load_library_test

  use, intrinsic :: iso_c_binding

  implicit none

  character(len=*),parameter :: dll_name = 'blah.so'
  integer(c_int),parameter :: rtld_lazy  = 1

  integer(c_intptr_t) :: ihandle
  character(len=:),allocatable :: error_message

  interface
    function dlopen(library, iflag) result(handle) bind(C, name='dlopen')
      import
      implicit none
      integer(c_intptr_t) :: handle
      character(kind=c_char),intent(in),dimension(*) :: library
      integer(kind=c_int),intent(in),value :: iflag
    end function dlopen
    function dlerror() result(error) bind(C, name='dlerror')
      import
      type(c_ptr) :: error
    end function dlerror
  end interface

  ihandle = dlopen(trim(dll_name)//c_null_char, rtld_lazy)

  if (ihandle == 0) then
    error_message = GetError()
    write(*,'(A)') error_message
  else
    write(*,'(A)') 'Success!'
  end if

  contains

  function GetError() result(error_message)

    implicit none

    character(len=:),allocatable :: error_message

    type(C_PTR) :: p

    if (C_ASSOCIATED(p)) then
      error_message = 'UNKNOWN ERROR'
    else
      error_message = c_to_fortran_string(dlerror())
    end if

  end function GetError

  function c_to_fortran_string(cstr) result(str)

    implicit none

    type(c_ptr),value  :: cstr
    character(len=:),allocatable :: str

    character(c_char),dimension(:),pointer :: string_array
    character(kind=c_char,len=1),pointer :: string
    integer :: i ! counter

    str = '' ! initialize

    if (c_associated(cstr)) then
      call c_f_pointer(cptr=cstr, fptr=string)
      call c_f_pointer(cptr=cstr, fptr=string_array, shape=[c_string_length(string)])
      do i=1,size(string_array)
        str = str // string_array(i)
      end do
      if (associated(string_array)) deallocate(string_array)  !this works
      !if (associated(string)) deallocate(string)  ! crashes... "double free or corruption (fasttop)"
    end if

  end function c_to_fortran_string

  function c_string_length(string) result(length)

    implicit none

    character(c_char),dimension(*),intent(in) :: string
    integer :: length

    length = 0
    do while(string(length+1)/=c_null_char)
      length = length + 1
    end do

  end function c_string_length

end program load_library_test

 

0 Kudos
8 Replies
Steven_L_Intel1
Employee
781 Views

Don't deallocate something you didn't allocate. Treat the "string" pointer as readonly.

0 Kudos
FortranFan
Honored Contributor II
781 Views

Jacob Williams wrote:

.. I want to call a C function that is returning a char* (in the example, this is dlerror). What I have here seems to work OK. I'm wondering about memory leaks though. In the c_to_fortran_string function (which is based on something I found on the internet), there is some C_F_POINTER voodoo to get the result into a Fortran deferred length string. Is this the best way to do this? ..

I prefer directly calling C library function of strlen from my Fortran code via normal C interoperability facility of standard Fortran; I invoke strlen when I need to deal with a C type of "char *" with unknown string length as is the case with your dl_error function invocation.  I usually have the "char *" mapped as TYPE(c_ptr) in my code.  All the systems I work with provide highly efficient and reliable strlen implementation, so I don't feel compelled to "reinvent the wheel".  Once the length is determined (say saved in a Fortran integer of lenstr), I use C_F_POINTER to associate the "char *" C pointer to a Fortran pointer of "character(kind=c_char,len=lenstr), pointer :: f_str", normally within a block construct.  Then one can do the normal Fortran CHARACTER type of operations on f_str e.g., assignment of error_message = f_str in your GetError function.  Once done with the operations, I nullify f_str, typically before the block construct is exited.

Bottomline: this can all be a lot less code than what you show.  As to whether it is any better, no comments; to each their own, I suppose.

0 Kudos
Jacob_Williams
New Contributor I
781 Views

Thanks! Actually, I didn't know about strlen (I try to avoid C when possible). So this approach would be something like this?:

interface
  function strlen(str) result(isize) bind(C, name='strlen')
    import
    type(c_ptr),value :: str
    integer(c_int) :: isize
  end function strlen   
end interface

function GetError() result(error_message)
  
  implicit none

  character(len=:),allocatable :: error_message
    
  type(c_ptr) :: cstr
  integer(c_int) :: ilength
        
  cstr = dlerror()
  
  if (c_associated(cstr)) then
  
    ilength = strlen(cstr) 
    
    block
      character(kind=c_char,len=ilength), pointer :: f_str
      call c_f_pointer(cptr=cstr, fptr=f_str)
      error_message = f_str
      deallocate(f_str) ! or nullify(f_str) ???
    end block
    
  else
    error_message = ''
  end if  

end function GetError

Same question though: should f_str be deallocated, rather than nullified? The compiler lets me deallocate(f_str) in this case. Steve, are saying this is not necessary since I'm not explicitly doing an allocate(f_str(...))?

0 Kudos
FortranFan
Honored Contributor II
781 Views

Jacob Williams wrote:

Thanks! Actually, I didn't know about strlen (I try to avoid C when possible). So this approach would be something like this?:

interface
  function strlen(str) result(isize) bind(C, name='strlen')
    import
    type(c_ptr),value :: str
    integer(c_int) :: isize
  end function strlen   
end interface

function GetError() result(error_message)
  
  implicit none

  character(len=:),allocatable :: error_message
    
  type(c_ptr) :: cstr
  integer(c_int) :: ilength
        
  cstr = dlerror()
  
  if (c_associated(cstr)) then
  
    ilength = strlen(cstr) 
    
    block
      character(kind=c_char,len=ilength), pointer :: f_str
      call c_f_pointer(cptr=cstr, fptr=f_str)
      error_message = f_str
      deallocate(f_str) ! or nullify(f_str) ???
    end block
    
  else
    error_message = ''
  end if  

end function GetError

Same question though: should f_str be deallocated, rather than nullified? The compiler lets me deallocate(f_str) in this case. Steve, are saying this is not necessary since I'm not explicitly doing an allocate(f_str(...))?

Yes, except for the "deallocate(f_str)" bit, that's very much what I prefer and suggest for your situation.  A couple of changes I suggest are: 1) initialize error_message first and 2) check for ilength being greater than zero and only then invoke the block construct.

My opinion is that the appropriate action is nullify(f_str) (or f_str => null()).  A general practice of only deallocating what one allocates seems appropriate here.  Note f_str is not allocated in the block construct; it is only associated with the target of c_str with the c_f_pointer procedure.  When one is done, one can simply nullify such an association.

Now, of course, another option for a situation like this where there is a function like dl_error returning char * pointer is to have a C wrapper function that accepts a string parameter of specified length from the Fortran side and this wrapper function then simply copies the returned message from dl_error using a safe strncpy_s type of C string library function.  This way, no pointers need be dealt with on Fortran side nor an invocation to a C library function.

 

0 Kudos
Steven_L_Intel1
Employee
781 Views

Interesting - I would expect the compiler to set the "do not deallocate" flag in the pointer descriptor when C_F_POINTER is used. I will look into that and ask the developers to fix that. This would get an error at runtime (one that says "don't do that!"), not compile-time, as the compiler itself can't track how you've assigned the pointer.

0 Kudos
Steven_L_Intel1
Employee
781 Views

It turns out that we received a similar complaint back in 2013 about being allowed to deallocate a pointer set with C_F_POINTER. The decision at that time was that a program that did this was not valid but that we had no obligation to report an error.

0 Kudos
FortranFan
Honored Contributor II
781 Views

Steve Lionel (Intel) wrote:

It turns out that we received a similar complaint back in 2013 about being allowed to deallocate a pointer set with C_F_POINTER. The decision at that time was that a program that did this was not valid but that we had no obligation to report an error.

A general comment, my 2 cents worth.  Surely, there is no obligation to report an error.  But going "above and beyond" what Intel Fortran may be obligated to do can yield benefits which are immeasurable, something that the Intel Fortran team may wish to keep in mind given the brand name.  Think of "Intel Inside" and how that helped market products based on something most people had never seen, the computer chip.  It was based on a certain trust and confidence in Intel and the expectation of high performance, quality, diligence, etc..  It is obviously a 24x7x365 thing that cuts across the board and applies to all products and services that has the Intel brand associated with it, Fortran included.  Yes, it can be high price (i.e., considerable lot of developer time and effort), but how can one compare immeasurable things (like PCs and other electronics selling like crazy possibly because of a simple sticker) to some low level view of costs!

0 Kudos
Steven_L_Intel1
Employee
781 Views

I am inclined to agree. We have a more generic problem with recognizing when it is and is not permissible to deallocate a pointer, and I have proposed a general solution that would handle this case as well. Fixing this particular case is trivially easy, but it means that some existing, valid program would stop working. Indeed it appears we had a complaint of that in the past, so we have to tread carefully. I'd rather not catch an erroneous program than block a valid program.

0 Kudos
Reply