Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Parameter passing and Interfaces

ThermoX
Beginner
1,152 Views

Greetings,

I can't seem too get the behavior I want in the following case.

I have an interface that looks like this:

      INTERFACE
        SUBROUTINE SUBA(PA_FP)
          REAL(4) PA_FP(:)
        END SUBROUTINE
      END INTERFACE

When I call that subroutine using a 1D Array, everything compiles and works fine.  However, if I have a 2D array and I call the subroutine as such:

REAL(4) ARRAY2D(10,20)

C Some code...

DO I = 1, 20
  CALL SUBA(ARRAY2D(1,I))
END DO

I get a compile error #6634: The shape matching rules of actual arguments and dummy arguments have been violated.
 

Clearly, the interface defines the parameter as a 1D array but by passing the parameter as I did above, I'm actually passing the address of a scalar.  So I tried calling it like this, instead:

REAL(4) ARRAY2D(10,20)

C Some code...

DO I = 1, 20
  CALL SUBA(ARRAY2D(:,I))
END DO

The compiler is now happy, but I'm not getting the expected behavior from within SUBA.  SUBA does not see the proper array content.

Note that without the interface definition, the first method works just fine.

So what's the proper way of calling SUBA in the case of a 2D Array, such that SUBA "sees" the 1D array only?

Steve?

