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.

1 Like

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.

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