Curious result with ASSOCIATE

I am trying to use ASSOCIATE in a somewhat creative way:

program moa_assoc
    implicit none

    integer, parameter   :: n = 20
    real, dimension(n,n) :: x, y

    x = 1.0

    !
    ! Use x also for result
    !
    associate( a => x(3:n,:), b => x(1:n-2,:), c => x(2:n-1,:) )
        c = a + b
    end associate

    write(*,'(20f5.1)') x(:,2)

    !
    ! Use y instead
    !
    x = 1.0
    y = 1.0

    associate( a => x(3:n,:), b => x(1:n-2,:), c => y(2:n-1,:) )
        c = a + b
    end associate

    write(*,'(20f5.1)') y(:,2)
end program moa_assoc

While I will probably get the right answer in the full application I have in mind, I am curious as to the difference between the two ASSOCIATE blocks. The result is this:

  1.0  2.0  3.0  4.0  5.0  6.0  7.0  8.0  9.0 10.0 11.0 12.0 13.0 14.0 15.0 16.0 17.0 18.0 19.0  1.0
  1.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  2.0  1.0

I expected the first line to be the same as the second one, but either I am mistaken or there is something odd about this use of ASSOCIATE. I got this result with both gfortran and ifx.

So, is my understanding of ASSOCIATE less than perfect or is the outcome wrong?

In the first case, in the implicit loops, I think x(2,:) is modified then used to compute x(3,:), etc. In the second case, it is y() which is modified step by step and it does not impact the following computations.

Indeed, that is how I explain the result myself, but the question is: is this the correct behaviour? I would think that the ASSOCIATE construct would, magically, result in code where array operations are used, as that is superficially the nature of the statement. In that case, the left-hand side should remain untouched until the right-hand side has been evaluated.

It would imply a copy operation, either on the left-hand side (before computation) or the right-hand side (after computation).

Once again, the standard text is quite vague on some important points, and I really can’t tell if your code is standard conforming or not…

But I’m not surprised by the result: for, I usually see the ASSOCIATE construct as it is was a kind of inlined internal subroutine, and I see the associate names as if they were dummy arguments. So, you are in an equivalent situation where you are modifying a dummy argument that is aliased to another dummy argument, which is forbidden.

Thanks, my application would use the second kind of use, so there the problem of updating an aliased dummy argument as it were, would not play a role. It simply surprised me, henve my question.

Indeed initially surprising, but I think the standard does declare that non-conforming as it does say in the description for ASSOCIATE:

  • If selector is not a variable or is a variable that has a vector
    subscript, associate‐name shall not appear in a variable definition
    context.

So since C has a vector subscript, it cannot appear on the LHS, if I am reading that right.
But I would then expect the compiler to produce an error or warning. Is the compiler obligated to produce an error or warning? Am I reading that wrong? As that says that using Y with a subscript for C is also not allowed.

I think that by vector subscript, the standard refers to something like c([1,2,4,5]), which is not the case here.

Here c => x(2:n-1,:) is a variable (i.e., designator → array-section, etc.), not an expression.

1 Like

Ahhh, that makes more sense. I was reading that simply as “subscript”. I do not think I have ever used “vector subscripts” so I did not even realize that had a different meaning than that.

Same goes for multiple-subscript, subscript-triplet, multiple-subscript-triplet
for the most part.

The compilers back that up, reporting an error if “J=123” is uncommented.

! vector-subscript
integer :: i(3)

   i=[10,20,30]
   write(*,*)i([3,2,1])

   i([2,3,1])=[(k,k=11,33,11)]
   write(*,*)i

   i=[10,20,30]
   associate(j=>i([2,3,1]))
   write(*,*)j
   !j=123  ! DOES PRODUCE COMPILE-TIME ERROR

end associate

end

I think this is correct, but I don’t see those kinds of limitations (like aliasing restrictions) mentioned in the standard.

If you add the statements

    x = 1.0
    x(2:n-1,:) = x(3:n,:) + x(1:n-2,:)
    write(*,'(20f5.1)') x(:,2)

then with gfortran you see that the, presumably correct, results are the same as using the separate variable y(:,:) on the lhs.

Also, if you replace c=a+b with x(2:n-1,:)=a+b in the first ASSOCIATE block, then the same, presumably incorrect, results are generated. In this case, the “dummy arguments” would still violate the aliasing restrictions, so it makes the same mistake when computing the results.

That still does not say whether this is a programmer error or a compiler error, just that the ASSOCIATE restrictions appear to be consistent with dummy argument restrictions for this one compiler.

1 Like

I can’t find such restrictions either. This means that in theory the example posted by the OP should work (i.e. the 2 results should be identical).

But this puts a lot of burden on the compiler to sort out what is aliased to what, because the user can’t help the compiler with the “pointer/target” attributes here.

Well, it does not really matter for my use case, but it was surprising. I have always been surprised anyhow by the flexibility of ASSOCIATE.