(hey, it's always you ;) )

 

0 Kudos
1 Solution
mecej4
Honored Contributor III
1,152 Views

ThermoX wrote:
What do you mean, they're not consistent?

You can see for yourself by running the compiler on the following test code, first without and then with the option /warn:interfaces:

program pgm

   interface
      subroutine sub(Y)
      integer :: Y(:)
      end subroutine
   end interface

   integer i,A(20)

   do i=1,20
      A(i)=2*i-1
   end do
   call sub(A)
   
end program

subroutine sub(X)

   integer :: X(10)
   write(*,10)(i,X(i),i=1,10)
10 format(2I8)
   return

end subroutine

What you did, if unintentionally, amounts to giving the compiler false information.

Some of the things that you said about array arguments raise a suspicion that you believe that passing an array as argument merely requires passing an address. That was commonly true in Fortran 77 and earlier, which is why an implicit interface was sufficient. But now, since we have assumed shape arrays and allocatable arrays in Fortran 90 and up, the rules regarding array arguments are considerably more complex. You can remain oblivious to the complexities if you only use assumed-size array arguments; otherwise, please read the relevant chapters in a Fortran manual or book.

View solution in original post

0 Kudos
14 Replies
Arjen_Markus
Honored Contributor I
1,152 Views

What do you mean with SUBA not seeing the proper content? In your call you pass an array section and that is all that the subroutine will see and is supposed to see.

If the subroutine works on individual elements, then an elemental routine might help - that type of routines uses one element of an array (or a scalar) at a time, but just like SIN(..) and other intrinsics it gets to process the whole array, regardless of the dimensionality.

If the argument is read-only, you might try with RESHAPE to convert the argument to 1D. Otherwise you could do:

tmp = reshape( array, [size(array)] )
call suba( tmp )
array = reshape( tmp, shape(array) )

But that is not quite what you want I guess.

By the way: these things are called arguments in Fortran, not parameters - parameters are named constants

0 Kudos
ThermoX
Beginner
1,152 Views

Hi Markus,

First... You're right about using Argument vs Parameter.  I actually was aware of this whole thing about the proper name to use but I didn't quite remember what it was and didn't feel like spending time on looking into it.  It's also not just the case in Fortran, if I recall. Many, including me, tend to blindly use Parameters in this context, regardless of the programming language.... but you're right, it's not right.

Anyway...

When I say that SUBA does not see the proper content, I mean that the individual array values, as seen within SUBA, are not at all the values of the array section I was trying to send.  Without the INTERFACE definition, and using the (1,I) approach, the array values seen from within SUBA are fine.

Thanks for your inputs.

0 Kudos
mecej4
Honored Contributor III
1,152 Views

The OP did not show the declarations and the heading of the subroutine. Does the actual subroutine code match the interface provided to the caller? If it was known in advance that the subroutine would be called sometimes with 1-D array arguments and at other places with 2-D array arguments, why was an assumed-shape interface used?

0 Kudos
ThermoX
Beginner
1,152 Views

SUBA is declared as such:

SUBROUTINE SUBA(PA_FP)

REAL(4) PA_FP(PASIZE)

Where PASIZE is some global constant containing the size of that array.

Note that SUBA is ALWAYS expecting a 1D array and that's what my calling code is supposed to pass, i.e. a series of 1D arrays through a DO LOOP.

Again, the code works fine without the INTERFACE definition and using the (1,I) approach. It's the INTERFACE definition that forces me to use something else than (1,I).  And when I try to use (:,I) instead, the compiler is now ok with it since *that* matches the format of the INTERFACE definition... but in this case, the content f the array is all messed up from within SUBA.

I guess I could define the INTERFACE as passing a scalar, instead of a 1D array. In this case, (1,I) would work.  But then, when passing actual 1D array, I'd have to pass them as ARRAY1D(1), instead of just ARRAY1D.

This doesn't look right.  Surely, there must be a way to pass a 1D subsection of a 2D array to a subroutine that expects a 1D array, when defining an INTERFACE.

0 Kudos
mecej4
Honored Contributor III
1,152 Views

That confirms what I had suspected: the interface provided to the caller is not consistent with the actual interface. If the body of the subroutine had been visible to the compiler (by being in the same source file, or if you had specified /warn:interfaces) it would have flagged the error.

0 Kudos
ThermoX
Beginner
1,152 Views

What do you mean, they're not consistent?  How else should I define the Interface or the Subroutine, then?

Thanks.

0 Kudos
ThermoX
Beginner
1,152 Views

I mean, the INTERFACE defines the argument as a 1D array.  It doesn't define the size of that array but that should be irrelevant as the address passed should be the same, regardless.  I can't see why actually defining the size of the argument within the subroutine would change that behavior.

0 Kudos
ThermoX
Beginner
1,152 Views

Well... I stand corrected!  When I actually define SUBA as such:

SUBROUTINE SUBA(PA_FP)

REAL(4) PA_FP(:)

Instead of the sized array, then PA_FP now sees the proper values!  What's more (and this is REALLY puzzling me), SUBA actually "knows" the size of PA_FP (as seen in debugger), even though SUBA was never told explicitly??

This clearly points to a larger understanding problem on my part.  What the heck is going on in this case??  

0 Kudos
mecej4
Honored Contributor III
1,153 Views

ThermoX wrote:
What do you mean, they're not consistent?

You can see for yourself by running the compiler on the following test code, first without and then with the option /warn:interfaces:

program pgm

   interface
      subroutine sub(Y)
      integer :: Y(:)
      end subroutine
   end interface

   integer i,A(20)

   do i=1,20
      A(i)=2*i-1
   end do
   call sub(A)
   
end program

subroutine sub(X)

   integer :: X(10)
   write(*,10)(i,X(i),i=1,10)
10 format(2I8)
   return

end subroutine

What you did, if unintentionally, amounts to giving the compiler false information.

Some of the things that you said about array arguments raise a suspicion that you believe that passing an array as argument merely requires passing an address. That was commonly true in Fortran 77 and earlier, which is why an implicit interface was sufficient. But now, since we have assumed shape arrays and allocatable arrays in Fortran 90 and up, the rules regarding array arguments are considerably more complex. You can remain oblivious to the complexities if you only use assumed-size array arguments; otherwise, please read the relevant chapters in a Fortran manual or book.

0 Kudos
Arjen_Markus
Honored Contributor I
1,152 Views

More complex, but the solution is very simple: make sure that the routines are contained in a module or in a subprogram.

As mecej4 is hinting at, assumed-shape arrays carry extra information allowing the (sub)program to examine the size and dimensions of the array that is actually passed. That makes it much less error-prone than the old FORTRAN 77 way, where the user was responsible for passing the right sizes.

0 Kudos
ThermoX
Beginner
1,152 Views

I've been exposed!

Yes, our stuff is really old and we still use Fixed Format Fortran.  We also almost never use INTERFACES in our case.  In fact, I'd venture to say that I'm pretty much the only one who uses them in my field.  And I only use them because I want to set pointers through subroutine calls, something I cannot seem to be able to do otherwise.

I had no idea that using (:) and INTERFACES would carry hidden information about the passed arrays!

That worries me a little... I might have to look back at some of my other stuff...

Thanks for all the inputs!

0 Kudos
mecej4
Honored Contributor III
1,152 Views

ThermoX wrote:

I've been exposed!

How about "enlightened" instead?

I had no idea that using (:) and INTERFACES would carry hidden information about the passed arrays! 

It is when this information is being passed that interfaces are required. If the called subroutine does not know that a descriptor is being passed to it, or it expects a descriptor when none was passed, runtime errors are almost inevitable.

That worries me a little... I might have to look back at some of my other stuff...

If you have old code with only assumed-size array arguments, no need for worry. Otherwise, a few runs with /check:all and /warn:interfaces should catch the mismatched interfaces.

0 Kudos
ThermoX
Beginner
1,152 Views

Hello again mecej4,

Thanks for the additional information.

If you have old code with only assumed-size array arguments, no need for worry. Otherwise, a few runs with /check:all and /warn:interfaces should catch the mismatched interfaces.

I've already enabled /warn:interfaces, after your other comment.  Now I'm getting a crap load of errors in some black box code we have.  I'll have to disable it there cause there ain't no way I'm gonna try to fix that ugly mess!

Thanks again.

0 Kudos
ThermoX
Beginner
1,152 Views

The /warn:interfaces switch is a pretty powerful diagnostic option!

0 Kudos
Reply