Array element actual argument & assumed size dummy

The following code does not compile (whichever the compiler):

program foobar
implicit none

    integer :: x(100)
    x = 1
    call foo(x)

contains

    subroutine foo(x)
    integer, contiguous :: x(:)
    call bar(x(10))   ! error here
    end subroutine

    subroutine bar(x)
    integer :: x(*)
    print*, x(1)
    end subroutine

end

Error message:

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 can see the reason for the “not assumed shape” restriction: if the dummy argument of foo is assumed shape, then it can be discontiguous. bar is expecting a contiguous array, which means that copy-in/copy-out should occur, but what should be copied is possibly ambiguous to the compiler.

However, the dummy argument of foo is specified as contiguous here, so that no copy-in/copy-out is required anyway.

Isn’t it a too strong restriction?

2 Likes

What happens if you use a range like x(10:)?

1 Like

It works. But there are some cases where passing an array element (i.e. an address and nothing else) is really what is needed (the toy example here is too simplistic to illustrate the cases where it’s needed)

EDIT: the usage case is mainly when calling a C or a legacy F77 routine. For instance a FFT routine, and imagine you want to perform 1D FTTs along the 3rd dimension of a cube. You would write something like:

interface 
   subroutine cfft( buf, len, nvect, inc, incv )
   complex :: buf(*)
   integer :: len     ! fft length
   integer :: nvect   ! number of vectors to transform
   integer :: inc     ! increment between 2 adjacent elements of a vector
   integer :: incv    ! increment between the first elements of 2 adjacent vectors
   end subroutine
end interface

complex :: x(:,:,:)   ! the shape is [n1,n2,n3]

do i2 = 1, n2
   call cfft( x(1,i2,1), n3, n1, n1*n2, 1 )
   ! this could be alternatively:
   ! call cfft( x(:,i2,:), n3, n1, n1, 1 )
   ! but copy-in/copy-out would occur
end do

It also works with ifx if you remove bar and compile/link it separately from foobar. This is as it should be for backwards compatibility with f77 where there were no explicit interfaces for the compiler to check TKR against.

Edit.

This is an example of one of the more frustrating things you have to deal with when refactoring old code to modern coding practices. You can’t tell if the actual argument is supposed to be associated with a scalar, or if its suppose to be the address of a subsection of an array thats associated with an assumed size array. I’ve always wanted a way to override rigid TKR checking on a local basis (on the dummy argument side of the subroutine). Maybe by a compiler directive or a new dummy array attribute. As Ivan points out, the fix is simple. It’s just sometimes takes a lot of digging through code to determine what the intent of the original programmer was.

Here is a modified version of your code that, I think, cannot achieve the desired storage sequence association with the assumed shape dummy argument.

program foobar
   implicit none
   integer :: i, x(3,3) = reshape([(i, i=1,size(x))],shape(x))
   
   call bar(x(2,2))
   call foo(x)

contains

   subroutine foo(x)
      integer, contiguous :: x(:,:)
      !call bar(x(2,2))   ! error here
      call bar(x(2:,2:))
   end subroutine foo
   
   subroutine bar(x)
      integer :: x(*)
      print*, x(1:3)
   end subroutine bar
   
end program foobar

$ gfortran foobar.f90 && a.out
           5           6           7
           5           6           8

The call bar(x(2,2)) in the main program gives the desired association, and it is legal there because the array is not assumed shape. However, that same call statement is not legal within foo() where the dummy argument is assumed shape. Furthermore, I don’t think there is a call statement within foo() that does give the desired storage sequence association. I added call bar(x(2:,2:)) just to show one such attempt, but of course it associates the incorrect third element of the array. I didn’t test it, but I’m certain that copy-in/copy-out is being performed for the argument association (from foo to bar), so it is easy to see why that third element does not match for the two calls.

edit: I found a way to get the correct array element association within foo().

associate (b=>x)
   call bar(b(2,2))
end associate

Presumably this would work in the original code too.

edit2: The above associate block incantation only works with gfortran, it does not work with nagfor. I further verified with both gfortran and nagfor that c_loc(b(2,2)) and c_loc(x(2,2)) are the same, so no copy-in/copy-out is being done for just the associate block.

Well, that’s not really the point here. When the dummy argument is an assumed size or explicit shape array, the TKR conformance is relaxed to a TK conformance: the actual argument can have any rank, or it can be a single element of an array.

The issue that I wanted to highlight here is the restriction “…that is not assumed shape”, which I find unnecessarily restrictive if the assumed shape array is declared contiguous.

Yes I know that (and please don’t assume I didn’t). My question is the restriction you quote a recent one. I always thought it was relaxed to TK as I implied above just so all the f77 code etc. that operated that way would still work. Again, it does work if there is no explicit interface seen by the compiler. The issue is in the light of the “can’t break existing code” mantra that many Standards folks quote like its devine scripture, why (if this is a recent addition) did they go out of their way to break so much code.

That might be just a coincidence. I suspect that it still violates the standard, whether the interface is implicit or explicit.

How can it violate the standard if the standard allowed it for several decades before F90 introduced explicit interfaces. I’ve seen a lot of old code where a scalar or the inner-most dimension of a multi-dimensional array was passed to an assumed size array. It was common practice to try to improve vectorization performance by passing a 3D array of say size NX x NY x NZ to a 2D assumed size array A(NX*NY,*) to get a longer vector length (NX*NY) on systems like the Cyber 205 that wanted a long vector length. The fact that error is only thrown when there is an explicit interface indicates to me (as @PierU suggests) that in this particular case there is an over-rigid intepretation of the Standard. Also, my original question stands. Is this a recent addition to the Standard.

