Problem with Ambiguous interfaces with gfortan - interface

I have a situation similar to the following code snipped (saved in test.f90):
module interfaces_mod
private
public :: interf
interface interf
module procedure interf1
module procedure interf2
end interface
contains
subroutine interf1(&
numbers,&
num_numbers,&
dense_ranks&
)
Implicit None
integer, dimension(:), intent(in) :: numbers
integer, intent(in) :: num_numbers
integer, dimension(:), intent(out), optional :: dense_ranks
end subroutine interf1
subroutine interf2(&
degeneracies,&
numbers,&
num_numbers,&
dense_ranks&
)
Implicit None
Integer, dimension(:), intent(inout) :: degeneracies
integer, dimension(:), intent(in) :: numbers
integer, intent(in) :: num_numbers
Integer, dimension(:), intent(out), optional :: dense_ranks
end subroutine interf2
end module interfaces_mod
The module therefore defines a generic interfaces with two possible realizations.
This snipped can be compiled using ifort with
ifort -c -o "test.o" "test.f90"
to create a module.
However trying to compile the same code with gfortran:
gfortran -c -o "test.o" "test.f90"
leads to the error:
15 | subroutine interf1(&
| 1
......
32 | subroutine interf2(&
| 2
Error: Ambiguous interfaces in generic interface 'interf' for ‘interf1’ at (1) and ‘interf2’ at (2)
Now looking at the dummy parameters of the realizations, interf1 is called with
an Integer array followed by an Integer and an optional Integer array.
interf2 instead is called with two Integer arrays followed by an Integer and an optional
Integer array.
So I dont understand where the ambiguity is coming from, and why ifort can compile this snipped and gfortran is not able to compile it.
gfortran version is 9.3.0,
ifort version is 19.0.5.281

Your procedures do not meet the rules for having the same generic identifier, and gfortran is entitled to reject the generic.
The constraint to consider is C1514 of Fortran 2018. Let's take a detailed look. There are no dummy procedures or passed-object dummy arguments, so we're down to (1) and (4) of that constraint. One of these conditions must pass.
For (1):
We have one scalar argument in each procedure, called num_numbers in each. The scalar argument cannot be used to disambiguate.
In interf1 we have a (1a) score of 1 for the two array dummy arguments, whereas the (1b) score for each is 3. For interf2 the (1a) scores are 2 for the three array dummy, whereas the (1b) score for each is also 2.
(1) is not met.
For (4):
No dummy argument in one procedure is distinguishable from that with the same name in the other.
interf1 does not have a dummy argument with name not appearing in interf2.
interf2 has name-disambiguating argument degeneracies at position 1 while its first position-disambiguating argument is at position 2.
(4) is not met.
Although (4) is not met, it is easy to modify the procedure definitions such that it is: move degeneracies later in the argument list.
There's an important note in the Fortran standard itself, before you try to work out exactly how to create an ambiguous reference:
These rules are sufficient to ensure that references to procedures that meet them are unambiguous, but there remain examples that fail to meet these rules but which can be shown to be unambiguous [...] The rules
to cover all cases are too complicated to be useful.

Related

Fortran function to get association status and size of a pointer in one go

I am writing a Fortran (2003) integer function to check a pointer to an array of arbitrary elements for association status and size, using class(*). If not associated, it shall return -1, otherwise the number of elements of the array. It is assumed that the pointer is defined pointing to null().
The goal is to avoid two subsequent if statements. (I am aware that in C the 2 checks can be combined to a single statement.)
The code compiles and runs under gfortran (6.1.0) and Intel ifort (17.0.4), but only gfortran gives the desired result.
The complete code comprising a test routine and the function called "size_field" is shown below:
program tpa
implicit none
real,pointer :: tp(:)=>null()
write (6,*) size_field(tp)
allocate (tp(53)); write (6,*) size_field(tp)
deallocate (tp); write (6,*) size_field(tp)
tp=>null(); write (6,*) size_field(tp)
allocate (tp(0)); write (6,*) size_field(tp)
deallocate (tp); write (6,*) size_field(tp)
contains
function size_field(ff)
integer :: size_field
class(*),target :: ff(:)
class(*),pointer :: field(:)
field => ff
size_field=-1 ! shall indicate not associated
if (associated(field)) size_field=size(field)
end function
end program
Compiled with gfortran (default compiler options), the output is as intended:
-1
53
-1
-1
0
-1
Compiled with ifort (default compiler options), the output is:
0
53
53
53
0
0
Why is ifort not giving the result I intended?
If I replace class(*) with real, also the ifort compiled program shows the correct result.
Your program is not valid Fortran. A compiler is allowed to give any result it likes when asked to compile this program.
The dummy argument ff
class(*), target :: ff(:)
is a non-pointer, non-optional dummy argument and so (Fortran 2018 15.5.2.3 p1) any pointer actual argument when referencing the function size_field, in this case tp, must be pointer associated with a target.
On the first reference, tp is not pointer associated.
As to how to meet your requirements, the "non-optional" part is a big hint. Under Fortran 2008+ one may make the dummy argument optional, and then the actual argument need not be pointer associated when referencing the function. If the actual argument is not pointer associated then the dummy argument is not present:
function size_field(ff)
integer :: size_field
class(*), target, optional :: ff(:)
if (PRESENT(ff)) then
size_field = SIZE(ff)
else
size_field = -1
end if
end function
However, addressing the "non-optional" part of the restriction is the sole helpful way in the case of the question. Trying to make the dummy argument a pointer instead is not helpful: for a polymorphic dummy pointer argument the actual argument must also be polymorphic (and with an unlimited polymorphic dummy the actual argument must also be unlimited polymorphic).

what is the correct way to write a specific interface in fortran?

I tried the following code to get the code to work correctly. It seems I need to write an interface to avoid mistaken results. I wrote the following, but it does not pass the compiling stage. The errors are the following: (use gfortran compiler)
fit.f90:34.16:
TYPE(spec), INTENT(IN) :: SMP
1
Error: Derived type 'spec' at (1) is being used before it is defined
fit.f90:35.12:
REAL(q), INTENT(OUT) :: RES
1
Error: Symbol 'q' at 1 has no IMPLICIT type
...
Here is the compilable code to illustrate the issue.
MODULE prec
INTEGER, PARAMETER :: q=8
END MODULE prec
MODULE MOD_FIT
USE prec
INTEGER, PARAMETER :: NO_NI=200
TYPE spec
! source of fitting
INTEGER NW
COMPLEX(q), POINTER :: W(:),G(:)
! how spectrum is parametrized
INTEGER NO_NM ! continuous points labeled as 1,2,3,...,NO_NM
REAL(q), ALLOCATABLE :: O_N(:),O_D(:) ! frequency
REAL(q), POINTER :: A_N(:),B_N(:),A_D(:) ! A(Omega)
END TYPE
TYPE(spec) SMP
INTERFACE
SUBROUTINE NNLS_CMPLX(SMP,RES,RES_V)
IMPLICIT NONE
TYPE(spec), INTENT(IN) :: SMP
REAL(q), INTENT(OUT) :: RES
COMPLEX(q), OPTIONAL, INTENT(OUT) :: RES_V(SMP%HN)
END SUBROUTINE NNLS_CMPLX
END INTERFACE
CONTAINS
SUBROUTINE NNLS_CMPLX(SMP,RES,RES_V)
IMPLICIT NONE
TYPE(spec) :: SMP
REAL(q) :: RES
COMPLEX(q), OPTIONAL :: RES_V(*)
RES=0
IF(PRESENT(RES_V)) RES_V(1)=0
END SUBROUTINE NNLS_CMPLX
END MODULE MOD_FIT
PROGRAM MAIN
USE prec; USE MOD_FIT
REAL(q) PK_RES
COMPLEX(q) RES_V(4)
CALL NNLS_CMPLX(SMP,PK_RES,RES_V)
END
Having an explicit interface means that the compiler knows how the called subroutine or function (procedure) looks like.
Explicit interfaces should not be normally provided by an interface block, that is the thing:
interface
...
end interface
but by placing the procedures in modules instead.
You definitely cannot use an interface block for a module procedure (a procedure placed inside a module). Interface block tells that there is some external procedure somewhere with the properties you declare in the interface block. But your procedure is not external, it is in a module.
Just remove the interface block and it should work.
Just a suggestion: use small caps and indentation in your code. It is very difficult to read as it stands.
To explain the actual error message: As francescalus comments, interface blocks have a separate scope. If they are placed in a module, they do not see the other contents of the module. That's why the compiler complains it does not know what spec and q are.

Fortran Select Type with arrays [duplicate]

My question is, "Can a select type block be used to distinguish real :: realInput from real :: realArrayInput(:)?" It's clear how select type may be used to distinguish derived types, but becomes less clear to me how (or whether) it may be used on intrinsic types.
In Mad Libs form, can the blanks be filled in below to distinguish between the inputs above:
select type (input)
type is (real)
print *, "I caught the realInput"
type is (___________)
print *, "I caught the realArrayInput"
end select
I've found some related posts that did not quite contain the answer I was hoping for:
Select Type Issues
Determining Variable Type
No. input is either declared as an array or a scalar, even when it is polymorphic (and even when it is unlimited polymorphic).
The recent further interoperability with C TS (which may be part of F201X) introduced the concept of assumed rank and the RANK intrinsic, which may do what you want. But there are many limitations around what can be done with assumed rank objects. And regardless of that SELECT TYPE still only works on type. The syntax of the select type construct simply doesn't permit specification of rank in the type guard statements.
Obviously depending on what it is that you actually want to do (?) ... and beyond generic interfaces mentioned by others, a way to have objects that can be either array or scalar in current Fortran (there are other possibilities) is to use derived type wrappers that are an extension of a common parent type. You then use a polymorphic object declared as the parent type (or you can use an unlimited polymorphic object) to refer to an object of the relevant derived type.
TYPE :: parent
END TYPE parent
TYPE, EXTENDS(parent) :: scalar_wrapper
REAL :: scalar_component
END TYPE scalar_wrapper
TYPE, EXTENDS(parent) :: array_wrapper
REAL :: array_component(10)
END TYPE array_wrapper
...
SUBROUTINE what_am_i(object)
! Note that object is scalar, but that doesn't tell us
! the rank of the components of the dynamic type of object.
CLASS(parent), INTENT(IN) :: object
!****
SELECT TYPE (object)
TYPE IS (scalar_wrapper)
PRINT "('I am a scalar with value ',G0)", &
object%scalar_component
TYPE IS (array_wrapper)
PRINT "('I am an array with values ',*(G0,:,','))", &
object%array_component
CLASS DEFAULT
PRINT "('I am not sure what I am.')"
END SELECT
END SUBROUTINE what_am_i
Just to combine IanH's anwser and M.S.B's comment and explain more in detail: You can not use the select type construct to distinguish between real scalars and real arrays as they only differ in their dimension, but not in their type. When you declare your variable input, you already decide 'for ever', whether it has or it has not the dimension attribute:
class(*) :: input_scalar
class(*), dimension(10) :: input_array
Whichever value the variable takes later (or to whichever object it points to, if it is a pointer), it can not represent something with a dimensionality (rank) different from the one in its declaration.
On the other hand, you could for example use the interface construct (or generic in type bound procedures) to distinguish between objects of the same type but different ranks. The example below demonstrates that for scalar and rank one integer and real arrays.
module testmod
implicit none
interface typetest
module procedure typetest0, typetest1
end interface typetest
contains
subroutine typetest0(object)
class(*), intent(in) :: object
select type(object)
type is (real)
print *, "real scalar"
type is (integer)
print *, "integer scalar"
end select
end subroutine typetest0
subroutine typetest1(object)
class(*), dimension(:), intent(in) :: object
select type(object)
type is (real)
print *, "real array"
type is (integer)
print *, "integer array"
end select
end subroutine typetest1
end module testmod
program test
use testmod
implicit none
integer :: ii
integer, dimension(10) :: iarray
call typetest(ii) ! invokes typetest0
call typetest(iarray) ! invokes typetest1
end program test

How to use a user-defined-type in a Fortran interface

In a Fortran 2003 module I'm defining a type called t_savepoint and, later, I want to define an interface for a subroutine called fs_initializesavepoint, which takes an object of type t_savepoint as only argument.
Here is the code for the whole module:
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
interface
subroutine fs_initializesavepoint(savepoint)
type(t_savepoint) :: savepoint
end subroutine fs_initializesavepoint
end interface
end module m_serialization
The reason why I want such an interface is that later on I will make this fortran module interoperate with C.
If I try to compile it (gfortran-4.7.0), I get the following error message:
type(t_savepoint) :: savepoint
1
Error: The type of 'savepoint' at (1) has not been declared within the interface
The error disappears if I move the definition of the type inside the subroutine; but if then I want to use the same type within many subroutines, should I repeat the definition in all of them?
Thank you in advance.
EDIT: a solution would be to move the definition of the type onto another module and then to use it in every subroutine. However I don't like this solution too much, because the type t_savepoint and the subroutines are part of the same conceptual topic.
Rightly or wrongly in an interface block you don't have access to the environment by host association. To fix this you need to import the datatype exlicitly:
[luser#cromer stackoverflow]$ cat type.f90
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
interface
subroutine fs_initializesavepoint(savepoint)
Import :: t_savepoint
type(t_savepoint) :: savepoint
end subroutine fs_initializesavepoint
end interface
end module m_serialization
[luser#cromer stackoverflow]$ gfortran -c type.f90
This is f2003.
However I suspect the way you have put this suggests you are not going about coding this up the best way. Better is simply to put the routine itself in the module. Then you don't need bother with the interface at all:
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
Contains
Subroutine fs_initializesavepoint(savepoint)
type(t_savepoint) :: savepoint
Write( *, * ) savepoint%savepoint_index, savepoint%savepoint_value
End Subroutine fs_initializesavepoint
end module m_serialization
[luser#cromer stackoverflow]$ gfortran -c type.f90
Given that modules are really designed to deal with connected entities this is really the way to do it in Fortran. It also has the advantage of only requiring a f95 compiler, so is universally available (though admittedly import is commonly implemented)

Module calling an external procedure with implicit interface

The following code, combining module procedures and external procedures:
module module_dummy
implicit none
contains
subroutine foo(a)
real, intent(inout) :: a(:)
call bar(a)
end subroutine foo
end module module_dummy
program main
use module_dummy
implicit none
integer, parameter :: nelems = 100000000
real, allocatable :: a(:)
allocate( a(nelems) )
a = 0.0
call foo(a)
print *, a(1:10)
deallocate(a)
end program main
subroutine bar(a)
implicit none
real, intent(inout) :: a(:)
a = 1.0
end subroutine bar
seems to fail either:
with a segmentation fault
printing a block of 0.000 instead of a block of 1.000
on any platform I have tried so far. The problem is related to the implicit interface declaration of bar, and in fact the issue can be solved adding in any way an explicit interface, e.g. using:
module module_dummy
implicit none
contains
subroutine foo(a)
interface
subroutine bar(x)
real, intent(inout) :: x(:)
end subroutine bar
end interface
real, intent(inout) :: a(:)
call bar(a)
end subroutine foo
end module module_dummy
or declaring bar inside a module to be used by module_dummy.
Anyhow I really don't understand what is the error in the first place. What I have found on the Fortran 90 standard (sec. 12.3.2.4) says that:
The type, type parameters, and shape of dummy arguments of a procedure
referenced from a scoping unit where the interface of the procedure is
implicit must be such that the actual arguments are consistent with
the characteristics of the dummy arguments.
In this case the rule seems to be respected, as a is always declared as
real, intent(inout) :: a(:)
So, what am I missing in the interpretation of the standard that makes the previous code wrong?
Dummy arguments that are assumed shape must have an explicit interface at their point of reference. F90 12.3.1.1 item 2c.
Practically, assumed shape arrays are passed by passing a descriptor - a little structure that describes the bounds and the location of storage of the array. Ye-olde F77 explicit shape and assumed size arrays are passed simply by passing the address of the first element. Without the explicit interface the compiler doesn't know that it needs to build and pass the descriptor - hence chaos and confusion results.