I have a comment/question regarding the mechanism provided by the standard to store a number of identical interfaces and the level of verbosity involved.
Say I write a bunch of functions, all with the same interface and the same function result. The only difference involved are the methods employed to evaluate the same function.
One of the things I can do in this case is to create a module, with a single INTERFACE block containing the interfaces of the different implementations inside it. If I declare the interfaces with the “module function” keywords I can write the source codes inside a submodule, with the header “module procedure” for each individual function code. In this way, i achieve the recommended data abstraction.
This works very well and is very useful. The only irksome detail here is that the interface block inside the module ended up containing several almost identical declarations, whose only differences were the actual names of the various functions.
Then I thought of declaring an abstract interface andPreformatted text only include the list of the proper names inside the interface block with the PROCEDURE() declaration, in order to achieve a lower verbosity level. But it seems that the standard forbids this alternative.
This is the sample code:
MODULE module_procedures_abstract_interface
use, intrinsic :: iso_fortran_env, only: dp => real64
implicit none
ABSTRACT INTERFACE
function fun_2_args(x, y)
import :: dp
real(dp) :: fun_2_args
real(dp), intent(in) :: x, y
end function fun_2_args
END INTERFACE
! INTERFACE ! version 1
! PROCEDURE(fun_2_args) :: fun1, fun2
! END INTERFACE
INTERFACE ! version 2
module function fun1(x,y)
! import :: dp
real(dp) :: fun1
real(dp), intent(in) :: x, y
end function fun1
!***
module function fun2(x,y)
! import :: dp
real(dp) :: fun2
real(dp), intent(in) :: x, y
end function fun2
END INTERFACE
END MODULE module_procedures_abstract_interface
Compilation with version 1 commented works all right, but if I uncomment version 1, error messages appear. The intel compiler gives:
$> ifort -c module_procedures_abstract_interface_MOD.f90
module_procedures_abstract_interface_MOD.f90(16): error #6651: The PROCEDURE specification is allowed only if the interface-block has a generic-spec.
PROCEDURE(fun_2_args) :: fun1, fun2
---^
compilation aborted for module_procedures_abstract_interface_MOD.f90 (code 1)
So it seems to me that I only have the more verbose solution allowed.
Or am I missing something?