Error: There is no specific subroutine for the generic ‘sort_index’

Hi,

I’d like to play with stdlib_sorting (sort_index in particular, for now) but I cannot get this “hello world” program to compile:

program test_sort_index
  use stdlib_kinds, only: dp
  use stdlib_sorting, only: sort_index, int_size
  implicit none
  
  integer(int_size), allocatable :: idx(:)
  real(dp), parameter :: test(6) = [0.8_dp, 0.4_dp, 42._dp, 89._dp, 546._dp, -5.23_dp]
  call sort_index(test, idx)
end program test_sort_index
$ gfortran-10 --version
GNU Fortran (Ubuntu 10.3.0-1ubuntu1~20.04) 10.3.0

complains

call sort_index(test, idx)
                           1
Error: There is no specific subroutine for the generic ‘sort_index’ at (1)

I have the latest version of stdlib (to the last commit) from GitHub built with cmake. If I open the generated stdlib_sorting.f90 I can clearly see the public interface of sort_index that includes the module subroutine dp_sort_index with the right signature that I need. I have copied all stdlib module and submodule files and the generated static library in the same directory of the test program above to rule out any accessibility issues.

Before opening an issue, I’d like to understand if I’m doing something wrong.

1 Like

I have the latest version of stdlib (to the last commit) from GitHub built with cmake . If I open the generated stdlib_sorting.f90 I can clearly see the public interface of sort_index that includes the module subroutine dp_sort_index with the right signature that I need. I have copied all stdlib module and submodule files and the generated static library in the same directory of the test program above to rule out any accessibility issues.

Can you make dp_sort_index public and try calling that explicitly? Then the compiler will say why the calling code is invalid. That is what I do when I get the no specific subroutine for the generic error.

1 Like

sorted_index generic interface in stdlib has for the first parameter the INTENT(INOUT) attribute whereas your actual argument is a named constant. Retry with your test object as rank-1 variable instead.

3 Likes

Thanks @FortranFan: without the parameter attribute it works (maybe I should stop working late at night to avoid wasting my and other people’s time :grin: ).

@Beliavsky excellent general suggestion: I admit that I tried to do that before posting, but the fact that I do not know how fypp exactly works didn’t help me.

BTW, please note that if you don’t want to receive a segfault upon execution, you need to manually allocate idx:

program test_sort_index
  use stdlib_kinds, only: dp
  use stdlib_sorting, only: sort_index, int_size
  implicit none
  
  integer(int_size), allocatable :: idx(:)
  real(dp) :: test(6) = [0.8_dp, 0.4_dp, 42._dp, 89._dp, 546._dp, -5.23_dp]
  allocate(idx(size(test)))
  call sort_index(test, idx)
end program test_sort_index

This is also documented (my bad for missing it) but (personally) I do not find it very user-friendly.

1 Like

EDIT. Sorry, I think I got it: it’s again because of the intent(inout) attribute of the first argument in the signature of the sorted_index: the compiler has no way to “modify” the returned array by get_test()

Ok, new case: can someone explain why the following fails?

program test_sort_index
  use stdlib_kinds, only: dp
  use stdlib_sorting, only: sort_index, int_size
  implicit none
  
  integer(int_size), allocatable :: idx(:)
  real(dp) :: test(6) = [0.8_dp, 0.4_dp, 42._dp, 89._dp, 546._dp, -5.23_dp]
  allocate(idx(size(test)))
  call sort_index(get_test(), idx)
contains
  function get_test()
    real(dp) :: get_test(6)
    
    get_test = test
  end function get_test
end program test_sort_index
call sort_index(test, idx)
                         1
Error: There is no specific subroutine for the generic ‘sort_index’ at (1)

I hope I’m not missing something obvious :thinking:

Say one has a “library” module providing generic interfaces to some cool procedures that should be seen as standard:

