I’m trying to write an interface to a module that performs some operations on real matrices.
My plan is to have an interface to performs those operations on integer matrices too.
Here is a minimum working piece of the module
module AAA
implicit none
contains
subroutine t_transpose(matrix,matrix_t)
implicit none
real, dimension(:,:), intent(in) :: matrix
real, allocatable, dimension(:,:), intent(out) :: matrix_t
matrix_t=transpose(matrix)
end subroutine t_transpose
subroutine tt_transpose(matrix,matrix_t)
implicit none
real, dimension(:,:), intent(in) :: matrix
real, allocatable, dimension(:,:), intent(out) :: matrix_t
matrix_t=transpose(transpose(matrix))
end subroutine tt_transpose
subroutine t_all(matrix, matrix_t,t_type)
implicit none
real, dimension(:,:), intent(in) :: matrix
real, allocatable, dimension(:,:), intent(out) :: matrix_t
integer, intent(inout) :: t_type
if (t_type.eq.1) then
call t_transpose(matrix,matrix_t)
else if (t_type.eq.2)
call tt_transpose(matrix,matrix_t)
else
t_type=-1 !error flag
end if
end subroutine t_all
end module AAA
I’d like to be able to call t_all with both real and integer matrices, without having to have a real and an integer version of the module subroutines!
I throw your question to ChatGPT, and I get, from my perspective, a pretty nice answer. Here you go!
from ChatGPT:
Hello Roberto,
To achieve your goal of having the t_all subroutine work with both real and integer matrices without duplicating code for each type, you can use Fortran’s generic interfaces. This feature allows you to write a generic interface that can call different subroutines based on the type of the arguments passed.
Here’s how you can modify your module to include a generic interface for handling both real and integer matrices:
First, write additional subroutines for handling integer matrices. These will be similar to your existing subroutines but will work with integer matrices.
Then, define a generic interface in your module that maps to the specific subroutines based on the type of the matrix passed.
Here is an example of how you can modify your module:
module AAA
implicit none
interface t_all
module procedure t_all_real, t_all_integer
end interface
contains
! Existing real matrix operations
subroutine t_transpose_real(matrix, matrix_t)
! ... Your existing code ...
end subroutine t_transpose_real
subroutine tt_transpose_real(matrix, matrix_t)
! ... Your existing code ...
end subroutine tt_transpose_real
subroutine t_all_real(matrix, matrix_t, t_type)
! ... Your existing code ...
end subroutine t_all_real
! New integer matrix operations
subroutine t_transpose_integer(matrix, matrix_t)
! ... Similar to t_transpose_real but for integer matrices ...
end subroutine t_transpose_integer
subroutine tt_transpose_integer(matrix, matrix_t)
! ... Similar to tt_transpose_real but for integer matrices ...
end subroutine tt_transpose_integer
subroutine t_all_integer(matrix, matrix_t, t_type)
! ... Similar to t_all_real but for integer matrices ...
end subroutine t_all_integer
end module AAA
In this modification:
t_transpose_integer, tt_transpose_integer, and t_all_integer are new subroutines that you need to write for handling integer matrices. They will be similar to the real matrix subroutines but will use integer arrays.
The t_all interface is defined to automatically choose t_all_real or t_all_integer based on the type of the matrix passed to it.
With this setup, when you call t_all with a real matrix, t_all_real will be called, and when you call it with an integer matrix, t_all_integer will be called. This approach avoids code duplication and keeps your module organized and efficient.
It says that I don’t need to duplicate/rewrite the subroutines, but then it suggests to have a 2 versions of each subroutine, one real and the other one integer! It doesn’t make much sense!
I was curious if a way existed that could permit to not rewrite code two times!
You can achieve this with Fortran 90 generic interfaces. Sadly, that requires code duplication that can only be avoided with preprocessing as of Fortran 2023. Fortran 202y, with y = merge(7, 8, .5 < rand()), is set to resolve this shortcoming hopefully once and forever.
For now, the best approach might be to write interfaces in a module, the implementations in a submodule of that module, where the actual implementation is included in the submodule via either FPP preprocessing or Fortran intrinsic deprecated include statement. Here is one without submodules:
module test_mod
interface test
module procedure :: test_int, test_real
end
contains
subroutine test_int(x)
real :: x
include "test_mod.inc"
end
subroutine test_int(x)
integer :: x
include "test_mod.inc"
end
end
Then test_mod.inc will contain the generic implementation:
I guess the “without duplicating code for each type” means that you can just use the interface t_all instead of t_all_integer or t_all_real. But you still have to implement the t_all_integer and t_all_real.
What you are expecting (and what most fortraners want) is the generic programming feature of Fortran, which won’t be a part of standard Fortran until Fortran202Y. There are workarounds. For example, you could use Fortran preprocessors. But it complicates your building processes. If you are familiar with building tools like cmake or meson and if you are building a large library for multiple types, kinds and ranks, I would suggest fypp. If you are interested in using fypp, take a look at the Fortran Standard Library. It’s a perfect example of “how to write a generic Fortran library in the pre-Fortran202y era”. With fypp, you could write something like
#: for type, kind in zip(types, kinds)
subroutine t_all_${kind}$(matrix, matrix_t, t_type)
${type}$(${kind}$), intent(in) :: matrix(:)
${type}$(${kind}$), allocatable, intent(out) :: matrix_t(:,:)
integer, intent(inout) :: t_type
! your implementation
end subroutine t_all_${kind}$
#: endfor
Most people trying to do what @Rob777 wants will need at least 3 versions of each subroutine, for default integer, default real (what you get with real declarations), and double precision (what you get with real(kind(1d0)) declarations. There are several other ways to get these kinds. Some people prefer to use selected_real_kind, others prefer to use real32 and real64 from the intrinsic module iso_fortran_env. If you want to be really comprehensive, be warned that gfortran offers 5 integer kinds and 4 real kinds, and you may want subroutines that deal with complex matrices (of 4 kinds in gfortran).
Another workaround could be to use class(*). Depending on the subroutine you’re planning to implement, this might make things easier inside the subroutine, but generally I wouldn’t recommend it in cases like the minimal example.
program p
implicit none
integer :: i(2,3)
real :: r(2,3)
class(*), allocatable :: i_t(:,:), r_t(:,:)
i = reshape([1, 2, 3, 4, 5, 6 ], [2,3])
r = reshape([1.,2.,3.,4.,5.,6.], [2,3])
call t_transpose(i, i_t)
call t_transpose(r, r_t)
select type(i_t)
type is(integer)
print*, i, i_t
end select
select type(r_t)
type is(real)
print*, r, r_t
end select
contains
subroutine t_transpose(matrix, matrix_t)
class(*), intent(in) :: matrix(:,:)
class(*), intent(out), allocatable :: matrix_t(:,:)
select type(matrix)
type is(integer)
matrix_t = transpose(matrix)
type is(real)
matrix_t = transpose(matrix)
end select
end subroutine t_transpose
end
Agreed, though much less duplication with respect to the generic interface approach.
Indeed, fypp would avoid any code duplicatiopn at all, but it is an external tool, while class(*) is fully built-in. And it could avoid any useless code duplication, if one could have written something like
select type (var)
type is (integer, real [, others with shared implementation])
...
type is (OtherType1, OtherType2)
...
class default
error stop "Unsupported type"
end select
Thanks for sharing @Carltoffel .
Steve Lionel wrote:
“Currently, the “declared type” of p inside the type is block is what was specified. The language would have to be contorted and twisted to say that the declared type can be any of the types named. This doesn’t add anything you can’t already do - “syntactic sugar” - and would be a nightmare to describe.”
I don’t have the competencies to argue on this, but I can get the point of such statement.
So, in such case, talking about “syntactic sugar” (as a way to help the programmer write less duplicate code possible), another possibility would have been (IMO) something like:
select type (var)
type is (integer)
type is (real)
type is (whatever type shares with previous)
... shared operations for all above types
type is (Othertype1)
type is (OtherType2)
... shared ops for these 2 types
[etc..]
end select
Because, from the others concerns in that thread, I don’t see any difference in using fypp (meaning that using fypp would not solve them w.r.t to the multiple-types list in type is, except for what Steve pointed out).
But maybe even this option would hide important implementation details.
Indeed, this is now just a mere discussion, since generics should (and hopefully will soon) solve this generic API Fortran limitations.