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

Passing (by reference) a Python string to Fortran function (subroutine)

MattHouston
New Contributor I
3,526 Views

I would like to

  • either pass by reference a Python string to Fortran subroutine that could modify it and pass it back (modified) to Python
  • or pass a Python string to a Fortran function that could return the modified string into "something" (see beneath) interoperable enough that Python could get a string from

I tried this in Fortran :

 

 

 

	module example

		use iso_c_binding
		implicit none
		integer, parameter :: STRLEN = 64
		
	contains
		
		function to_upper(cptr) BIND(C, NAME='to_upper') result(cptrres)
			!DEC$ ATTRIBUTES DLLEXPORT :: to_upper
		
			type(c_ptr), intent(in), value :: cptr
			type(c_ptr) :: value, cptrres
			character, pointer :: fptr(:)
			character(len=STRLEN), allocatable :: fstrings
			
			integer :: i, lenstr
			
			call c_f_pointer(cptr, fptr, [STRLEN])
			lenstr = cstrlen(fptr)
			allocate(fstrings)
			fstrings = transfer(fptr(1:lenstr),fstrings)
	 
			do i = 1, len(fstrings)
				select case(fstrings(i:i))
					case("a":"z")
						fstrings(i:i) = achar(iachar(fstrings(i:i))-32)
				end select
			end do
			
			fptr(1:lenstr) = transfer(fstrings, fptr(1:lenstr))
			cptrres = c_loc(fstrings) ! WHAT TO PUT HERE ?... I'd like a sub f_c_pointer "inverse" to c_f_pointer so that ...
									  ! ... I could write :
									  ! call f_c_pointer(fptr, cptrres, [STRLEN])
			
		end function to_upper
		
		function cstrlen(carray) result(res)
		character(kind=c_char), intent(in) :: carray(:)
		integer :: res
		integer :: ii
		do ii = 1, size(carray)
		  if (carray(ii) == c_null_char) then
			res = ii - 1
			return
		  end if
		end do
		res = ii
		end function cstrlen

	end module example

 

 

 

that I compiled to a TestLib.dll, and that in the Python code :

 

 

 

 

	redist_path = r"C:\Program Files (x86)\Intel\oneAPI\compiler\2021.3.0\windows\redist\intel64_win\compiler"
	dll_full_name = r"C:\MY_DLLs\TestLib.dll"

	import os
	os.add_dll_directory(redist_path)
	#os.add_dll_directory(dll_path)

	import ctypes as ct
	import numpy as np


	# import the dll
	fortlib = ct.CDLL(dll_full_name)

	pyfunc_addition = getattr(fortlib, "addition")

	r = pyfunc_addition(n,m)

	str1 = b"CouCou"

	pyfunc_to_upper = getattr(fortlib, "to_upper")
	#pyfunc_to_upper.argtypes=[ct.c_char_p,ct.c_int]
	#pyfunc_to_upper.restype=None

	pstr2 = pyfunc_to_upper(str1, ct.pointer( ct.c_int(len(str1))))

	str2 = ct.c_char_p(pstr2).value
	print(str2)

 

 

 

but it obviously didn't work.

What preceeds was inspired from the case where one wants to pass back and forth an array of strings (instead of a string as I want), see here :

https://gist.github.com/dektoud/a3b9bb0c485d2ae58143d71f55a8d9e4 

 

Also, I am a bit worried because of Steve Lionel's comment here :

https://community.intel.com/t5/Intel-Fortran-Compiler/passing-string-from-Fortran-to-C/td-p/1138766 

Labels (1)
0 Kudos
7 Replies
IanH
Honored Contributor II
3,327 Views

Amongst other things, you need to consider which language (and underlying runtime) is managing the storage associate with the things that you are passing back and forth.  You have an allocate statement in your attempt - how would that thing get deallocated?

An example of how things might be set up to work...

 

! 2021-07-10 ctypes.f90
module example
  implicit none
