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