Fastest sorting for a specific genre of unordered numbers

Counter to what I expected, it’s perfectly feasible. Even more surprisingly, host association in internal functions permits using qsort for indirect sorting, which is not possible in pure C without the use of global variables.

Here’s a demonstration:

module sorting
   use, intrinsic :: iso_c_binding
   implicit none
   private
   public :: argsort
contains

   !> Returns the indices that would sort an array
   !>
   !> Arguments:
   !>   n: number of elements
   !>   list: on entry, list of indices 1..(1)..n 
   !>           (for reverse sort, n..(-1)..1)
   !>         on return, the indices such that keys(list) would be sorted
   !>   keys: array to be sorted
   !>
   subroutine argsort(n,list,keys)
      integer, intent(in) :: n
      integer, intent(inout), target :: list(*)
      integer, intent(in) :: keys(*)

      interface
         subroutine qsort(ptr,count,size,comp) bind(c,name="qsort")
            import c_ptr, c_int, c_size_t, c_funptr
            implicit none
            type(c_ptr), intent(in), value :: ptr
               !> pointer to the array to sort
            integer(c_size_t), intent(in), value :: count
               !> number of elements in the array
            integer(c_size_t), intent(in), value :: size
               !> size of each element in the array in bytes
            type(c_funptr), intent(in), value :: comp
               !> comparison function which returns ​a negative integer value 
               !> if the first argument is less than the second, a positive 
               !> integer value if the first argument is greater than the 
               !> second and zero if the arguments are equivalent
         end subroutine
      end interface

      if (n < 2) 
         ! list already sorted
         return
      end if

      call qsort(c_loc(list),int(n,c_size_t),c_sizeof(list(1)), &
         c_funloc(argsort_compare))

   contains
      ! technically, the inputs should be void pointers
      ! but works nevertheless
      integer(c_int) function argsort_compare(a,b) bind(c)
         integer(c_int), intent(in) :: a, b
         argsort_compare = keys(a) - keys(b)
      end function
   end subroutine
end module

program main

   use sorting
   implicit none

   integer :: list(4)
   integer :: keys(4)

   list = [1,2,3,4]
   keys = [7,5,6,3]

   call argsort(4,list,keys)

   ! Supposed to print [ 3, 5, 6, 7]
   print *, keys(list)

end program

Notice the comparison function is encoded in Fortran. So the conclusion in my previous post is curiously enough - wrong. You can perform an indirect sort using qsort without global variables from Fortran. :exploding_head:

Further, we could give argsort the bind(c) attribute, making it a callable from C again. Using Fortran to bypass restrictions of C would make an interesting addition to the Wikipedia entry on qsort.

2 Likes