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

QSort - works only if disregarding advice in documentation

Uwe_H_
Beginner
1,186 Views

I need to sort an array of custom-type elements. I thought qsort might be a good tool for that. To get started I ignored all advice given in the qsort-documentation (https://software.intel.com/en-us/node/679798): I did _not_ provide an Interface for qsort specific to my type. I did _not_ "USE IFPORT". I did _not_ declare the compare function  "external" (but everything is in the same module). I tried it out and found it works nicely!

But because of the warnings in the documentation I´m worried that this may be unsafe, so I started changing it to the recommended way: put in "USE IFPORT" (at module Level), added an Interface (using !DIR$ ATTRIBUTES ALIAS:'qsort' with no underscore as this is 64 bit), moved the compare function out of the module and declared it "external". Now when the compare function is called the first time the second argument is invalid.

It´s interesting that in the sample given in the documentation it says:
! Passing "element_type" objects, it's called first with the pair (1, <invalid>),
! and the second item has a address well before the beginning of "C".
and further down:
! SEGV on access to C2

I wondered about this before changing my implementation, now it suddenly makes sense!

Finally I tested the sample code given (using 32 bit), and it fails in the same way!

Now my question is: What is the safe/recommended way to sort my custom-type array?

My Compiler Version is 17.0.0.109 on VS/Windows.

Thanks!

0 Kudos
14 Replies
andrew_4619
Honored Contributor II
1,186 Views

It would make sense to post a sample set code that you believe conforms to the documentation that demonstrates the failure. Otherwise there is not that much to go other than forum users making many guesses as to what is going wrong. 

0 Kudos
Uwe_H_
Beginner
1,186 Views

Hi Andrew,

sorry I did not make this clear enough: The failing sample is in the documentation of qsort which can be found here: https://software.intel.com/en-us/node/679798

thanks
Uwe

0 Kudos
andrew_4619
Honored Contributor II
1,186 Views

Ah OK. Yes I agree the example fails. The QSort does not correctly pass the second arg into the sort function OrderCharCI(c1, c2),  c2  is undefined at the first call and then it crashes when c2 is touched..

0 Kudos
andrew_4619
Honored Contributor II
1,186 Views

I think the fortran qsort needs looking at ...... You could use the Clib version e.g.

module share_type
  use iso_c_binding
  implicit none 
  
  interface
    subroutine qsort(array, elem_count, elem_size, compare) bind(C,name="qsort") !standard C library 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 
  end interface
  
  type element_type 
        integer       :: data
        character(10) :: key
  end type 
  
  contains
  function OrderCharCI(c1, c2) Bind(C)
    use iso_c_binding
    implicit none

    type(element_type), intent(in) :: c1 ! Character strings to be ordered.
    type(element_type), intent(in) :: c2 !

    ! Function result:
    !
    integer(c_int) :: OrderCharCI

    ! Locals:
    !
    character(10) :: c1L !} Local copies of c1 and c2.
    character(10) :: c2L !}

    integer :: i ! Loop index.

    write(*,*)'OrderCharCI, parameter C1 is "', c1%key, '" ', c1%data, ', len is ', len(c1%key)
    write(*,*)' len_trim is ', len_trim(c1%key)
    write(*,*) ' '
    
    ! SEGV on access to C2
    !
    write(*,*)'OrderCharCI, parameter C2 is "', c2%key, '" ', c2%data, ', len is ', len(c2%key)
    write(*,*)' len_trim is ', len_trim(c2%key)
    write(*,*) ' '
    c1L = c1%key
    c2L = c2%key

    write(*,*) 'about to start do loop'

    do i = 1, len_trim(C1L)
        if ('a' <= C1L(i:i) .and. c1L(i:i) <= 'z') c1L(i:i) = char(ichar(c1L(i:i)) - ichar('a') + ichar('A'))
    end do
    do i = 1, len_trim(C2L)
        if ('a' <= c2L(i:i) .and. c2L(i:i) <= 'z') c2L(i:i) = char(ichar(c2L(i:i)) - ichar('a') + ichar('A'))
    end do
    if (c1L == c2L) Then
        OrderCharCI = 0
        write(*,*) ' - equal'
    else if (c1L < c2L) Then
        OrderCharCI = -1
        write(*,*) ' - c1 is less'
    else
        OrderCharCI = 1
        write(*,*) ' - c1 is more'
    end if
