I sometimes use C’s qsort to do sorting in Fortran, but am uncertain whether I’m doing it in a standard-conforming way.
In the example below I create an example derived type my_derived_type
containing an allocatable string and some (unused) other stuff. Then I define a function stringcompare
that behaves like the comparison function required of C’s qsort
, and use it to sort an array of type my_derived_type
, based on its string values.
The example compiles and runs correctly with gfortran, and I’ve successfully used this approach in elsewhere.
module sorting_example_mod
use iso_c_binding
implicit none
! An example derived type
type my_derived_type
! This string will be used for sorting
character(:), allocatable :: s
! The following variables are unused (but emulate the complexity of a derived type)
integer :: a=1, b=2, c=3
real :: x(10)
real, allocatable :: z(:,:)
end type
! Enable calling C's qsort
interface
subroutine qsort_C(array, elem_count, elem_size, comparison_fun) bind(C,name="qsort")
use iso_c_binding, only: c_ptr, c_size_t, c_funptr
implicit none
type(c_ptr), value :: array ! C-pointer to the first entry of the array
integer(c_size_t), value :: elem_count ! Number of elements in the array
integer(c_size_t), value :: elem_size ! Size of each element, according to c_sizeof()
type(c_funptr), value :: comparison_fun ! c_funptr to the user-provided comparison function
end subroutine qsort_C
end interface
contains
! String comparison function for sorting.
! This cannot be bind(C) because s1,s2 are not of interoperable type. Does that matter?
integer(c_int) function stringcompare(s1, s2) ! bind(C) ! Fails because my_derived_type is not interoperable
type(my_derived_type) :: s1, s2
if(s1%s < s2%s) stringcompare = -1_c_int
if(s1%s == s2%s) stringcompare = 0_c_int
if(s1%s > s2%s) stringcompare = 1_c_int
end function stringcompare
end module
program test_sorting_my_derived_type
use iso_c_binding
use sorting_example_mod
integer :: i
integer, parameter :: BITS_IN_BYTE = 8 ! To convert storage_size() to bytes
type(my_derived_type), target:: t1(5)
! Strings to put in t1%s
character(len=20) :: t1_strings(5) = [character(len=20) :: 'bc', 'abc', 'gh?', 'bcd', 'cd']
! Set strings in t1
do i = 1, size(t1_strings)
t1(i)%s = trim(t1_strings(i))
end do
! Print the pre-sorted strings
write(*, '(A20,A5,A20)') 'Before sorting t1: ', 'i', 't1(i)%s '
do i = 1, size(t1)
write(*, '(A20,I5,A20)') ' ', i, t1(i)%s
end do
print*, ''
! Do the sort
call qsort_C(c_loc(t1(1)), &
elem_count = size(t1, kind=c_size_t), &
elem_size = int(storage_size(t1(1))/BITS_IN_BYTE, kind=c_size_t), &
comparison_fun = c_funloc(stringcompare))
! Print the post-sorted strings
write(*, '(A20,A5,A20)') 'After sorting t1: ', 'i', 't1(i)%s '
do i = 1, size(t1)
write(*, '(A20,I5,A20)') ' ', i, t1(i)%s
end do
end program
If I put the above in a file sorting_experiments_small.f90
then it compiles and runs successfully with:
gfortran sorting_experiments_small.f90
./a.out
Before sorting t1: i t1(i)%s
1 bc
2 abc
3 gh?
4 bcd
5 cd
After sorting t1: i t1(i)%s
1 abc
2 bc
3 bcd
4 cd
5 gh?
While that looks OK, I’m questioning whether it is standard conforming because to call qsort_C
I need to pass the c_funloc
of stringcompare
. From the gfortran online manual I understand this requires that stringcompare
be interoperable. However I cannot add the bind(C)
attribute to that function because my_derived_type
is not interoperable.
Given that it works, I’m wondering whether that is fortuitous and/or what the right approach is?