If the explicit interface is removed the error indeed goes away, but this is just because the compiler can no longer check the correctness of the call. It does not make the code legal.

And I don’t think the restriction is recent, it probably goes back to Fortran 90. The restriction actually makes sense, but I think it should have been updated when the contiguous attribute went into the standard.

Explicit interface for all the calls, just one case that is illegal:

program foobar
implicit none

    integer :: x(100), y(100,100)
    x = 1

    call bar( x(10) )    ! legal
    call bar( y )        ! legal
    call foo( x, y )

contains

    subroutine foo(x, y)
    integer, contiguous :: x(:)
    integer             :: y(*)
    call bar( x(10) )    ! illegal
    call bar( y(10) )    ! legal  
    end subroutine

    subroutine bar(x)
    integer :: x(*)
    print*, x(1)
    end subroutine

end

I guess we can agree to disagree. Passing an assumed shape array to an assumed size array without an interface has to the best of my knowledge always been legal even without an interface (and it helps I guess if you declare things without an interface EXTERNAL). You just run the risk of a copyin/copyout. What is illegal but sometimes works is passing an assumed size array to an assumed shape array. Also, why you can’t use an assumed shape array in any routine thats not in a module or has an explicit interface block for the routine. This is one of the reasons you can’t pass an assumed size array to an intrinsic function (other than the BOUND functions if I remember correctly). Again, if it was legal prior to Fortran 90 given the Standards committee’s fixation with not breaking existing code, why is it illegal now.

Edit.

I thought one of my Fortran books had a section that addressed this problem but couldn’t remember which one it was. Look in Adams et al, “Fortran 95 Handbook” at the discussion of array element sequence association (Chapter 12 section 12.7.2 and 12.7.2.1). Other than the explicit interface, I don’t see why for your example the compiler doesn’t see this as a case of array sequence association. I’ll admit that I’m looking at only a small part of the problem and will accept that there is other language in the Standard that overrides this. I’m just curious as to where it is. Since I quit using assume size arrays a long time ago I only see this problem in old code that I usually convert to assumed shape anyway.

Assumed shape arrays did not exist before f90, so this situation could not have possibly occurred before then. Remember, this discussion is specifically about a restriction on the use of assumed shape arrays, not the more general situations which were, and are still, allowed.

Again, my question is why isn’t the example given above a case of argument sequence association. I’m not trying to pick fights, just trying to understand where in the Standard it says this is not a case of AES association as defined in the Fortran 95 Handbook.

For f2023, it is section 15.5.2.12:

1 Sequence association only applies when the dummy argument is an explicit-shape or assumed-size array.

As you point out, passing an array element actual argument to a dummy array argument works because of storage sequence association. This case is described in the paragraphs that follow the above sentence.

edit: In the f2003 document, section 12.4.1.1 has the sentence:

If the actual argument is scalar, the corresponding dummy argument shall be scalar unless the actual argument is an element of an array that is not an assumed-shape or pointer array, or a substring of such an element.

edit2: I just checked the f90 and f95 documents, and that same sentence also appears in section 12.4.1.1 in those documents.

1 Like

Again, I am not talking about passing an assumed shape array to an assumed size (or explicit shape) array, which is of course legal, but about the specific case of passing an element of an assumed shape array to an assumed size array.

With gfortran -fcheck=array-temps, Line (*2) creates an array temporary while Line (*1) does not (and I have not tried other compilers yet):

    subroutine foo(x)
    integer, contiguous :: x(:)

    !! call bar(x(10))   ! error here
    call bar(x(10:))   ! compiles (no array temp)  (*1)
    !! call bar(x(10::2))   ! compiles (array temp) (*2)

    end subroutine

So in the following code also, we could use call cfft( x(1:,i2,1), ... ) to pass the address of the `x(1,i2,1)…?

1 Like

This will indeed work in practice, I guess. However, although the call is legal, I think it’s illegal for the cfft routine to access the elements past the n1 elements that are passed. Again, it will work in practice because the compiler has no reason to copy-in/copy-out the x(1:,i2,1) array section, but it could.

The standard says:


Going one step further, if the argument in the call were x(1:,i2,1:), then with an implicit interface (or the appropriate explicit interface) I think the compiler would be required to do the copy-in/copy-out, and the stride argument would need to be changed (to n1 I think) to account for the contiguous nature of the intermediate array copy. On the other hand, if the dummy argument were an assumed shape 2D array with an explicit interface, then the compiler would not be required to make a temporary copy (although it could if it wanted).

When the actual and dummy array arguments are explicit shape or assumed size, then the actual argument x(1,i2,1) is standard conforming. When the actual array is assumed shape, then x(1,i2,1) is not standard conforming, and compilers will catch the error and likely print an informative error message. The argument x(1:,i2,1) is not standard conforming, but it is likely to work nonetheless, without a compiler warning. The argument x(1,i2,1:) is not standard conforming, and it will almost certainly fail because the compiler will generate an intermediate 1D array of length n3, and then the subroutine will try to references n1*n3 elements in that array. The argument x(1:,i2,1:) is standard conforming, but it would require some of the other arguments in the call to change. All that seems complicated, even for an experienced programmer.