end function OrderCharCI
  
  
end module share_type


program main

    use share_type
    implicit none
    type(element_type), target        :: c(7)
    integer                           :: i

    c(1)%key  = 'aisjdop'
    c(1)%data = 3
    c(2)%key  = '35djf2'
    c(2)%data = 1
    c(3)%key  = 'ss:ss'
    c(3)%data = 6
    c(4)%key  = 'MMhQQ'
    c(4)%data = 4
    c(5)%key  = 'mmHqq'
    c(5)%data = 5
    c(6)%key  = 'aaaa'
    c(6)%data = 2
    c(7)%key  = '["\/'
    c(7)%data = 7

    call qsort( c_loc(c(1)), int(size(c), c_size_t), C_sizeof(c(1)), c_funloc(OrderCharCI) )
    
    write(*,*) 'Sorted "C" is '
    do i = 1, size(c)
         write(*,*) ' "', c(i)%key, '" value ', c(i)%data
    end do 
end program main

 

0 Kudos
Kevin_D_Intel
Employee
1,186 Views

Thank you. We'll investigate shortly.

0 Kudos
Uwe_H_
Beginner
1,186 Views

Is there any update on this?

0 Kudos
mecej4
Honored Contributor III
1,186 Views

There is something out of plumb here. If I take the QSORT example that Uwe referred to, namely, the first example code at https://software.intel.com/en-us/node/679798, I run into an access violation. By chance/curiosity, I changed the alias from '_qsort' to '_QSORT' in the !DIR$ line, and found that with this modification the program runs correctly when I use the following compiler:

     Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on IA-32, Version 17.0.4.210 Build 20170411

Unfortunately, this did not work with the 64-bit version of the 17.0.4.210 compiler.

A little probing with map files shows us why changing to _QSORT works in 32-bits. When the !DIR$ line specifies _QSORT, the map file shows:

 0001:0000313e       _QSORT                     0040413e f   libifportmd:libifportMD.dll
 0003:00000120       __imp__QSORT               00406120     libifportmd:libifportMD.dll

On the other hand, when the !DIR$ line specifies _qsort, the map files shows

 0001:00003c6a       _qsort                     00404c6a f   ucrt:api-ms-win-crt-utility-l1-1-0.dll
 0003:000000f8       __imp__qsort               004060f8     ucrt:api-ms-win-crt-utility-l1-1-0.dll

Note that _QSORT is in the Fortran RTL, whereas _qsort is in the Visual C RTL; the Fortran and C routines are not interchangeable. In fact, there are comments in the example code cautioning us about this issue!

0 Kudos
mecej4
Honored Contributor III
1,186 Views

Experimenting further with the 64-bit compiler shows that the second (LEN) and third (ISIZE) arguments to QSORT should be 64-bit integers. Here is the modified code. Note that the DIR$ALIAS line is different for 32 and 64 bit targets. The changes are in lines with "X64" in comments. Since the 64-bit compiler defines _WIN64 and the 32-bit compiler does not, this modified code should work for 32- and 64-bit targets.

! program showing how to call 'QSORT' on
! a user-defined type.
!
! Define the type to be shared.
!
module share_type
    type element_type
        integer       :: data
        character(10) :: key
    end type
end module

