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

Making a wrapper routine seems nice :slightly_smiling_face:

RE equivalence, I’ve just tried to use it for dummy arguments, but it was really illegal… (rejected by gfortran). So the usefulness of equivalence seems pretty limited (*).

If the legacy code is not very often called (eg only once), it might be useful to prepare some helper routine (like toarray() below) and “cast” a scalar to an array pointer on the fly (but, I am not 100% sure whether the result is portable… I’ve tried Gfortran only).

module util_m
    use iso_c_binding
    implicit none
contains

function toarray( s ) result( a )
    integer, target  :: s      !! scalar
    integer, pointer :: a(:)   !! array
    call c_f_pointer( c_loc(s), a, [1] )  !! return array pointer
end

end module

program main
    use util_m
    implicit none
    integer :: foo
    foo = 7

    !! call mult( foo )   !! Error: Rank mismatch
    call mult( toarray( foo ) )

    print *, "main: foo = ", foo   !! 700
contains

subroutine mult( arr )   !! legacy code
    integer arr(*)
    arr(1) = arr(1) * 100
end

end program

(*) @RonShepard Thanks very much for your explanation about equivalence. Now I think its usefulness is pretty limited if it cannot be used for dummy arguments and module variables… (I think we should simply use pointers instead). Here, I have a related question: Although equivalence is considered error-prone by many people, is it mainly because one can do type punning with equivalence and a lot of legacy codes “abused” it, e.g., for efficient memory handling in the F77 era?

program main
    implicit none
    integer i
    real x
    equivalence (i, x)

    i = 100
    print *, x   !!    1.40129846E-43
end
1 Like

That is probably the main reason. The c_f_pointer(c_loc(s),...) approach is more or less the modern way to do the same thing, although, as you demonstrated, it works more generally for dummy arguments and modules variables too.

One comment about your code is that I think the actual argument foo should have the target attribute. That guarantees that the actual argument and the dummy argument are the same thing, rather than just a copy. This is one of the subtle things about fortran pointers, and one of the dangers of functions that return pointers.

2 Likes

@marcus_andreas ,

See this thread for the enhanced interoperability with C facility also with a fully worked out illustration and commentary.

But note my point to you earlier was only that a wrapper layer that enables use of some legacy subprograms in modern code can use some tools from the C interoperability facility in the standard even though the wrapper layer and the caller code is in Fortran. So it was about multipurposing a feature, it was not suggesting to anything toward adapting the code for C interoperability. However if you do have to “think about C interoperability soon elsewhere in the code”, just FYI I have posted many examples at this site that you may try to look up.

1 Like

@septc I have adopted a solution like you propose and created separate functions for integer/real/logical scalar arguments. This gives me a lot of flexibility for my use case (the scalar arguments of several functions are sometimes problematic, there are many function calls, either an integer/real/logical argument is problematic or a combination of those).

The point by @RonShepard below regarding giving the target attribute to the real argument has been noted. However, due to the multitude of calls from many different subroutines in the code I refrain from implementing it here, as it is unclear if any performance gains would be worth it. Thank you, anyway!

@marcus_andreas , please note that (I guess) @RonShepard 's point is not much about code performance, but code safety instead. Indeed, most of the times this “lack” of attribute would not hurt you, but in some cases, this can turn to be a nightmare to spot based on code complexity, since it’s not explicitly a logic error. And since you mention “multitude of calls”, the probability of such subtle cases arises.

1 Like

@marcus_andreas , @mEm ,

TL;DR: toarray function as shown above requires TARGET attribute with the actual argument but there is no way to enforce it and that’s a problem.

At its root, the point by @RonShepard re: TARGET attribute on the original object foo (and effectively the actual argument) in the example and suggestion by @septc is about standard conformance and thus portability.

Without the TARGET attribute, the standard offers no persistent association of the function result (that has a POINTER attribute) with the target once the function returns. “Just becoz” it works as expected by an author (@septc) with a given instance of a processor does not mean much in this case; another incarnation of the same processor or other processor can behave differently.

1 Like

@FortranFan ,

what about introducing some compiler option preventing declaring associated dummy arguments as target if the actual argument is not ?
Just like allocatables:
An allocatable (A target) dummy argument may only be argument associated with an allocatable (a target) actual argument.

This would be a very significant restriction of usages.

Sure.
That’s why I said “compiler option”, which if not turned on, would leave everything as it is.
And it would not need to be a compile error, also a warning, just to tell the user that, as @FortranFan clarified, the code is not standard conformant, and might show unexpected behaviours.

This is actually something that is treated as a special case and is allowed by the standard. When the target dummy argument is associated with a target actual argument, then the standard requires that they point to the same thing (i.e. the same memory). When the actual argument does not have the target attribute, then the compiler is allowed to make a copy of the actual argument, in which case the dummy argument is associated with that copy instead of the original. The standard allows this because a local pointer to that target can be used internally within that subprogram, and that pointer can be passed on to other lower level subprograms and so on, and it behaves normally from that point on down the calling sequence.

