Correctly calling qsort from C

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?

1 Like

I believe adding bind(C) to my_derived_type would allow adding bind(C) to stringcompare, and would thus be standard conforming. My guess is that gfortran is nice enough to lay things out in such a way that it works anyways, but it may not strictly be guaranteed.

In your case there may be reasons you can’t add bind(C) to your type, which would make my suggestion irrelevant, but since nothing is actually going to look at what’s being passed through on he C side, I wouldn’t see any reason it shouldn’t work in most cases. I’m curious to see what others have to say.

Just now I tried making my_derived_type interoperable, by changing start of the type declaration to:

    type, bind(C) :: my_derived_type
   

This causes gfortran to throw a compile error due to the allocatable character s:

    6 |     type, bind(C) :: my_derived_type
      |                                    2  
    7 |         ! This string will be used for sorting
    8 |         character(:), allocatable :: s
      |                                      1
Error: Component ‘s’ at (1) cannot have the ALLOCATABLE attribute because it is a member of the BIND(C) derived type ‘my_derived_type’ at (2)

Using ifort also results in a similar error in this case.

sorting_experiments_small.f90(8): warning #8753: A CHARACTER component of an interoperable derived type must have length 1.   [S]
        character(:), allocatable :: s
-------------------------------------^
sorting_experiments_small.f90(8): error #8080: Each component of a derived type with the BIND attribute shall be a nonpointer, nonallocatable data component with interoperable type and type parameters.   [S]
        character(:), allocatable :: s

An alternative that might solve the issue in general (?) is to make stringcompare take c_ptr as arguments, and then do type-casting in the function. This enables stringcompare to have the bind(C) attribute, even though my_derived_type is not interoperable.

     ! String comparison function for sorting.
    integer(c_int) function stringcompare(s1, s2) bind(C)
        !type(my_derived_type) :: s1, s2
        type(c_ptr), value :: s1, s2
        type(my_derived_type), pointer :: t1, t2

        call c_f_pointer(s1, t1)
        call c_f_pointer(s2, t2)

        if(t1%s <  t2%s) stringcompare = -1_c_int
        if(t1%s == t2%s) stringcompare = 0_c_int
        if(t1%s >  t2%s) stringcompare = 1_c_int
    end function stringcompare

With this change it works with gfortran and ifort (although the initial version does as well).

Does the above make for a “general” approach to sorting in Fortran with a user-defined comparison function? My interest stems from related discussions about possible sorting routines for stdlib here and here.

1 Like

What I do is declaring the interface for type(c_ptr) and converting those pointers to Fortran pointers inside. Not sure if it is any better, but the procedure is bind(C).

  function CompareWMPoints(Aptr,Bptr) bind(C,name="CompareWMPoints") result(res)
    use iso_c_binding
    integer(c_int)         :: res
    type(c_ptr), value :: Aptr, Bptr
    type(WMPoint), pointer  :: A, B

    call c_f_pointer(Aptr,A)
    call c_f_pointer(Bptr,B)

    if ...
    end if

  end function CompareWMPoints

@gareth,

The prototype for the compare function parameter for qsort is

int (*compar)(const void *, const void *)

and given this, the Fortran function interface shall indeed be type(c_ptr), intent(in), value. So it’s not an alternative, it’s the approach to be taken…

Would f2018’s type(*) be appropriate here? IIRC, it’s main intended use is for interoperating with void * in C interfaces.

Just curious why you need to use the C qsort when there are
several Fortran implementations you could use. A nice
modern Fortran implementation that can be easily modified
to sort derived types is given in Chapter 6 of Hanson and Hopkins
book Numerical Computing with Modern Fortran, SIAM 2013.
The source code can be downloaded at:
https://archive.siam.org/books/ot134/

No, 'type(*) is inappropriate under the circumstances here because the compar function in Fortran needs to do something useful i.e., compare the two elements.

With the Fortran 2018 feature of type(*), there are very limited things one can do with it, basically invoke some intrinsic inquiry functions and that’s about it.

type(*) offers a certain sense of generic metaprogramming capability when the data reference is to be sent to the C companion processor toward some operations, mostly type-agnostic, on the data using that processor.

Thanks for the pointer. I don’t have that book so may be misunderstanding, but from the code, I got the impression that use of this approach was relatively verbose compared to using qsort_C? It appears one needs to define a derived type that inherits from their base class, and then also define quite a few type bound procedures for that type?

For the qsort_C approach, one just needs to define a comparison function (like stringcompare). The one can call qsort_C while applying all the appropriate c-interoperability functions to the arguments (c_loc, c_funloc, and so on). While certainly not elegant, my impression was that it’s quite a bit less code?

If anyone is aware of a Fortran approach that can treat an array of any derived type, with a similar amount of user-code as in the qsort_C approach, then I would be most interested.

When possible I sort derived types by converting them to REALs and sorting those. For example a date type (month,day,year) can be converted a Julian day. Rosetta code shows how to Sort using a custom comparator in Fortran. Here is the code, pasting a needed function, fixing the array of strings constructor, and making a few small other changes:

module sorts_with_custom_comparator
  implicit none