! Main program calls QSORT.
!
program main
    use IFPORT       ! To get QSORT
    use share_type   ! To get shared type

    ! Define an overload of the default QSORT signature
    ! with a signature using the shared type.
    !
    interface
        subroutine QSORT_element_types(array, len, isize, comp)
           use ifport
           use share_type
           type(element_type) array(len)
           integer(SIZEOF_SIZE_T) len, isize                              ! --->>> for X64
           integer(2), external :: comp
           !
           ! Hook the overload to the real thing but be careful
           ! to connect to the correct qsort: the Fortran one, not
           ! the C one!
           !
           ! We need to call the _Fortran_ qsort, not the _C_ one, or
           ! there will be errors from the 1-origin vs. 0-origin indexing
           ! and the row-major vs. column-major ordering.
           !
           ! The symptom is that "OrderCharCI" is called with pointer values
           ! which are outside the bounds of the array to be sorted.
           !
		   !DIR$ IF  DEFINED(_WIN64) 
           !DIR$ ATTRIBUTES ALIAS:'QSORT' :: QSORT_element_types          ! --->>> for X64
		   !DIR$ ELSE
           !DIR$ ATTRIBUTES ALIAS:'_QSORT' :: QSORT_element_types         ! --->>> for IA32
		   !DIR$ ENDIF
        end subroutine QSORT_element_types
    end interface

    type(element_type) :: c(7)

    integer(2), external :: OrderCharCI

    integer(SIZEOF_SIZE_T) :: size_of_element, size_of_array             ! --->>> for X64
    ! Fill in the array to be sorted.  The data value is chosen so
    ! that the sorted array will have the values in numeric order.
    ! Thus we can check the result of the sort.
    !
    c(1)%key  = 'aisjdop'
    c(1)%data = 3
    c(2)%key  = '35djf2'
    c(2)%data = 1
    c(3)%key  = 'ss:ss'
    c(3)%data = 6
    c(4)%key  = 'MMhQQ'
    c(4)%data = 4
    c(5)%key  = 'mmHqq'
    c(5)%data = 5
    c(6)%key  = 'aaaa'
    c(6)%data = 2
    c(7)%key  = '["\/'
    c(7)%data = 7

    size_of_array   = size(c)         !  7
    size_of_element = sizeof(c(1))    ! 16

    write(*,*) '"C" is:'
    do i = 1, 7
        write(*,*) ' "', c(i)%key, '" value ', c(i)%data
    end do

    write(*,*) ' '
    write(*,*) 'size of C is            ', size_of_array, ' elements'
    write(*,*) 'size of element C(1) is ', size_of_element, ' bytes'
    write(*,*) 'len of key in C(1) is   ',   len(c(1)%key)
    write(*,*) ' '

    ! Call the overloaded QSORT routine.
    !
    Call QSort_element_types(C, size_of_array, size_of_element, OrderCharCI)

    write(*,*) 'Sorted "C" is '
    do i = 1, 7
         write(*,*) ' "', c(i)%key, '" value ', c(i)%data
    end do

end program main

! Computes order of character strings using a case insensitive ordering.
!
! Return -1 if C1 before C2, 0 if C1 = C2, and 1 if C1 after C2.
!
! Called first with the pair (2,3), then (1,2), then (1,3)...when passing
! character strings of length 10.
!
! Passing "element_type" objects, it's called first with the pair (1, <invalid>),
! and the second item has a address well before the beginning of "C".
!

function OrderCharCI(c1, c2)
    use share_type

    implicit none

    type(element_type), intent(in) :: c1 ! Character strings to be ordered.
    type(element_type), intent(in) :: c2 !

    ! Function result:
    !
    integer(2) :: OrderCharCI

    ! Locals:
    !
    character(10) :: c1L !} Local copies of c1 and c2.
    character(10) :: c2L !}

    integer :: i ! Loop index.

    write(*,*)'OrderCharCI, parameter C1 is "', c1%key, '" ', c1%data, ', len is ', len(c1%key)
    write(*,*)' len_trim is ', len_trim(c1%key)
    write(*,*) ' '
    
    ! SEGV on access to C2
    !
    write(*,*)'OrderCharCI, parameter C2 is "', c2%key, '" ', c2%data, ', len is ', len(c2%key)
    write(*,*)' len_trim is ', len_trim(c2%key)
    write(*,*) ' '
    c1L = c1%key
    c2L = c2%key

    write(*,*) 'about to start do loop'

    do i = 1, len_trim(C1L)
        if ('a' <= C1L(i:i) .and. c1L(i:i) <= 'z') c1L(i:i) = char(ichar(c1L(i:i)) - ichar('a') + ichar('A'))
    end do
    do i = 1, len_trim(C2L)
        if ('a' <= c2L(i:i) .and. c2L(i:i) <= 'z') c2L(i:i) = char(ichar(c2L(i:i)) - ichar('a') + ichar('A'))
    end do
    if (c1L == c2L) Then
        OrderCharCI = 0
        write(*,*) ' - equal'
    else if (c1L < c2L) Then
        OrderCharCI = -1
        write(*,*) ' - c1 is less'
    else
        OrderCharCI = 1
        write(*,*) ' - c1 is more'
    end if
