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

Hi all,

I’m working with a legacy code and am trying to debug interface errors by generating/checking explicit interfaces using the Intel Fortran /gen-interface /warn:interfaces compiler options.

The code very often uses subroutines with dummy arguments being assumed size arrays of this form:

subroutine SUBR(I2,R2)
INTEGER I2(*)
REAL R2(*)

The arguments passed to the subroutine are both arrays and (more commonly) scalars:

INTEGER I
REAL R
CALL SUBR(I,R)

More often than not, these are implicitly declared in the code.

The use above is flagged by the compiler as:

error #8284: If the actual argument is scalar, the dummy argument shall be scalar unless the actual argument is of type character or is an element of an array that is not assumed shape, pointer, or polymorphic.   [I]	C:\...\main.for	866	

So far so good - the types on both sides of the subroutine call do not match and can be made consistent via, e.g.:

INTEGER I(1)
REAL R(1)
CALL SUBR(I,R)

I’d like to understand this issue a bit better. A few questions:

  1. Has this ever been legal Fortran and changed over time, or is it simply an issue that has been flying under the radar in this case as interface checks have not been made?

  2. I have found the following work-around (cannot find the thread now):

INTEGER I
REAL R
CALL SUBR([I],[R])

This makes the error disappear, but was discouraged in the original thread. What exactly is happening here? I suspect this is using Fortran 2003 enhanced array constructors to cast the scalars into arrays and pass those to the function. I understand this should behave as expected, as long as the subroutine dummy arguments are INTENT(IN), such as in:

CALL SUBR([5],[2.0])

Can this construct, however, be used in general? If not, is it illegal Fortran or simply discouraged for other reasons? What can I expect to happen for INTENT(OUT) or INTENT(INOUT) or the implicit use of one of these two?

Thanks!

1 Like

I don’t know if it was legal but passing a scalar to an assumed size array was common prior to F90 introducing rigid TKR rules. Not a good idea in general but its what you sometimes had to do to avoid multiple copies of a routine just to handle the scalar case. If you have INTENT issues, the path of least resistance might be to just make a single element local array, copy the scalar into that and pass the array as the actual argument. Its up to you to decide if the extra verbage is worth it. ie

INTEGER :: I
INTEGER :: IA(1)
REAL      :: R
REAL      :: RA(1)
IA = I
RA = R
CALL SUB(IA, RA)

I do something similar to this in a lot of my codes with assumed shape arrrays. I’ll write the subroutine that does all the work to handle arrays but write an additional wrapper routine for scalars that takes in the scalars, creates local arrays of size 1, and uses those to call the array based subroutine. I’ll then create a generic interface that can call either routine based on if the arguments are scalars or arrays. Yes this is a big kludge but the only other option that might work (and I don’t know enough about them to say for sure) is to use the new assumed rank constructs but that would probably require a lot of code surgery thats probably not worth the effort. Plus, assumed rank is one of those features that might be buggy in some compilers.

1 Like

Assumed rank introduces runtime checks and supports almost no intrinsic functions or other routines, so it would end up just being a wrapper anyways.

1 Like

Like I said I don’t know much about assumed rank so your comment makes sense. Just from what I’ve read, assumed rank is one of those things that looks like a real good idea on paper but it comes with so many restrictions that its really not much use except in some special cases.

equivalence might be useful for this purpose? (though I’ve never used it up to now…)

program main
    implicit none
    integer i, i_(1)
    equivalence (i, i_)

    i = 10
    print *, i   

    !! call sub( i )   !! Error: Rank mismatch (rank-1 and scalar)
    call sub( i_ )

    print *, i

contains

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

end program
1 Like

I would not encourage the use of equivalence. An approach as you suggested would probably work fine though.

1 Like

Situations like this is are one reason I’ve always wanted more fine grain control over TKR for dummy arguments. Maybe something like.

subroutine sub1(a,b)
    real, intent(in) :: a(:)
    real, intent(out) :: b(:)
    allow, scalar :: a, b  

Edit

I know elemental routines would handle most of these cases but not in this case where you are dealing with old legacy codes

1 Like

