How ASSOCIATE works

I have experimented with the ASSOCIATE and have come up with some “rules” about how it works. (Of course, the true rules are defined in the standard.) A few things did surprise me. The rules are illustrated with a code, where (n) in a comment indicates which rule applies. Since I may tweet about this, corrections are especially welcome.

The LHS and RHS of an ASSOCIATE statement are termed the associate-name and selector.

associate (pi => 3.14) ! pi is associate-name, 3.14 is selector

(1) Each ASSOCIATE statement must be followed by an END ASSOCIATE

(2) If ASSOCIATE appears in a loop, END ASSOCIATE must appear in the same loop.

(3) If the selector of an ASSOCIATE is a variable, the associate-name
can be changed in an ordinary assignment, which also changes the variable.

(4) If the selector of an ASSOCIATE is an expression, the associate-name
cannot be changed in an ordinary assignment.

(5) An associate-name can appear in an ASSOCIATE statement even if it previously
appeared in an ASSOCIATE statement that has not been terminated.

(6) The associate-name is not ALLOCATABLE even if the selector is, so it
stays the same size within the ASSOCIATE construct. If the selector is
an unallocated allocatable array, the associate-name is a zero-size array.

program demonstrate_associate
implicit none
integer :: i,j
integer, allocatable :: v(:), w(:)
do i=1,3
   associate (x => real(i))
   print*,i,sqrt(x)
   end associate ! (1) must appear here, not after end do
end do
j = 2*i
associate (n => i)
n = 10
associate (n => 2*n)
print*,"@ n=",n
! (4) n = 100 ! invalid -- cannot change n when it is assigned an expression 
associate (n => 2*n) ! (5) n is associated to a new value
print*,"@@ n=",n
v = [10,20]
associate (c => v, d => w) ! (6) c and d are not allocatable even though v and w are
c = [2,4]
print*,"c =",c
w = [10,20]
print*,"d =",d ! (6) d has zero size even though size(w) = 2
! d = [10,20] ! (6) invalid since d has zero size and is not allocatable
end associate ; end associate ; end associate; end associate
end program demonstrate_associate
! output with gfortran and Intel Fortran:
!            1   1.000000    
!            2   1.414214    
!            3   1.732051    
!  @ n=          20
!  @@ n=          40
!  c =           2           4
!  d =
2 Likes

The NAG Fortran compiler considers “d => w” a runtime error, since w is not currently allocated. The sitiuation is the same if a POINTER w were not associated.

19.5.1.6 Construct association
1 Execution of a SELECT RANK or SELECT TYPE statement establishes an 
association between the selector and the associate name of the construct. 
Execution of an ASSOCIATE or CHANGE TEAM statement statement establishes 
an association between each selector and the corresponding associate name 
of the construct. 

2 In an ASSOCIATE or SELECT TYPE construct, the following rules apply. 

• If a selector is allocatable, it shall be allocated; the associate name is 
associated with the data object and does not have the ALLOCATABLE attribute. 

• If a selector has the POINTER attribute, it shall be associated; the 
associate name is associated with the target of the pointer and does not have 
the POINTER attribute.
1 Like

Thanks – I was wondering about that. The revised rule 6 is

(6) The associate-name is not ALLOCATABLE even if the selector is, so it
stays the same size within the ASSOCIATE construct. A selector may not
be an ALLOCATABLE array that is not ALLOCATED.

That’s strange as a similar (but much simpler test):

program assaloc
  real, allocatable :: x(:)
  associate (a => x)
    allocate(x(5))
    x = 1.1
    print *, size(x), x
    a = 2.3
    print *, size(a), a
  end associate
end program assaloc

on my MacOS laptop segfaults with gfortran 11.2 right after first print:

 5   1.10000002    1.10000002    1.10000002    1.10000002    1.10000002
 Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

while ifort 2021.5.0 gives, exactly as @Beliavsky points,

  5   1.100000    1.100000    1.100000   1.100000   1.100000
  0

Strange also to find compiler issues in two implementations with a Fortran 2003 feature, how long will it be before both these compilers help produce the following expected output instead?

5   1.100000    1.100000    1.100000   1.100000   1.100000
5   2.300000    2.300000    2.300000   2.300000   2.300000

@FortranFan, could you self-comment on that? If the standard, as @themos pointed, requires that the allocatable selector should be allocated, which is not the case in my snippet, how can we expect a to be associated with x allocated after the association?

1 Like

I think it unwise to introduce language such as “may not”, in place of the “shall not” of the standard.

1 Like

Well, we can expect ANYTHING to happen because we have left the standard behind.

1 Like

If you write

integer, allocatable :: v(:)
! set v
associate (c => v)

are you allowed to allocate v to a different size before the ASSOCIATE is terminated? If so, what happens to c? Gfortran and Intel Fortran give different results when doing so:

program demonstrate_associate
implicit none
integer, allocatable :: v(:)
v = [3,4]
associate (c => v) ; call disp("1",v,c)
c = c*10           ; call disp("2",v,c)
v = [2,4,6]        ; call disp("3",v,c)
c = c*10           ; call disp("4",v,c)
v = [2]            ; call disp("5",v,c)
end associate
contains
subroutine disp(label,v,c)
character (len=*), intent(in) :: label
integer, intent(in) :: v(:),c(:)
write (*,"(a,' v = ',*(1x,i0))",advance="no") label,v
write (*,"(3x,'c = ',*(1x,i0))") c
end subroutine disp
end program demonstrate_associate