contains
  ! This handles the Fortran side of the interfacey bits.  It needs to 
  ! be exported from the DLL on Windows.  You could do that using a 
  ! `!DEC$ DLLEXPORT :: upper` directive, or a DEF file, or via the linker 
  ! command line.  I've done the latter, for aesthetic reasons and because 
  ! I originally forgot the need for the export...
  subroutine upper_python(in_ptr, in_length, out_ptr)  &
      bind(c, name='upper')
    use, intrinsic :: iso_c_binding, only: &
        c_ptr,  &
        c_int,  &
        c_char,  &
        c_f_pointer
    type(c_ptr), value :: in_ptr
    integer(c_int), value :: in_length
    type(c_ptr), value :: out_ptr
    
    character(len=in_length,kind=c_char), pointer :: in_str
    character(len=in_length,kind=c_char), pointer :: out_str
    
    ! Only length one kind=c_char CHARACTER objects are interoperable.  
    ! But case (iii) of F2018 18.2.3.3p3 probably lets us get away 
    ! with this, perhaps in a processor dependent fashion.  If you are 
    ! writing to earlier standards you probably need to do the whole 
    ! c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument
    ! -associate-the-resulting-array-with-a-len(x)-scalar-using
    ! -sequence-association trick.  Whatever!
    call c_f_pointer(in_ptr, in_str)
    call c_f_pointer(out_ptr, out_str)
    
    out_str = upper_fortran(in_str)
  end subroutine upper_python
  
  ! This does the operation we are actually interested in (though 
  ! I was a bit lazy, and didn't deal with c_char kind conversion).
  !
  ! If the string comes in null terminated, it will go out null 
  ! terminated.
  function upper_fortran(in) result(out)
    use, intrinsic :: iso_c_binding, only: c_char
    character(len=*,kind=c_char), intent(in) :: in
    character(len=len(in),kind=c_char) :: out
    
    integer :: i
    
    do i = 1, len(in)
      select case (in(i:i))
      case ('a':'z')
        out(i:i) = achar(iachar(in(i:i)) - iachar('a') + iachar('A'))
      case default  ! Don't forget this bit...
        out(i:i) = in(i:i)
      end select
    end do
  end function upper_fortran
end module example

 

 

 

# 2021-07-10 ctypes.py
from ctypes import *

# The DLL loading mechanism within ctypes on python, by default, uses a very 
# limited set of search paths, which means that the Fortran runtime DLLs are 
# unlikely to be found, even if they have been installed in their normal system 
# wide locations.  Setting winmode to zero means the DLL loading mechanism 
# reverts back to the more typical LoadLibrary API call behaviour, where 
# PATH gets searched for dependent DLLs.  (This still requires that the 
# Fortran runtime DLLs be on PATH!)
#
# Change the path and/or name of the "example" DLL to match your 
# situation...
example_dll = CDLL(
    '2021-07-10 example.dll', 
    winmode=0 )

# The input [byte] string - which we leave unchanged.
in_ptr = c_char_p(b'Hello World')

# Buffer for the result of the Fortran call - set to be the same size as the 
# input byte string.
out_ptr = create_string_buffer(len(in_ptr.value))

# Make magic happen.
example_dll.upper(in_ptr, c_int(len(in_ptr.value)), out_ptr)

print(out_ptr.value)

 

 

 

>ifort /dll "2021-07-10 example.f90" /link /export:upper
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2021-07-10 example.dll"
-dll
"-implib:2021-07-10 example.lib"
/export:upper
"2021-07-10 example.obj"
   Creating library 2021-07-10 example.lib and object 2021-07-10 example.exp

>%localappdata%\Programs\Python\Python39\python.exe "2021-07-10 ctypes.py"
b'HELLO WORLD'

 

 

 

0 Kudos
IanH
Honored Contributor II
3,471 Views

(Forum ate earlier reply...)

Amongst other things, you need to consider which language and language runtime manages the storage for the objects that you are returning from your function or procedure.  You have an allocate statement in your Fortran code -- where is a matching deallocate?

One possibility...

! 2021-07-10 example.f90
module example
  implicit none
contains
  ! This handles the Fortran side of the interfacey bits.  It needs to 
  ! be exported from the DLL on Windows.  You could do that using a 
  ! `!DEC$ DLLEXPORT :: upper` directive, or a DEF file, or via the linker 
  ! command line.  I've done the latter, for aesthetic reasons and because 
  ! I originally forgot the need for the export...
  subroutine upper_python(in_ptr, in_length, out_ptr)  &
      bind(c, name='upper')
    use, intrinsic :: iso_c_binding, only: &
        c_ptr,  &
        c_int,  &
        c_char,  &
        c_f_pointer
    type(c_ptr), value :: in_ptr
    integer(c_int), value :: in_length
    type(c_ptr), value :: out_ptr
    
    character(len=in_length,kind=c_char), pointer :: in_str
    character(len=in_length,kind=c_char), pointer :: out_str
    
    ! Only length one kind=c_char CHARACTER objects are interoperable.  
    ! But case (iii) of F2018 18.2.3.3p3 probably lets us get away 
    ! with this, perhaps in a processor dependent fashion.  If you are 
    ! writing to earlier standards you probably need to do the whole 
    ! c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument
    ! -associate-the-resulting-array-with-a-len(x)-scalar-using
    ! -sequence-association trick.  Whatever!
    call c_f_pointer(in_ptr, in_str)
    call c_f_pointer(out_ptr, out_str)
    
    out_str = upper_fortran(in_str)
  end subroutine upper_python
  
  ! This does the operation we are actually interested in (though 
  ! I was a bit lazy, and didn't deal with c_char kind conversion).
  !
  ! If the string comes in null terminated, it will go out null 
  ! terminated.
  function upper_fortran(in) result(out)
    use, intrinsic :: iso_c_binding, only: c_char
    character(len=*,kind=c_char), intent(in) :: in
    character(len=len(in),kind=c_char) :: out
    
    integer :: i
    
    do i = 1, len(in)
      select case (in(i:i))
      case ('a':'z')
        out(i:i) = achar(iachar(in(i:i)) - iachar('a') + iachar('A'))
      case default  ! Don't forget this bit...
        out(i:i) = in(i:i)
      end select
    end do
  end function upper_fortran
end module example

 

# 2021-07-10 ctypes.py
from ctypes import *

# The DLL loading mechanism within ctypes on python, by default, uses a very 
# limited set of search paths, which means that the Fortran runtime DLLs are 
# unlikely to be found, even if they have been installed in their normal system 
# wide locations.  Setting winmode to zero means the DLL loading mechanism 
# reverts back to the more typical LoadLibrary API call behaviour, where 
# PATH gets searched for dependent DLLs.  (This still requires that the 
# Fortran runtime DLLs be on PATH!)
#
# Change the path and/or name of the "example" DLL to match your 
# situation...
example_dll = CDLL(
    '2021-07-10 example.dll', 
    winmode=0 )

# The input [byte] string - which we leave unchanged.
in_ptr = c_char_p(b'Hello World')

# Buffer for the result of the Fortran call - set to be the same size as the 
# input byte string.
out_ptr = create_string_buffer(len(in_ptr.value))

# Make magic happen.
example_dll.upper(in_ptr, c_int(len(in_ptr.value)), out_ptr)

print(out_ptr.value)

 

>ifort /dll "2021-07-10 example.f90" /link /export:upper
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2021-07-10 example.dll"
-dll
"-implib:2021-07-10 example.lib"
/export:upper
"2021-07-10 example.obj"
   Creating library 2021-07-10 example.lib and object 2021-07-10 example.exp

>%localappdata%\Programs\Python\Python39\python.exe "2021-07-10 ctypes.py"
b'HELLO WORLD'
0 Kudos
MattHouston
New Contributor I
3,321 Views

Thank you very much for your answer, IanH.

You are totally right about the missing deallocate. I was probably wanting to do it right after the 

call f_c_pointer(fptr, cptrres, [STRLEN])

bit I was dreaming of, but even there, it doesn't seem right, does it ?

About the standard :

F2018.18.2.3.3.JPG

I understand that A) we are obviously not in the (ii) case, and that we are also not in the case (i) because in "If the value of CPTR is the C address of an interoperable data entity" the term "data entity" refers to a Fortran data entity (am I right) so that elimination we are indeed in the case (iii). Correct ?

Then, reading case (iii), it seems that what you do (the associating *_ptr's to *_str's) work by the very standard, hence I don't understand your "case (iii) of F2018.18.2.3.3p3 probably lets us get away with this, perhaps in a processor dependent fashion'. Where do I make a mistake ?

Also, I am very interested by your "do the whole c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument-associate-the-resulting-array-with-a-len(x)-scalar-using-sequence-association" trick : could you please develop a bit, or point me to a reference ? (Btw, I am really short in Fortran idioms/patterns/concepts (like this trick you mention, or the opaque pointer method I read about this night) so that, would you have references about that, I would be happy.)

Concerning your solution and memory, I am correct to sum it up like this :

  • python allocates memory for b'Hello World' and in_ptr points to (the beginning of) it
  • this pointer is passed byreference to the fortran subroutine
  • memory is allocated inside upper_fortran for the out c_char arry

? So that we could say that, all in all, your solution makes only one string copy ?

Is a solution with no out_ptr and only modification of in_str (with a subroutine upper_fortran (instead of a function) modyfing in and outing it) possible ?

0 Kudos
MattHouston
New Contributor I
3,433 Views

(Forum also ate my reply, two times, it is really boring. Apparently, the problem was with the "in reply" picture, that I finally simply attached to the reply without including it in the tesx ... Now, by out of angst, I will have to copy paste my replies and questions in a notepad, in case of forum eating them ...)

 

Thank you very much for your answer, IanH.

 

Regarding the missing matching deallocate you are perfectly right. I intented to make it right after the 

call f_c_pointer(fptr, cptrres, [STRLEN])
I was dreaming about. But even there, it does not feel right, doesn't it ?

 

Regarding the standard (see attached picture) : obviously were not in the case (ii). Also, we are a not in the case (i) as I guess that an "interoperable data entity" is irst a Fortran entity, which is not the case here as we pass a Python object to Fortran. Hence by elimination we are in the case (ii). Correct ?

 

Now, about case (iii) of F2018 18.2.3.3 :

 

"If the value of CPTR is the C address of a storage sequence that is not in use by any other Fortran entity, FPTR becomes associated with that storage sequence. If FPTR is an array, its shape is specified by SHAPE and each lower bound is 1. The storage sequence shall be large enough to contain the target object described by FPTR and shall satisfy any other processor-dependent requirement for association."

 

I understand that there is no problem at all, so that I don't get your "case (iii) of F2018 18.2.3.3p3 probably lets us get away with this, perhaps in a processor dependent fashion".

 

Could you please consider developing on your "c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument-associate-the-resulting-array-with-a-len(x)-scalar-using-sequence-association" trick ? By the way, I am quite ignorant of classical idioms/patterns/tricks (like the one you refer to, or like the opaque pointer trick I learned about this night) so that if you have reference(s) regarding this, I would be happy.

 

On the memory aspect of your code, am I right to summerize it as follows :

  • python allocates memory for b'Hello World' and a pointer pointing to (the beginning of) it
  • this is passed by reference (meaning bu that "no copy is created"
  • In the function upper_fortran, the line 
    character(len=len(in),kind=c_char) :: out​
    creates memory for the returning "string"
  • this string is returned by reference to the python

?

 

Also, is it possible to in your upper_python subroutine not to have the out_ptr, but just have the in_ptr, in an "inout" fashion ? It obviously is, sorry.

0 Kudos
IanH
Honored Contributor II
3,358 Views

Regarding the missing matching deallocate you are perfectly right. I intented to make it right after the

call f_c_pointer(fptr, cptrres, [STRLEN])
I was dreaming about. But even there, it does not feel right, doesn't it ?

No - if you had called deallocate there, then the object you were trying to pass back to Python would have ceased to exist, before Python had an opportunity to do anything with it. The C address for that now non-existent object becomes what is informally known as a dangling pointer - it is the address of something that no longer exists. If the pointer is subsequently de-referenced you have a "use after free" situation.

Regarding the standard (see attached picture) : obviously were not in the case (ii). Also, we are a not in the case (i) as I guess that an "interoperable data entity" is irst a Fortran entity, which is not the case here as we pass a Python object to Fortran. Hence by elimination we are in the case (ii). Correct ?

There's a whole subsection in the standard about what things are considered interoperable. When it comes to Fortran objects of type CHARACTER, they need to be of kind C_CHAR and of length one. That wasn't the [general] case for the in_str and out_str actual arguments to C_F_POINTER in my example - the length was arbitrary - that is why we are not relying on case (i).

Now, about case (iii) of F2018 18.2.3.3 :

"If the value of CPTR is the C address of a storage sequence that is not in use by any other Fortran entity, FPTR becomes associated with that storage sequence. If FPTR is an array, its shape is specified by SHAPE and each lower bound is 1. The storage sequence shall be large enough to contain the target object described by FPTR and shall satisfy any other processor-dependent requirement for association."

I understand that there is no problem at all, so that I don't get your "case (iii) of F2018 18.2.3.3p3 probably lets us get away with this, perhaps in a processor dependent fashion".

I simply don't know what "processor-dependent" requirements there might be on this association. (With ifort on Windows x64 I very much suspect there are no requirements for the case of an object that is of type character and kind C_CHAR, for other types/kinds things like alignment requirements might come into play.)

Could you please consider developing on your "c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument-associate-the-resulting-array-with-a-len(x)-scalar-using-sequence-association" trick ? By the way, I am quite ignorant of classical idioms/patterns/tricks (like the one you refer to, or like the opaque pointer trick I learned about this night) so that if you have reference(s) regarding this, I would be happy.

Case (iii) of the C_F_POINTER description that we are relying on above is new to F2018 (which is the real reason I wrote "probably" about it above, because it is relatively new to me, but let me continue pretending...). Previously with F2008, the formal way to associate a character scalar of arbitrary length with a char* passed in from C, without creating a copy, was something along the lines of...

  ! Corresponds to a C function with prototype:
  !
  !   void proc(char *in_ptr, int in_len);
  SUBROUTINE proc(in_ptr, in_len) BIND(C, NAME='proc')
    USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_INT, C_CHAR, C_F_POINTER
    TYPE(C_PTR), VALUE :: in_ptr
    INTEGER(C_INT), VALUE :: in_len
    
    CHARACTER(LEN=1,KIND=C_CHAR), POINTER :: array(:)
    CHARACTER(LEN=:,KIND=C_CHAR), POINTER :: scalar
    
    CALL C_F_POINTER(in_ptr, array, [in_len])
    CALL sequence_associate(array, in_len, scalar)
    PRINT *, scalar
  END SUBROUTINE proc

  SUBROUTINE sequence_associate(target, in_len, ptr)
    USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_CHAR
    INTEGER, INTENT(IN) :: in_len
    CHARACTER(LEN=in_len,KIND=C_CHAR), INTENT(IN), TARGET :: target(1)
    CHARACTER(LEN=:,KIND=C_CHAR), INTENT(OUT), POINTER :: ptr
    
    ptr => target(1)
  END SUBROUTINE sequence_associate

I think with F2003 the above was processor dependent.

On the memory aspect of your code, am I right to summerize it as follows :

python allocates memory for b'Hello World' and a pointer pointing to (the beginning of) it
this is passed by reference (meaning bu that "no copy is created"
In the function upper_fortran, the line

character(len=len(in),kind=c_char) :: out​

creates memory for the returning "string"
this string is returned by reference to the python

No. Handwaving a bit on the Python side...

  • Python creates an object in memory for the byte string b'Hello world', references that object in the internals of a c_char_p object and binds a reference to that c_char_p object to the name `in_ptr`. Note that Python requires the byte string object to be immutable. The c_char_p object will stay around as long as there is at least one reference to it (the in_ptr name being such a reference), and the byte string object will similarly stay around as long as there is at least one reference to it.
  • As a result of the call to create_string_buffer, Python creates an "managing" object that in turn allocates 11 bytes of arbitrary memory (length of the Hello World byte string - but this will be used to get the output from the Fortran code), and binds a reference to that managing object to the name out_ptr. This 11 bytes of arbitrary memory is mutable, and it will stay around as long as there is at least one reference to the managing object.
  • Python passes the address of the start of the storage for the b'Hello World' byte string, the length of the byte string and the address of start of the arbitrary 11 bytes of memory.
  • The Fortran code associates Fortran objects with the two addresses, and does its magic, creating an upper case version of the characters originally in the byte string in the arbitrary memory storage. Beyond internal temporary storage that the Fortran compiler manages itself, the Fortran code does not allocate any memory - it just uses storage already set up by the Python code.
  • Python displays the contents in the 11 bytes of arbitrary memory, showing the modifications made by the Fortran code.

(Some time later... ordering will depend on what you subsequently do...)

  • The in_str name in Python goes out of scope, is explicitly unbound using `del` or is bound to something else. If no further references to the previously bound c_char_p object exist, then Python will [eventually] delete it, if no other references exist to the byte string, Python will [eventually] delete that.
  • The out_str name in Python goes out of scope, is explicitly unbound using `del` or is bound to something else... the managing object for the 11 bytes of memory is [eventually] deleted, as part of its deletion it deallocates the arbitrary 11 bytes of memory that is has been managing.

(Note that the potential for the object managing the memory buffer arising from create_string_buffer to be deleted (and hence the memory to be freed) when the name formerly bound to that object is bound to something else, may result in problems with FortranFan's approach.)

Also, is it possible to in your upper_python subroutine not to have the out_ptr, but just have the in_ptr, in an "inout" fashion ? It obviously is, sorry.

Yes, but don't modify things that Python expects to be unmodifiable (immutable).

0 Kudos
MattHouston
New Contributor I
3,325 Views

(Forum also ate my reply, it is really boring ... Now, by out of angst, I will have to copy paste my replies and questions in a notepad, in case of forum eating them ...)

 

Thank you very much for your answer, IanH.

 

Regarding the missing matching deallocate you are perfectly right. I intented to make it right after the 

call f_c_pointer(fptr, cptrres, [STRLEN])

I was dreaming about. But even there, it does not feel right, doesn't it ?

Regarding the standard :

F2018.18.2.3.3.JPG

Obviously were not in the case (ii). Also, we are a not in the case (i) as I guess that an "interoperable data entity" is irst a Fortran entity, which is not the case here as we pass a Python object to Fortran. Hence by elimination we are in the case (ii). Correct ?

 

Now, about case (iii) of F2018 18.2.3.3 :

 

"If the value of CPTR is the C address of a storage sequence that is not in use by
any other Fortran entity, FPTR becomes associated with that storage sequence.
If FPTR is an array, its shape is specified by SHAPE and each lower bound
is 1. The storage sequence shall be large enough to contain the target object
described by FPTR and shall satisfy any other processor-dependent requirement
for association."

 

I understand that there is no problem at all, so that I don't get your "case (iii) of F2018 18.2.3.3p3 probably lets us get away with this, perhaps in a processor dependent fashion".

 

Could you please consider developing on your "c_f_pointer-associate-cptr-with-a-len(1)-array-then-argument-associate-the-resulting-array-with-a-len(x)-scalar-using-sequence-association" trick ? By the way, I am quite ignorant of classical idioms/patterns/tricks (like the one you refer to, or like the opaque pointer trick I learned about this night) so that if you have reference(s) regarding this, I would be happy.

 

On the memory aspect of your code, am I right to summerize it as follows :

  • python allocates memory for b'Hello World' and a pointer pointing to (the beginning of) it
  • this is passed by reference (meaning bu that "no copy is created"
  • In the function upper_fortran, the line 
    character(len=len(in),kind=c_char) :: out
    creates memory for the returning "string"
  • this string is returned by reference to the python

?

 

Also, is it possible to in your upper_python subroutine not to have the out_ptr, but just have the in_ptr, in an "inout" fashion ?

0 Kudos
FortranFan
Honored Contributor II
3,418 Views

@MattHouston ,

The description by @IanH and the example provided is generally the way to go for safe programming with Fortran, particularly in mixed-language solutions.

As you have noted the interoperability of Python using ctypes is with C and as you know, the language standard for Fortran too follows the interoperability with a C companion processor.  Given this, it's often the case C programming idioms and style come into the mix.  Starting with the seminal work by Kernighan and Ritchie, the lessons and examples imparted widely with C programs do tend to lean toward heavy use of pointers and a function to upper case a string might be written as below where the char case conversion is in situ and no copying is involved:

 

char *strupr(char s[])
{
  char	*p;
  for (p = s; *p; ++p)
    *p = toupper(*p);
  return(s);
}

 

So now, if what you are trying is influenced by such an approach and you do think you need to provide such functions in Fortran for consumption on the Python side, then caveat emptor with a Fortran snippet below!

 

module Fdll_m

   use, intrinsic :: iso_c_binding, only : c_size_t, c_char, c_ptr, c_null_ptr, c_loc, c_f_pointer

contains

   function to_upper(s, lens) result(sptr) bind(C, name="to_upper")
      ! Argument list
      character(kind=c_char,len=1), intent(in), target :: s(*)
      integer(c_size_t), intent(in), value             :: lens
      ! Function result
      type(c_ptr) :: sptr

      sptr = c_null_ptr
      if ( lens > 0 ) then
         sptr = c_loc(s)
         block
            character(kind=c_char,len=lens), pointer :: str
            integer :: I, K
            integer, parameter :: CASE_OFFSET = iachar('a') - iachar('A')
            call c_f_pointer( cptr=sptr, fptr=str )
            do I = 1, lens
               K = iachar( str(I:I) )
               if ( K >= iachar('a') .and. K <= iachar('z') ) then
                  K = K - CASE_OFFSET
                  str(I:I) = achar(K)
               end if
            end do
         end block
      end if 
   end function
    
end module Fdll_m

 

where a basic aspect of safety and convenience is brought in by including a function parameter toward length of the string (c.f. the message by @Steve_Lionel you referenced) but otherwise it follows in rather verbose Fortrannic fashion the style of C of a "long rope to shoot oneself in the foot".

Assuming the above Fortran snippet is compiled using /libs:static and the resultant DLL is on one's Windows OS PATH (e.g., in "C:\xx\yy\bin" folder where one may place one shared library objects and which is specified first/earlier on in the environment settings), the function can be consumed in Python like so:

 

import ctypes
# Load the Fortran DLL; ensure it's on the PATH
Fdll = ctypes.CDLL('Fdll.dll')
# Specify the interface toward the Fortran function
Fdll.to_upper.restype=ctypes.c_char_p
Fdll.to_upper.argtypes=[ctypes.c_char_p, ctypes.c_size_t]
# Create a "mutable" ctypes string buffer
s = ctypes.create_string_buffer(b"modern fortran",15)
# Invoke the Fortran function
s = Fdll.to_upper(s, len(s))
# Output the modified "string"
print(s)

 

Running above, the output produced is

hw.png

0 Kudos
Reply