To answer your questions in order, no this has never been legal fortran. It works because some compilers pass both scalars and arrays by address, so the dummy argument would be addressed the same way in either case. Your example looks a little suspicious because typically the array length would be passed also as an argument (and set to 1 in the scalar actual argument case), but maybe you just posted a short example that does not have that argument.

There is a situation where you can pass an array element to an array dummy argument. This is how array slices (subsets) where passed before the language had array slice notation. But apart from this special case, it has never been allowed to pass a scalar actual argument to an array dummy argument.

Some fortran compiers passed scalar arguments a different way than array arguments. For example, scalar arguments were sometimes passed through registers rather than on the call stack. Depending on the details, this argument passing mechanism would cause the code to fail because of the argument mismatch.

Many (maybe even most) fortran compilers had the ability to detect these argument mismatches under certain conditions (such as when all the code was compiled together), but separate compilations of the caller and the callee would usually preclude this compile time detection. There are also common syntax utilities, such as FTNCHEK, that could detect these programmer errors with f77 code. As you noted, modern fortran has this kind of TKR argument matching built in when the subroutine has an explicit interface.

Your comments about the array arguments are correct. If the dummy arguments are not modified, then you could convert the actual scalar argument variable into an array expression with modern fortran. This option was not available in f77 and before. In f90, the array expression would be (/I/), the shorter [I] notation was introduced in f2003 when the square brackets were added to the fortran character set.

The equivalence trick could be used in f77 in some cases, but only for local or common variables. Dummy arguments (and now module variables) cannot be equivalenced. The equivalence trick works also when the dummy argument is modified, so it is both more and less flexible than the array expression approach.

If you resolve this by introducing arrays of size one, then you must handle yourself the copy-in and the copy-out operations.

IA(1) = I; RA(1)=R
CALL SUBR( IA, RA )
I=IA(1); R=RA(1)
...
2 Likes

@marcus_andreas ,

Welcome to Fortran Discourse!

Are you sure the interface is as you show or are there additional received arguments (parameters in other languages) corresponding to size of the arrays? Say

subroutine SUBR(NI, I2, NR, R2)
INTEGER NI
INTEGER I2(*)
INTEGER NR
REAL R2(*)
..

Or are COMMON blocks or INCLUDE files involved that provide the size information or certain assumptions made that restrict the usability of the subprogram sub. You will have noticed the assumed-size arrays are rather limited in their functionality.

1 Like

@marcus_andreas ,

  1. No. It has been always nonconforming with standard Fortran.

  2. With [ I ] and ] R ], effective arguments of rank-1 come into play that are based on the values of your objects I and R but otherwise the processor has the leeway on how to set them up e.g., a compiler may decide to create a temporary array. Re: “was discouraged in the original thread,” so note with this workaround the program behavior may not be what you seek in more ways than one. Hence caveat emptor applies.

  3. Re: “Can this construct, however, be used in general?” - see comments with 2 above. Note with [ 5 ], etc. you are introducing an additional complication in the form of an unnamed entity which is thus immutable So the callee redefines the received argument - note there is no INTENT attributed - then it is nonconforming (what you consider illegal) and since the onus lies on the programmer with a lot of this in the absence of explicit interfaces, the program is further vulnerable. Hence the “simply discouraged” aspect also.

1 Like

@marcus_andreas ,

@rwmsu provides you with many helpful suggestions and points out the caveats.

You write, “working with a legacy code,” if you have the luxury of refactoring, please strongly consider modernizing this legacy code base using the current standard Fortran that offers better options for structured, modular, functional, object-oriented, and some concurrent execution and parallel programming support.

A common refrain, you will be aware, is the legacy code cannot be modified or it is too complicated a task and thus to be deferred to a later date. If that is the case, consider the wrapper suggestion by @rwmsu and via this wrapper bring in as much modern Fortran aspects as reasonable for present-day more secure and less vulnerable consumption by callers of this legacy code.

Here is an option worth considering which is similar to that advised by @rwmsu and which I had sketched out a few years ago to a team I have worked with in industry and which is still in use because the “legacy code” remains untouched for it being too difficult, there is a new solution using C++ and C# that is yet to be fully accepted by the users. The main aspects of this wrapper are:

  1. allow the caller to work with explicit interfaces
  2. avoid copying of caller data as much as possible using modern Fortran facilities.
  • So say the legacy code is as follows:
! legacy code: usually in fixed-form FORTRAN, shown here in free-form for illustration only
subroutine sub( NI, I2, NR, R2 )
   integer NI
   integer I2(*)
   integer NR
   real R2(*)
   ! Some instructions involving the received arguments
   print *, "In sub:"
   if ( NI > 0 ) print *, "I2 = ", I2(:NI)
   if ( NR > 0 ) print *, "R2 = ", R2(:NR)
end subroutine
  • Then introduce explicit interfaces for the legacy code (Intel compiler helps with it) e.g.,
module interface_m
   interface
      subroutine sub( NI, I2, NR, R2 )
         integer NI
         integer I2(*)
         integer NR
         real R2(*)
      end subroutine
   end interface
end module 
  • Now, make use of the INTERFACE in a wrapper layer to allow the legacy code to be used effectively: note the use of ASSUMED-RANK facility and also the taking advantage of semantics introduced toward interoperability with C companion processor even though there is no C code involved here:
module wrapper_m
   use, intrinsic :: iso_c_binding, only : c_loc, c_f_pointer
   use interface_m, sub_assumed_size => sub
contains
   subroutine sub( I2, R2 )
      ! Argument list
      integer, intent(inout), target :: I2(..)
      real, intent(inout), target    :: R2(..)
      ! Local objects
      real, pointer :: pR2(:)
      integer, pointer :: pI2(:)
      call c_f_pointer( cptr=c_loc(I2), fptr=pI2, shape=[ size(I2) ] ) 
      call c_f_pointer( cptr=c_loc(R2), fptr=pR2, shape=[ size(R2) ] ) 
      call sub_assumed_size( size(I2), pI2, size(R2), pR2 )
      pI2 => null()
      pR2 => null()
   end subroutine
end module 
  • The callers (users) are then setup to work with legacy code via the wrapper layer only, the original legacy code is “hidden” away in a backend “black box”
   use wrapper_m, only : sub
   integer :: m, n(3), o(2,3)
   real :: x, y(3), z(2,3)
   integer :: i
   m = 42 ; x = 99.0 
   call sub( m, x )
   n = [ 1, 2, 3 ] ; y = [ -100., -200., -300. ] 
   call sub( n, y )
   o = reshape( [( i, i=1,size(o) )], shape=shape(o) )
   z = reshape( [( 42.0, i=1,size(z) )], shape=shape(z) )
   call sub( o, z )
end 

So you can try this out with gfortran or Intel compiler to see it in action:

C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe
 In sub:
 I2 =           42
 R2 =    99.0000000
 In sub:
 I2 =            1           2           3
 R2 =   -100.000000      -200.000000      -300.000000
 In sub:
 I2 =            1           2           3           4           5           6
 R2 =    42.0000000       42.0000000       42.0000000       42.0000000       42.0000000       42.0000000

C:\temp>

So now you have the appearance of legacy code SUB in a modern Fortran caller which continues to use the legacy code “under the hood” but which can work with any rank arguments, including scalar, in a standard-conforming and efficient manner.

Keep in mind the adage YMMV. There is no solution or workaround that may apply to all cases, especially with legacy code that may have relied on additional nonstandard extensions. Hence adaptability is key. And make use of this Discourse, as you are doing, to seek out comments from many readers on other complications you may face.

1 Like

The following code uses the BLAS library to block multiply the last 10x10 blocks of A and B, and stores the matrix in the lower 10x10 block of C.

program test
implicit none

real(8) a(100,100),b(100,100),c(100,100)

a(:,:)=2.d0
b(:,:)=3.d0

call dgemm('N','N',10,10,10,1.d0,a(91,91),100,b(91,91),100,0.d0,c(91,91),100)

print *,c(91:100,91:100)

end program

I was always told that (in the absence of an explicit interface) Fortran always passes by reference. The above code works fine because of this.

How would you make this standard-conforming?

The above code works because of storage sequence requirements of the language. It could be implemented through pass-by-reference or by copy-in/copy-out. With the reference fortran dummy argument declarations, the code is standard conforming even with an explicit interface.

The posted code is standard conforming.