gfortran 12.0.1 20220213 output:

1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  2 4
4 v =  20 40 6    c =  20 40
5 v =  2    c =  2 40

Intel Fortran 2021.5.0 Build 20211109_000000 output:

1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  30 40
4 v =  2 4 6    c =  300 400
5 v =  2    c =  300 400

In the example you provide, c does not have the ALLOCATABLE attribute (11.1.3.3) “The associating entity does not have the ALLOCATABLE POINTER attributes; it has the TARGET attribute if and only if the selector is a variable and has either the TARGET or POINTER attribute.”

Curiously, I don’t get the Intel Fortran 2021.5.0 results you show:

1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  2 4
4 v =  20 40 6    c =  20 40
5 v =  2    c =  20 40

Are you sure you have labeled these correctly?

Does that mean it is invalid to resize v within the ASSOCIATE block? Or is it only invalid to resize v and then refer to c? Or only invalid to resize v and refer to c when c is associated with elements of v that no longer exist?

I do get the output shown with Intel Fortran.

transcript

c:\fortran\tweets\unposted>type associate_alloc.f90

program demonstrate_associate
implicit none
integer, allocatable :: v(:)
v = [3,4]
associate (c => v) ; call disp("1",v,c)
c = c*10           ; call disp("2",v,c)
v = [2,4,6]        ; call disp("3",v,c)
c = c*10           ; call disp("4",v,c)
v = [2]            ; call disp("5",v,c)
end associate
contains
subroutine disp(label,v,c)
character (len=*), intent(in) :: label
integer, intent(in) :: v(:),c(:)
write (*,"(a,' v = ',*(1x,i0))",advance="no") label,v
write (*,"(3x,'c = ',*(1x,i0))") c
end subroutine disp
end program demonstrate_associate
c:\fortran\tweets\unposted>ifort associate_alloc.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

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

-out:associate_alloc.exe 
-subsystem:console 
associate_alloc.obj
c:\fortran\tweets\unposted>associate_alloc.exe
1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  30 40
4 v =  2 4 6    c =  300 400
5 v =  2    c =  300 400

It is not invalid to redefine the selector, but the bounds of the associating variable don’t change within the block. You can think of it as similar to a dummy argument associated with an actual argument.

Very odd - when I tried it earlier, with that same ifort version, I got the correct results. If I try it again, I don’t.

Edit: Oh, even more fun - I can get BOTH results if I run the same EXE multiple times!

D:\Projects>ifort /stand t.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

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

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

D:\Projects>t.exe
1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  2 4
4 v =  20 40 6    c =  20 40
5 v =  2    c =  20 40

D:\Projects>t.exe
1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  30 40
4 v =  2 4 6    c =  300 400
5 v =  2    c =  300 400

D:\Projects>t.exe
1 v =  3 4    c =  3 4
2 v =  30 40    c =  30 40
3 v =  2 4 6    c =  30 40
4 v =  2 4 6    c =  300 400
5 v =  2    c =  300 400

Methinks a bug report is in order.

I started to wonder what compilers would do when you refer to a pointer whose target has been deallocated, as in the code below. Only g95 gives a run-time error. Are there options with other compilers that catch this? At least on WSL2, gfortran gives different results on each run, which signals a problem.

program main
implicit none
integer, allocatable, target :: v(:)
integer, pointer :: p(:)
v = [4,7,9]
p => v
print*,p
deallocate(v)
print*,p ! invalid, I think, because target has been deallocated
end program main

c:\fortran\tweets\unposted>gfortran -fcheck=bounds pointer_alloc.f90

c:\fortran\tweets\unposted>a.exe
           4           7           9
           2           0           0
c:\fortran\tweets\unposted>ifort pointer_alloc.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

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

-out:pointer_alloc.exe 
-subsystem:console 
pointer_alloc.obj
c:\fortran\tweets\unposted>pointer_alloc.exe
           4           7           9
           4           7           9

c:\fortran\tweets\unposted>g95 pointer_alloc.f90

c:\fortran\tweets\unposted>a.exe
Exception: Access Violation
Traceback: not available, compile with -ftrace=frame or -ftrace=full

Now using WSL2:

(fpm) /mnt/c/fortran/tweets/unposted$ gfortran pointer_alloc.f90
(fpm) /mnt/c/fortran/tweets/unposted$ ./a.out
           4           7           9
           0           0 -1709281264
(fpm) /mnt/c/fortran/tweets/unposted$ ./a.out
           4           7           9
           0           0 -2032820208
(fpm) /mnt/c/fortran/tweets/unposted$ flang pointer_alloc.f90
(fpm) /mnt/c/fortran/tweets/unposted$ ./a.out
            4            7            9
            4            7            9

I’d say that g95 probably has a bug here, in that the associate variable is not a pointer, so really shouldn’t be able to tell that the selector has been deallocated and the associate variable is now pointing to old memory.

Good catch, @kargl !