A compiler could not detect this situation at compile time in all cases. Imagine the situation where the subroutine is compiled before the calling program is compiled (or even before the calling program is written). So to test all possible cases would require a run time check. This would also require extra information to be created during the call and passed to the subroutine. I don’t know how expensive this would be, but it would require some extra effort during the argument association process.

Or said another way, this is not an issue regarding syntax, it is an issue regarding the program logic. Those are sometimes difficult, or impossible, to detect at compile time and to print the appropriate warning. In contrast, the allocatable dummy argument attribute is an issue regarding syntax, so it can be tested at compile time.

But you would also get errors or warning for perfectly legal codes: For, I suspect it would be very tricky for a compiler to identify legal and illegal cases for this problem.

@RonShepard , thanks for your explanation. I get the point.

Would this be true even when “using” (in the calling program) the subroutine with explicit interface ?

@PierU , I am sorry, but I cannot fully get :

What do you actually mean in such case ?

In the case of gfortran and LFortran, note all the users themselves indeed are compiler developers; or they urgently need to see themselves as such; then the users can investigate if “some compiler option” is viable.

With other compilers, their vendors would need to comment.

@septc,

I suppose you could try and suggest the following with a SUBROUTINE subprogram and INTENT(IN), POINTER received argument as a conforming alternative to the approach with a FUNCTION with a RESULT that has the POINTER attribute:

   integer, target :: foo   !<-- remove the TARGET attribute and retry
   integer, pointer :: x(:)
   foo = 0
   call toarray( foo, x )
   call sub( size(x), x )
   print *, "foo = ", foo, "; expected is 42"
contains
   subroutine toarray( s, a )
      use, intrinsic :: iso_c_binding, only : c_loc, c_f_pointer
      integer, pointer, intent(in)  :: s      !! scalar
      integer, pointer, intent(out) :: a(:)   !! array
      call c_f_pointer( c_loc(s), a, [1] )  !! return array pointer
   end subroutine
   subroutine sub( n, a )
      integer, intent(in) :: n
      integer, intent(inout) :: a(*)
      a(1:n) = a(1:n) + 42
   end subroutine
end

I mean that this is legal to pass a non-target actual to a target dummy: then how can a compiler sort out between the legal from the illegal cases ? It’s maybe possible, but at least very tricky (and not in all cases). Then you would probably have plenty of “false positive”.

I overlooked the automatic pointer targeting facility introduced in the standard starting Fortran 2008; with a conforming processor you can try INTENT(IN) POINTER received argument with your function solution as well.

   integer, target :: foo   !<-- remove the TARGET attribute and retry
   integer, pointer :: x(:)
   foo = 0
   call sub( 1, toarray(foo) )
   print *, "foo = ", foo, "; expected is 42"
contains
   function toarray( s ) result(a)
      use, intrinsic :: iso_c_binding, only : c_loc, c_f_pointer
      integer, pointer, intent(in)  :: s      !! scalar
      integer, pointer :: a(:)   !! array
      call c_f_pointer( c_loc(s), a, [1] )  !! return array pointer
   end function
   subroutine sub( n, a )
      integer, intent(in) :: n
      integer, intent(inout) :: a(*)
      a(1:n) = a(1:n) + 42
   end subroutine
end

I think this, or the subroutine version, should work. However, one wonders what is gained by using either the function or the subroutine when what it really does is just the single statement

call c_f_pointer( c_loc(s), a, [1] )

which could be moved into the calling program (with the actual arguments, of course).

@FortranFan said “In the case of gfortran and LFortran, note all the users themselves indeed are compiler developers; or they urgently need to see themselves as such;” But I have been a gfortran user since 2005 and I am not one of those. I have reported quite a few bugs but I don’t know C and I won’t try to join those excellent people who keep improving gfortran.

Well, the gain is really programmer convenience, by tucking away the two-stepping into a convenient function, towards which the processor will hopefully do some good stuff (inlining or whatever), she doesn’t have to repeat the same mind-numbing logic at each point-of-use.

Arguably this has been the same argument since Backus and team started off on their journey, the ASSEMBLERs wondered vehemently what is gained by using this Formula Translation thingy.

1 Like

@Harper , if you truly are a user of gfortran, you better figure out in a hurry how to contribute!

Don’t let your sheer failure of imagination get in your way.

You can make a difference in a myriad of ways. I, for example, have in the past made direct financial contributions to an Institute in the US who was coordinating the work to implement new standard features via a long time FOSS volunteer based in the UK.

But it can be different for different folks. Faculty in Mathematics, for example, can sponsor part-time work for students in CS and Math to do a variety of work around the gfortran ecosystem. First-year and second-year students do amazing coding these days and there is nothing better for students like getting paid to do work around coding to achieve well-defined target goals. However each user can best figure out how they advance the “ball”.

The users of gfortran need to really think hard and imaginatively, otherwise it risks going the way of g95. The users are the developers and stakeholders and they own it all.