There is possibly an issue regarding the dgemm() dummy argument declarations. If they were declared effectively as for example, A(100,10), where the dimension variables have been substituted with their values, then there would be a possible problem because the dummy array elements A(11:100,10) are outside of the range of the actual argument declaration. Within dgemm(), those elements are not referenced, so in practice it would not typically cause problems, but there is a potential issue regarding the language semantics (consider, for example a copy-in/copy-out argument association).

However, in the reference implementation of dgemm() the dummy argument is declared as A(100,*) (with value substitution). With this assumed-size declaration there is no problem, and the posted code is fully conforming, provided of course that no dummy argument elements beyond A(10,10) are referenced. Even a copy-in/copy-out argument association is supposed to work correctly in this case.

This is the situation I had in mind when I posted that previous statement. The above code looks like you are passing a scalar array element actual argument to an array dummy argumment. But this situation is an exception and, through storage sequence association requirements, it is standard conforming and it is required to work.

The code conforms, oddly, due to sequence association even with explicit interfaces, see example below:

   integer :: x(3,3)
   x = reshape( [( i, integer :: i = 1, size(x) )], shape=shape(x) )
   call sub( size(x(2:,2:), dim=1), a=x(2,2), le=size(x(2:,2:),dim=2) )
contains
   subroutine sub( la1, a, le )
      integer :: la1
      integer :: a(la1,*)
      print *, "a = ", a(:,1:le)
   end subroutine 
end program
C:\temp>ifort /standard-semantics /free p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 a =  5 6 7 8

As to the shown case using DGEMM, a coder using modern Fortran might also consider, in addition to explicit interfaces,

   double precision, target :: a(100,100),b(100,100),c(100,100)
   ..
   double precision, pointer :: pa(:,:), pb(:,:), pc(:,:)
   ...
   pa => a(91:,91:)
   pb => b(91:,91:)
   pc => c(91:,91:)
   call dgemm(..,..,..,..,..,..,a=pa,lda=10,b=pb,ldb=10,..,c=pc,..)
   ..

This works because the compiler makes contiguous temporary copies of the three arrays. There could be considerable overhead with this approach in the general case.

This is one of the problems with the BLAS and LAPACK libraries. The underlying code is based on f77 array indexing conventions, and it has never been updated to allow modern fortran argument association.

@rwmsu @FortranFan Thank you both for your suggestions. I’m leaning towards using a wrapper layer here, particularly for cases where a subroutine is called from many different locations in the code as it is more elegant and probably less work. Re-factoring would be a bigger project and perhaps not justified to solve this particular problem, although I have it in mind at a later point, perhaps for the most crucial parts of the code.

@FortranFan Thank you also for writing out the example also adapted for C interoperability. In this concrete case it is probably not needed, but I might actually have to think about C interoperability soon elsewhere in the code. So it is much appreciated!

I had to look up equivalence and agree that it is not the most self-evident feature. The approach of @septc would, however, be quite an elegant solution. I wonder, what are your arguments against it?

Edit: @RonShepard sheds some more light in his reply above, quoted below - thanks!

Thank you! I have been reading here for a while and find there is a wealth of knowledge shared by the users in this place.

Array sizes are in fact not passed explicitly, as perhaps used to be conventional for code like this. But you are right, the example is shortened, often information about the array size is passed implicitly (in a not very obvious way) by passing some string defining, so to speak, a ‘case’ for the subroutine. At other times it is not clear to me if size information is passed implicitly or not.

I do not quite understand, what other side effects apart from the possible creation of temporary arrays do you expect? Typically scalars or small arrays are passed into these subroutines, I wonder if these actually warrant implementing a different solution to the [I],[R] workaround.

Good point, while the original code does not use any INTENT I have introduced INTENT(IN) for the sake of this work-around.

The INTENT(IN) declaration, along with an explicit interface, helps the compiler identify argument mismatches at compile time. But it is the programmer’s responsibility to also ensure that those dummy arguments are not actually modified. Such modifications are illegal, of course, but there is much trickery that a programmer can do to modify an INTENT(IN) argument in ways that the compiler cannot detect. If the programmer does succeed in fooling the compiler, then the behavior is unspecified by the standard. The program could abort, for example by attempting to modify read-only memory, or it could run and produce incorrect results, or it could run and produce apparently correct results, or it could run and start WW III.

1 Like