Array section with vector subscript as procedure argument

Here is an example of my problem (in my real program, A would be much larger and random) :

    MODULE MOD_TST
        contains
        subroutine function_tst(A,B)
            real,intent(in) :: A(:)
            real,intent(out) :: B(:)
            integer :: i, n
            n = size(A)
            do i=1,n; B(i) = A(i); end do
        end subroutine function_tst
    end module MOD_TST
    
    PROGRAM PROG_TST
      USE MOD_TST

      IMPLICIT NONE
      integer,allocatable :: A(:),B1(:),B2(:),subA(:),subB(:)
      integer :: i, n = 10, p = 3
      integer,allocatable :: list(:)

      allocate(A(n),B1(n),B2(n))
      A = (/ 9, 5, 4, 7, 8, 1, 6, 0, 3, 2/)
    
      list = pack ( [( i, i=1,n )] , modulo(A,p) .eq. 0)
      allocate(subA(size(list)),subB(size(list)))
      subA=A(list); subB=B1(list);

      call function_tst(subA,subB)
      B1(list) = subB

      call function_tst(A(list),B2(list))

      write(*,*)'A ',A
      write(*,*)'B1',B1
      write(*,*)'B2',B2
    END PROGRAM PROG_TST

The output I get is :

A 9 5 4 7 8 1 6 0 3 2

B1 9 0 0 0 0 0 6 0 3 0

B2 0 0 0 0 0 0 0 0 0 0

Is there a way to make it work without having to create an intermediate variable for the procedure?


An array section with vector subscript is very heavily restricted in how it can be used. As a general (subjective) rule, it's fair to say they should be avoided if possible. Before coming on to the details, what is an array section with vector subscript?

A vector subscript is an integer array or rank 1, and an array section with such a subscript is one where the elements of the whole are selected by this subscript array:

integer :: i(5)=[1,2,3,4,5]
print *, i([1,2,5])

The array section has a vector subscript whenever this form is used, whether it has all of the elements of the whole array, is a contiguous sub-array, or selects an element more than once.

At the highest level, an array with vector subscript is particularly restricted when the vector array specifies the same element more than once: such an array section can never be subject to "definition":

integer i(5)
i([1,3,2]) = [1,2,3]  ! Allowed
i([1,3,1]) = [1,2,3]  ! Not allowed

So, in many cases assignment such as can be seen in the subroutine function_tst can be done directly to the array section.

However, in the case of a passing such an array section to a procedure, the dummy array is never1 definable, even if there is no repeat or if the array section is a contiguous part of the whole array. This means, in the case of the question

call function_tst(A(list),B2(list))

is never allowed.

Note also that an array section with vector subscript is subject to restrictions which avoid easy "hacking":

  • an array section with vector subscript cannot be a target of a pointer
  • an associate name associated with an array section with vector subscript is never definable

One way around this is to create a temporary copy and pass the changes back to the original. This is very general, even if painful to write. It isn't, though, guaranteed to be safe for all procedures:

Btemp = B(list) ! If the argument is for an intent(inout), skip if inient(out)
call other_subroutine(A(list), Btemp)
B(list) = BTemp  ! Can be dangerous

Specific to the type of action in the specific example is an elemental procedure. Just as we can write

B2(list) = A(list)  ! No repeats in list

we can

call function_tst(A(list),B(list)) 

if we make that subroutine elemental

elemental subroutine function_tst(A,B)
  integer, intent(in) :: A
  integer, intent(out) :: B
  B=A
end subroutine function_tst

If the subroutine is suitable to be elemental, then you also have the option of looping over the indexing array:

do i=1, size(list)
  call function_tst(A(list(i):list(i)), B(list(i):list(i)))
end do

These are suitable only when there is total independence between elements.

Intermediate between these extremes is rewriting as a function (as shown in veryreverie's answer. With a function you also may be able to consider masked assignment, such as with WHERE statements and constructs.

As with simple assignment activities, such an elemental or looped subroutine or function, or masked assignment will not be so general as to cover all desires. Each alternative has its own potential pitfalls or drawbacks. To repeat: vector subscripts are highly restricted. They can, however, frequently be avoided.


1 There is are two exceptions: continue reading for one; the second is the VALUE attribute (which doesn't help in this case).


If you're okay modifying function_tst, then you can change it from a subroutine to a function, e.g.

module mod_tst
  implicit none
contains
  function function_tst(A) result(B)
    real, intent(in) :: A(:)
    real, allocatable :: B(:)
    
    B = A
  end function
end module MOD_TST

And then the relevant part of your program is simply

B1(list) = function_tst(A(list))

This approach works well for replacimg most subroutines with exactly one intent(out) argument, but cannot trivially replace subroutines:

  • with intent(inout) arguments
  • which leave parts of the intent(out) argument undefined (hat tip @francescalus)
  • with multiple intent(out) arguments.