Dear all,
does anybody know an easy/elegant way to “work around” the fact, that the F2018 standard does not allow rank mismatch in generic calls? In the program below, I have type specific F77 (could be also C) routines, which copy elements from one array to an other. They are simple type specific memcopy routines, expecting a source and target address and the nr. of elements to copy. They are rank-agnostic though. I have defined explicit interfaces for those routines and would like now to find a way, that the caller can call all of them using the same generic name.
Note, I can not change the F77 routines themselves, as they are part of a library out of our control (ScaLAPACK), which we develop some modern wrappers for (in ScalapackFx).
subroutine copy_integer(source, dest, nelem)
integer, intent(in) :: source(*)
integer, intent(out) :: dest(*)
integer, intent(in) :: nelem
print *, "Integer copy"
dest(1:nelem) = source(1:nelem)
end subroutine copy_integer
subroutine copy_real(source, dest, nelem)
real, intent(in) :: source(*)
real, intent(out) :: dest(*)
integer, intent(in) :: nelem
print *, "Real copy"
dest(1:nelem) = source(1:nelem)
end subroutine copy_real
module testmod
implicit none
interface copy
subroutine copy_integer(source, dest, nelem)
integer, intent(in) :: source(*)
integer, intent(out) :: dest(*)
integer, intent(in) :: nelem
end subroutine copy_integer
subroutine copy_real(source, dest, nelem)
real, intent(in) :: source(*)
real, intent(out) :: dest(*)
integer, intent(in) :: nelem
end subroutine copy_real
end interface
end module testmod
program testprog
use testmod, only : copy, copy_integer, copy_real
implicit none
integer :: array1(2, 2), array2(4, 3)
array1(:,:) = reshape([1, 2, 3, 4], [2, 2])
array2(:,:) = 0
! Specific call with rank mismatch works nicely
call copy_integer(array1(1, 2), array2(2, 2), 2)
print "(A)", "Array2"
print "(4I4)", array2
! Generic call with rank-mismatch seems not to be allowed (due to C.9.6/5, I guess)
! Is there any workaround, so that the caller does not have to use the type-specific call?
! call copy(array1(1, 2), array2(2, 2), 2)
end program testprog