end function OrderCharCI

The whole thing boils down, in retrospect, to documentation errors. In particular, the sample codes should declare the type of the second and third arguments to QSORT to be SIZEOF_SIZE_T instead of INTEGER. This is already done correctly in the second QSORT example code, and the same type should be used in the first QSORT example code. The use of the macro _WIN64 to pick the correct name decoration needs to be shown in the !DIR$ ALIAS line.

Using the corrected documentation, one should be able to enjoy the benefits of checking that the correct interfaces are used. 

The 64-bit version of QSORT is no longer compatible, in respect to calling sequence, with the QSORT from CVF and 32-bit IFORT. Why persist, then, with INTEGER*2 for the type of the comparison function? Could we let it be default integer in type? 

0 Kudos
Uwe_H_
Beginner
1,186 Views

Thanks mecej4 for this clarification. It seems to make a lot of sense. So I will also try to dig a bit and find out which qsort version is actually being used by my current code (without any Interface etc.) and then probably change it to the suggested way, including size_t etc.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,186 Views

>>including size_t

A minor picking point, Fortran does not have UNSIGNED INTEGER types. For grammatically correct syntax, use C_INTPTR_T

Jim Dempsey

0 Kudos
Uwe_H_
Beginner
1,186 Views

Thanks Jim, definitely a good idea to really get the types right. I just wonder if these two differ at all, in the debugger they both evaluate to 4 on 32bit and 8 on 64bit. And I think the integer is still signed, which makes me wonder what happens when you pass in a C size_t value outside the signed range, if it appears as a negative value and you´d be on your own to figure out what to do with it. I haven´t tried it though.

I think that the main issue that kept me from getting the example to work was that I stuck with the lower case 'qsort' in !DIR$ ATTRIBUTES ALIAS. I guess that always causes the C function to be called instead of the Fortran one.
I see now that in my very first "simplistic" approach _without_ defining an interface, and _without_ using IFPORT I still end up using the Fortran QSORT (telling from the call stack). If I do then just add "use IFPORT" the linker complains that "There is no matching specific subroutine for this generic subroutine call.   [QSORT]". This makes sense, because I use a custom type array. Not sure why it works without "USE IFPORT", but I don´t care too much either.
I´m now using the implementation as outlined in the samples with the suggested corrections, plus I now have the confidence this is the "proper"/safe way to do it, so thanks for the advice!

0 Kudos
Steve_Lionel
Honored Contributor III
1,186 Views

C_SIZE_T is the best choice for the kind of the passed character size. In most implementations this would be the same as C_INTPTR_T, but not everywhere.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,186 Views

Steve,

C_SIZE_T could only differ from C_INTPTR_T on a Harvard architecture machine (instruction memory separated from data memory).

The "correct" value to use is the one defined in the API.

All this said, I would agree C_SIZE_T should be used in cases where a "struct" is passed containing a C-side size_t variable...
... with the provision that the Fortran programmer takes care to perform unsigned integer math when manipulating these variables.

Jim Dempsey

0 Kudos
Devorah_H_Intel
Moderator
1,186 Views

 mecej4 and Uwe,

Thank you for the report. I escalated this case to development. (It was not escalated back then. Kevin is no longer with Intel)

In future, for prompt support and follow up, please report this type of issues by submitting a ticket on Online Service Center.

0 Kudos
Reply