Passing strings from and to Fortran DLL using ctypes

hi ,

I want to read a file with a fortran dll using ctype.

the structure of my file is:

  • AX

  • BX

  • … .

  • 4.0 5.0 6.9

  • 1.2 8.0 7.0

  • … … …

for read the file , i have PATH to pass to dll fortran and get a character array from Ax,BX,… and float array from the number.

In my Fortran code:
DLL_READ.f90 (2.2 KB)

I have error : error #8532: A character dummy argument with length other than 1 is not interoperable.

in my python code :

Summary

import ctypes
import numpy as np
from numpy.ctypeslib import ndpointer
import os

def Import_DLL():

PATH = os.path.dirname(os.path.realpath(__file__))
print('path=',PATH)
Lib = ctypes.CDLL(os.path.join(PATH,"./DLL_read.dll"))
return Lib

def Decla_Arg():

Lib.open_file.argtypes = [ctypes.c_int, ctypes.c_char_p]
Lib.open_file.restype = None

Lib.get_char_col.argtypes = [ctypes.c_int, ctypes.POINTER(ctypes.c_int), ctypes.c_char_p]
Lib.get_char_col.restype = None

Lib.get_float.argtypes = [ctypes.c_int, ctypes.POINTER(ctypes.c_int), ndpointer(dtype=ctypes.c_float)]
Lib.get_float.restype = None

def open_file(FicWxx,PATH):
Lib.open_file(FicWxx,PATH)
return

def get_char_col(FicWxx,nliais):
elem=list()
nliais = ctypes.c_int(nliais)
Lib.get_char_col(FicWxx, nliais, elem)
return elem

def get_res_type(FicWxx, nliais, istep):

param=np.zeros(shape=(3 , nliais),dtype=ctypes.c_float)

Lib.get_float(FicWxx, nliais,param)
return param

-------------- main --------------------------------

if name == “main”:

Lib=Import_DLL()
Decla_Arg()

FicWxx = 15
PATH ="C\\user\\file.txt"
open_file(FicWxx,PATH)

elem = get_char_col(FicWxx, nliais)
print("elem =", elem)

param = get_res_type(FicWxx, nliais)
print("param =", param)

I have problem with PATH : Lib.open_file(FicWxx,PATH)
ctypes.ArgumentError: argument 2: TypeError: wrong type

and I have errors with python strings array ELEM.

Thank you for your help

try changing this

subroutine OPEN_FILE(FicWxx,PATH)  BIND(C)
!DEC$ ATTRIBUTES DLLEXPORT :: OPEN_FILE
integer (KIND=C_INT)         , intent(in) ,value     :: FicWxx
character(KIND=C_char,len=264) , intent(in)    		    :: PATH

by

subroutine OPEN_FILE(FicWxx,path_cptr,lenpath_cptr)  BIND(C)
!DEC$ ATTRIBUTES DLLEXPORT :: OPEN_FILE
integer (KIND=C_INT)         , intent(in) ,value     :: FicWxx
type(c_ptr), value :: path_cptr
integer(c_int), value :: lenpath_cptr
character(len=lenpath_cptr,kind=c_char), pointer :: PATH

call c_f_pointer(path_cptr, PATH)
...

You’ll have to add a 3rd argument in the python call with the length of the string

...
Lib.open_file.argtypes = [ctypes.c_int, ctypes.c_char_p,ctypes.c_int]
...
def open_file(FicWxx,PATH):
      Lib.open_file(FicWxx,PATH.encode("utf-8"),len(PATH))
      return

something like this

@hkvzjal thank you
i know get un array float but i don’t know how get a array character.
i have problem with elem
elem = get_char_col(FicWxx, nliais)

i try this:

and in Fortran :

 subroutine GET_Char_COL(FicWxx,numel,Elem ) BIND(C) 
			  !DEC$ ATTRIBUTES DLLEXPORT :: GET_Char_COL

			  integer (KIND=C_INT), intent(in)   ,value                              :: FicWxx
			  integer (KIND=C_INT), intent(in)                                       :: numel
              character(KIND=C_char,len=1), dimension(numel), intent(out)  :: Elem 
			  
			  integer                                                        :: n,irec
              
              do n = 1, numel
                 read(FicWxx,*)Elem(n) 
             end do 
  end subroutine GET_Char_COL

The results is a null array elem = ?

Hi, you might want to try my library GitHub - rjfarmer/gfort2py: Library to allow calling fortran code from python which handles all the wrapping for you. You don’t even need to worry about using iso_fortran_env or bind(c) as long as your Fotran code is in a module.