contains
  subroutine a_sort(a, cc)
    character(len=*), dimension(:), intent(inout) :: a
    interface
       integer function cc(a, b)
         character(len=*), intent(in) :: a, b
       end function cc
    end interface
 
    integer :: i, j, increment
    character(len=max(len(a), 10)) :: temp
 
    increment = size(a) / 2
    do while ( increment > 0 )
       do i = increment+1, size(a)
          j = i
          temp = a(i)
          do while ( j >= increment+1 .and. cc(a(j-increment), temp) > 0)
             a(j) = a(j-increment)
             j = j - increment
          end do
          a(j) = temp
       end do
       if ( increment == 2 ) then
          increment = 1
       else
          increment = increment * 5 / 11
       end if
    end do
  end subroutine a_sort
end module sorts_with_custom_comparator
! Then we have to put our custom comparator in a module (to_lower is defined here):

module comparators
  implicit none
contains
   subroutine To_lower(str)
     character(*), intent(in out) :: str
     integer :: i
 
     do i = 1, len(str)
       select case(str(i:i))
         case("A":"Z")
           str(i:i) = achar(iachar(str(i:i))+32)
       end select
     end do  
   end subroutine To_Lower
!
  integer function my_compare(a, b)
    character(len=*), intent(in) :: a, b
 
    character(len=max(len(a),len(b))) :: a1, b1
 
    a1 = a
    b1 = b
    call to_lower(b1)
    call to_lower(a1)
 
    if ( len(trim(a)) > len(trim(b)) ) then
       my_compare = -1
    elseif ( len(trim(a)) == len(trim(b)) ) then
       if ( a1 > b1 ) then
          my_compare = 1
       else
          my_compare = -1
       end if
    else
       my_compare = 1
    end if
  end function my_compare
end module comparators
! At the end, we can test these:

program CustomComparator
  use comparators, only: my_compare
  use sorts_with_custom_comparator, only: a_sort
  implicit none
  character(len=100), dimension(8) :: str
  integer :: i
  str = ["this   ", "is     ", "an     ", "array  ", "of     ", "strings", "to     ", "sort   "]
  call a_sort(str, my_compare)
  do i = 1, size(str)
     print *, trim(str(i))
  end do
end program CustomComparator

It gives output

 strings
 array
 sort
 this
 an
 is
 of
 to

which

sort[s] an array (or list) of strings in order of descending length, and in ascending lexicographic order for strings of equal length.

The Fortran Wiki has a relevant qsort_inline code.

It is just damn quick and simple, that’s all. And the qsort function is available everywhere. No doubt there are good sorting modules in Fortran, but why bother for some quick and dirty sorting?

Even for the the link you gave you say “can be modified”. You can just call qsort from the standard library without any modification.

1 Like

With processors supporting Fortran 2018 and later revisions, the above will not apply. Fortran 2018 standard states in its Introduction, “The argument to C_FUNLOC can be a noninteroperable procedure.”

1 Like

No, you do not need the structure to be interoperable. My structures are not. Just pass the pointer instead. It may not be completely strictly F2008 conforming, but nothing bad will happen. Just use what I showed above and even older compiler versions will not complain


  interface
    subroutine qsort(array,elem_count,elem_size,compare) bind(C,name="qsort")
      import
      type(c_ptr),value       :: array
      integer(c_size_t),value :: elem_count
      integer(c_size_t),value :: elem_size
      type(c_funptr),value    :: compare !int(*compare)(const void *, const void *)
    end subroutine qsort !standard C library qsort
  end interface
function CompareWMPoints(Aptr,Bptr) bind(C,name="CompareWMPoints") result(res)
    use iso_c_binding
    integer(c_int)         :: res
    type(c_ptr),value :: Aptr,Bptr
    type(WMPoint),pointer  :: A,B

    call c_f_pointer(Aptr,A)
    call c_f_pointer(Bptr,B)

    if ((A%xi+(A%yj-1)*Prnx+(A%zk-1)*Prnx*Prny) < (B%xi+(B%yj-1)*Prnx+(B%zk-1)*Prnx*Prny)) then
      res = -1_c_int
...
  call qsort(c_loc(WMPoints(1)), &
             size(WMPoints,kind = c_size_t), &
             storage_size(WMPoints,c_size_t)/storage_size(c_char_'a',c_size_t), 
             c_funloc(CompareWMPoints))

@VladimirF I agree the approach you present here is correct (see also posts 4-6 in this thread). I also think it is standard conforming, because your comparison-function has arguments of type c_ptr, so it can be interoperable (with bind(C, ....)), and it also conforms with the interface that the C-language requires of qsort (where the function arguments are const void *).

That did not hold for the original (incorrect) approach in this thread. Your approach is right.

@FortranFan - thanks for pointing out that C_FUNLOC no longer needs an interoperable procedure as an argument (since the Fortran 2018 standard). I understand that the original code is anyway invalid (??), because the comparison function does not have input arguments of type const void * as required on the C side.

If C_FUNLOC allows noninteroperable procedures, then it might be easier to pass around procedures in mixed language code (e.g. procedure defined in Fortran, passed to C without calling, and passed back to Fortran). But is it right that one cannot actually call a non-interoperable procedure on the C side?

@gareth,

Please note the relevant aspect here is standard conformance and how it can help with consistency and portability across standard-conforming processors rather than being “invalid”, or “not right”, etc.

Re: " understand that the original code is anyway invalid (??), " as posted upthread a while ago the use of type(c_ptr), intent(in), value is consistent with the C function prototype (with const void *) as well as the Fortran standard whereas what is shown in the original post is likely processor-dependent.

Re: “is it right that one cannot actually call a non-interoperable procedure on the C side?,” again one can successfully invoke such a function on the C side on some or many processors and it has been done for a long time, the question will be whether is interest in a conformant approach.