module m
   use, intrinsic :: iso_fortran_env, only : RK => real_kinds
   interface proc
      subroutine proc_1( a )
         import :: RK
         real(RK(1)), intent(inout) :: a(:)
      end subroutine 
      subroutine proc_2( a )
         import :: RK
         real(RK(2)), intent(inout) :: a(:)
      end subroutine
   end interface
end module

So for the case in the original post with an actual argument that is a named constant, a processor can be expected to fail to resolve the generic resolution but the diagnostics can vary:

   use m
   real, parameter :: x(3) = [ 1.0, 2.0, 3.0 ] 
   call proc( x )
end 

C:\temp>gfortran -c o.f90
o.f90:16:17:

16 | call proc( x )
| 1
Error: There is no specific subroutine for the generic ‘proc’ at (1)

C:\temp>ifort /c /standard-semantics o.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

o.f90(16): error #6638: An actual argument is an expression or constant; this is not valid since the associated dummy argument has the explicit INTENT(OUT) or INTENT(INOUT) attribute.
call proc( x )
--------------^
compilation aborted for o.f90 (code 1)

Now, consider a case where the first argument is an expression:

   use m
   real :: x(3) = [ 1.0, 2.0, 3.0 ] 
   call proc( (x) )
end 

YMMV with the processor.

A function result with the case shown above is an expression and the same applies.

Yes, thanks for the explanation and sorry for the (rather) trivial questions.

I knew that code such as that below was illegal but did not know that compilers would catch it at compile time, so thanks for your questions.

module m
contains
subroutine twice(i)
integer, intent(in out) :: i
i = 2*i
end subroutine twice
end module m

program main
use m
call twice(3) ! invalid
print*,"done"
end program main
1 Like

With the latest stdlib version I’m getting the same error with this minimal example

program check
    use iso_fortran_env, only: real64
    use stdlib_sorting, only: sort_index
    implicit none

    real(real64) :: X(5) = [2, 5, 3, 5, 7]
    integer :: idx(5)

    call sort_index(X, idx)
    print *, idx
end program check

Gives

Error: There is no specific subroutine for the generic ‘sort_index’ at (1)
test/check.f90:9:27:

    9 |     call sort_index(X, idx)
      |                           1
Error: There is no specific subroutine for the generic ‘sort_index’ at (1)

Given the documentation below and that int_size is given by

integer, public, parameter :: int_size = int64,

I think the problem is that idx in your code has type default integer (int32), not int64.

People often use integers of the default type. Maybe stdlib should further overload the sort_index subroutine so that index can be of type int32.

 call sort_index( array, index[, work, iwork, reverse ] )

with the arguments:

  • array: the rank 1 array to be sorted. It is an intent(inout) argument of any of the types integer(int8), integer(int16), integer(int32), integer(int64), real(real32), real(real64), real(real128), character(*), type(string_type), type(bitset_64), type(bitset_large). If both the type of array is real and at least one of the elements is a NaN, then the ordering of the array and index results is undefined. Otherwise it is defined to be as specified by reverse.
  • index: a rank 1 array of sorting indices. It is an intent(out) argument of the type integer(int_size). Its size shall be the same as array. On return, if defined, its elements would sort the input array in the direction specified by reverse.
1 Like

Thank you! My wrong at the moment of reading documentation :sweat_smile:

I’m curious why this parameter is named int_size instead of int_kind.

It is a little confusing since the term “size” is used in the documentation to describe the size of array(:) and index(:).

Here is another comment on this programmer interface. If index(:) is defined to be intent(inout), then it can be initialized by the caller to do the indexed sort on a subset of array(:). For example, if array(1:5)=[5,4,3,2,1] and index=[1,3,5] on entry, then the return values would be [5,3,1] which would correspond to sorting the odd index entries of the array in increasing order. This convention adds some burden onto the programmer, but it makes the routine much more flexible.

I don’t remember why it has been called int_size. But it could be renamed, if users find/prefer a more appropriate name.

FYI: sort_index has been extended to allow both int32 and int64 index arguments

3 Likes