@rfarmer Thank you but i use Intel compiler and i can’t change .

@ldir,

Please see this thread from a while ago at the Intel Fortran forum where I provide a simple but worked out example of passing strings between Fortran and Python via ctypes.

Please take a look and see if you can reuse any of my suggestions from that Intel forum thread. I have not studied your specific issue here.

@FortranFan thank you for you reply.
it’s not the same thing . I try to read and pass a array string from DLL fortran to python with using ctype.

@Idir After looking closely at what you want to do, I would strongly recommend that you modify slightly your implementation. As I see in your def get_char_col(FicWxx,nliais): declaration you want to pass an empty array of characters to the Fortran function.

Already a first issue is that this array has not been allocated anywhere.

The second issue I see is that, on the Fortran side you are declaring character(KIND=C_char,len=1), dimension(numel), intent(out) :: Elem meaning that you assume each character in the array having a lengt of 1, but on the Python side you defined np.dtype('a16') meaning each element has length = 16.

The third issue is that you are trying to convert directly to character… To my understanding, strings are not directly interoperable, you have to use an intermediate pointer, thus this kind of implementations:

type(c_ptr), value :: path_cptr !> the string coming from C / Python as a type(c_ptr)
integer(c_int), value :: lenpath_cptr
character(len=lenpath_cptr,kind=c_char), pointer :: PATH !> a Fortran internal re-interpretation of the string by a pointer

call c_f_pointer(path_cptr, PATH) !> link your pointer

Not that it might not be possible, but if you can, avoid interoperating array of strings directly. In your current case, it seems it would be easier if you let Fortran do the heavy lifting (IO / crunching), and pass around arrays of numeric kind.

@hkvzjal thank you for your replay,
i changed the Fortran and python code. i allocate array in python and use pointer in fortran

def get_char_col(FicWxx,nliais):
    z=[' ' for i in range(nliais)]
    elem=np.asarray(z, dtype = np.dtype('a16'))
    nliais = ctypes.c_int(nliais)
    Lib.get_char_col(FicWxx, nliais, elem)
    return elem
subroutine GET_Char_COL(FicWxx,numel,Py_Elem ) BIND(C) 
              !DEC$ ATTRIBUTES DLLEXPORT :: GET_Char_COL

              integer (KIND=C_INT)       ,value            , intent(in)    :: FicWxx
              integer (KIND=C_INT)                         , intent(in)    :: numel
              type(c_ptr)                , value               :: Py_Elem
              character(KIND=C_char,len=16) ,dimension(:)     ,pointer   :: Elem  
              
              integer                                                        :: n
              
              call c_f_pointer(Py_Elem,Elem)
              
              do n = 1, numel
                 read(FicWxx,*)Elem(n)
             end do 
          end subroutine GET_Char_COL

when i run , i get this error : OSError: exception: stack overflow.

This is the link for python and fortran code .

thank you for your help

hi ,
After several trials and errors I finally managed to find a solution to my problem. I share the solution it might help someone else

subroutine GET_Char_COL(FicWxx,numel,Py_Elem ) BIND(C) 
          !DEC$ ATTRIBUTES DLLEXPORT :: GET_Char_COL

          integer (KIND=C_INT)       ,value            , intent(in)    :: FicWxx
          integer (KIND=C_INT)                         , intent(in)    :: numel
          type(c_ptr)                , value               :: Py_Elem
          character(KIND=C_char,len=16) ,dimension(:)     ,pointer   :: Elem  
          
          integer                                                        :: n
          
          call c_f_pointer(Py_Elem,Elem,[numel])  ! numel is Rank-one array .The size must be equal to the rank of Py_Elem 
          
          do n = 1, numel
             read(FicWxx,*)Elem(n)
         end do 
      end subroutine GET_Char_COL

I’m trying to do something similar to what @Idir did here but passing from a list of strings that represents full file paths in python to an array of characters in Fortran. Can’t manage to get it working, here is a minimum (non)working example:

a python file test_strings.py

import os
import numpy as np
import ctypes

api = np.ctypeslib.load_library('libtest.so','')

str_list = ['AAA','BBB','CCC','DDD']

str_arr = (ctypes.c_char_p * len(str_list))()
str_arr[:] = [i.encode("utf-8") for i in str_list]
num_paths = ctypes.c_int(len(str_list))
len_paths = ctypes.c_int(len(str_list[0]))

api.test_list_str( num_paths , len_paths , str_arr )

Fortran file test.f90

