Scalar/array mismatch in subroutine call - solvable via Fortran 2003 enhanced array constructor?

INTEGER I
REAL R
CALL SUBR (1,I,R)
...
SUBROUTINE SUBR (n,I,R)
integer :: n, I(n)
real :: R(n)
...

If you understand how Fortran’s call by reference allows this code example to work effectively, you can adopt a compiler option that turns this error into a warning and achieve what has been successfully done in FORTRAN for over 50 years.
Why shut down all that legacy code by listening to those don’t like this approach.

After some more testing, I found the following.

  1. The function approach by @septc / @RonShepard , amended with using the target attribute for the real argument foo in main / the calling subroutine:
  • In fact does not return the correct value in main on my machine, when compiled with Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on IA-32, Version 19.1.3.311 Build 20201010_000000>.
  • This is not dependent on whether foo is given the target attribute or not.
  • This does not change if instead integer, pointer, intent(in) :: s as in @RonShepard’s function above is used.
  • Does what is expected within subroutine mult. Could therefore be an approach if the respective arguments in all subroutines with the scalar/array mismatch are intent(in) (or, do not carry an intent statement but are not changed. e.g. “implicitly” intent(in).
  • The latter seems to be what’s normally happening, so I may still use this solution after verifying. The advantage is that I only need to edit the subroutine calls and the respective subroutine themselves (relatively easy), no big changes to the calling subroutines required (that would be a lot of work and make variable declarations quite inconsistent across the code base).
  • However, if indeed all affected arguments are (implicitly) intent(in), I wonder what the advantage of this solution really is over simply using enhanced array constructors, as proposed initially, is (for sections of the code that are not crucial for performance): CALL SUBR([I],[R])
  1. Subroutine approach by @FortranFan, with or without integer, target :: foo in main:
  • Does what is expected.
  • The target attribute is still required when compiling with Intel Visual Fortran Compiler 19.1.3.311, otherwise the following error occurs: error #7496: A non-pointer actual argument shall have a TARGET attribute when associated with a pointer dummy argument. [FOO]. This may not be a problem with other compilers or the most current version of the Intel compiler.
  • I like very much that this is a general solution apparently using current best practices.
  • I dislike the extra overhead: target attribute for foo in main, separate declaration of integer, pointer :: x(:) in main, separate function call. To fix many separate calls with conflicting scalar/array arguments this may not be the favoured approach.
  1. The approach by @JohnCampbell to turn off the errors via compiler option:
  • Looks increasingly more attractive to me.
  • The goal of the exercise for me is to remove any interface errors prior to activating compiler optimisation flags to i) prevent unexpected behaviour and ii) increase performance. If this can be achieved this way I’d be happy enough. Would anybody like to weigh in why this is a bad idea to achieve these goals, best practices of modern Fortran aside?

Thank you everyone for the discussion, I have learnt a lot from your examples and comments.

1 Like

Thanks very much for trying more codes (by other people) and also Intel Visual Fortran. Also, I am sorry for not having tried other compilers for my snippet (particularly, Intel compilers). Now trying ifort and ifx using Compiler Explorer, they indeed gave different results from gfortran (which can be tested via this link):

gfortran-13.2:
loc(foo) =       140734356428300
loc(arr) =       140734356428300
 main: foo =          700

ifort 2021.9.0 (-standard-semantics):
 loc(foo) =  4777396
 loc(arr) =  140736690401840
 main: foo =  7

ifx 2023.1.0 (-standard-semantics):
 loc(foo) =  4785604
 loc(arr) =  140727918892320
 main: foo =  7

I guess this is related to different treatment or interpretation of the function result. Because recent standards allow the use of pointer function result as a left-hand side of an assignment, I imagined that the returned pointer may be treated as reference in this kind of usage (like passing the pointer directly to a dummy argument). But the behavior seems not the same among compilers… (I have also tried simpler tests using scalar pointer function result, and the behavior was again different among gfortran and ifort. Because the latter tests are simpler (no array), I will probably ask a question in a new thread.)

So anyway, I think it will be safer not to use a pattern like my snippet (using toarray()). Instead, if an explicit array pointer is used to cast a scalar to an array, I believe it would be portable (though it would be much more verbose & tedious…). Also, to avoid future confusion, could you remove the “Solution” mark from my snippet above? I think it could be very dangerous for future readers…

RE SUBR (n,I,R), I think it would be most convenient if implicit interface is okay to use (with no check applied, by just sending the address). Initially, I imagined that the purpose of the first post is to sidestep some compiler checks via enforced explicit interface (?). I think separating legacy codes into different files makes the interface implicit, which I usually use to avoid this kind of “unnecessary” checks (when I am sure if there is no problem).

1 Like

Thanks for your comment and further testing!

I have moved the ‘Solution’ mark to @FortranFan 's answer, as it does what I set out to do and seems to be current best practice.

The issue actually crept up when activating explicit interface generation and check (compiler options /gen-interface /warn-interfaces with Intel Fortran 19.1 compiler). The goal was to weed out erroneous subroutine calls before turning on /O2, /O3 compiler optimisation. So I would like to keep these options activated (at least in Debug mode) also in the future to check new code also and I would like to avoid implicit interfaces.

2 Likes

One issue that should be highlighted with this discussion of using “F77 wrappers” is that this approach assumes all arrays are in contiguous memory. This “call by reference” approach works because we are transferring the start memory address of a sequence of memory of known integer or real kind.
Any use of pointers or targets that can imply non-contiguous arrays and the compiler may supply non-contiguous arrays; this will not work with the old wrapper approach.
A corollary to this is to never use a coding structure that could imply non-contiguous arrays, because you may use a Fortran compiler that utilises this approach. These can be ugly errors and under past definitions of buggy coding structures, I don’t know why these approaches were given a life.

1 Like