module test
  use iso_c_binding
  implicit none

  contains

  subroutine test_list_str(num_paths , len_paths , filelist_ptr) bind(c)
#if _WIN32 & __INTEL_COMPILER
        !DEC$ ATTRIBUTES DLLEXPORT :: test_list_str
#endif      
    integer(c_int), value :: num_paths , len_paths        
    type(c_ptr), value    :: filelist_ptr
    
    character(kind=c_char,len=len_paths), pointer :: filelist(:)
    
    integer   :: i
    !-------------------------------------------------
    print *, 'num_paths', num_paths, 'max_len', len_paths
    allocate( filelist(num_paths) )
    call c_f_pointer(filelist_ptr, filelist,[num_paths])
    do i = 1, num_paths
        print *, 'file: ',filelist(i)(1:len_paths)
    end do
                  
  end subroutine

end module

Compiling and executing

gfortran -cpp -O0 -fpic -c test.f90
gfortran -shared -o libtest.so test.o
python3 test_strings.py

Output

num_files           4 max_len           3
file: P?�
file: �
file: �
file: =��

I was trying to mix with the solutions here Passing a list of strings to from python/ctypes to C function expecting char ** - Stack Overflow. after several trials I don’t manage to capture the issue, any ideas?

Your problem is in the Fortran side Jose @hkvzjal: the Python-C binding assumes you are passing a char**, i.e., an array of character pointers. Your Fortran routine instead only reads the first pointer, and assumes it contains contiguous characters, instead of other pointers.

So you may want to modify your Fortran interface as:

  subroutine test_list_str(num_paths , len_paths , filelist_ptr) bind(c,name='test_list_str')
    integer(c_int), value :: num_paths , len_paths        
    type(c_ptr), intent(in) :: filelist_ptr(num_paths)
    
    character(kind=c_char,len=1), pointer :: filelist_c(:)
    character(kind=c_char,len=:), allocatable :: filelist(:)
    
    integer   :: i,j
    !-------------------------------------------------
    allocate(character(len=len_paths) :: filelist(num_paths)) 
    do i = 1, num_paths
        call c_f_pointer(filelist_ptr(i), filelist_c,[len_paths])
        forall(j=1:len_paths) filelist(i)(j:j) = filelist_c(j)
        print *, filelist(i)
    end do

  end subroutine

This returns

federico@Federicos-MBP tmp % python3 test_strings.py 
 AAA
 BBB
 CCC
 DDD
2 Likes

Brilliant! Thanks @FedericoPerini, exactly what I was looking for!

it fails (means does not correctly print the str_list data) for the following str_list:

str_list = ['AAA','BBBbbb','CCC','DDD']

Only characters of length as that of the first str_list value are output. Is it possible to assign length/size for each str_list variable to print out the correct str_list?

update: may be by taking the max length value from len_paths.

1 Like

No python expert, but it looks like Python returns c_null_char-terminated strings. So, no need to pass the length parameter:

module test
  use iso_c_binding
  implicit none

  contains

  subroutine test_list_str(num_paths , filelist_ptr) bind(c,name='test_list_str')
    integer(c_int), value :: num_paths
    type(c_ptr), intent(in) :: filelist_ptr(num_paths)

    character(kind=c_char,len=1), pointer :: filelist_c(:)
    character(kind=c_char,len=:), allocatable :: filelist(:)

    interface
       integer(c_int) function c_strlen(s) bind(C,name='strlen')
          import c_int,c_ptr
          type(c_ptr), value :: s
       end function c_strlen
    end interface

    integer   :: i,j,l(num_paths)

    ! Get max length
    do j=1,num_paths
       l(j) = c_strlen(filelist_ptr(j))
    end do

    allocate(character(len=maxval(l)) :: filelist(num_paths))
    do i = 1, num_paths
        call c_f_pointer(filelist_ptr(i), filelist_c,[l(i)])
        forall(j=1:l(i)) filelist(i)(j:j) = filelist_c(j)
        print *, filelist(i)
    end do
  end subroutine

end module

I added the following to “clean” the “garbage” tailing the strings:

do i = 1, num_paths
      call c_f_pointer(filelist_ptr(i), filelist_c,[l(i)])
      forall(j=1:l(i)) filelist(i)(j:j) = filelist_c(j)
      forall(j=l(i)+1:maxval(l)) filelist(i)(j:j) = ' '
      print *, filelist(i)
end do

Otherwise I was getting things like:

AAA=�
BBBbbb
CCC
DDD
1 Like