Creating temporary array when declared in a module

This is my first post here, I am still learning the etiquette here. Therefore, please, apologise me if I do not fully conform the style of posts here.

I decided to register here after my post at Stackoverflow received only little attention. I copy it here almost verbatim.

I do not understand why gfortran creates a temporary array only in one case. Consider the following program

program temporary_arrays
  use Mvars, only       : am
  use Mtemporaries, only: create_matrix
  implicit none
  integer, parameter    :: dp = kind(1.d0), n = 3
  real(dp), allocatable :: bm(:, :)
  
  allocate(am(n, n), bm(n, n))

  ! -- temporary array is created --
  am = create_matrix(n)

  ! -- no temporary array --
  bm = create_matrix(n)
  
end program temporary_arrays

!------------------------
module Mtemporaries

contains
  function create_matrix(n) result(A)
    implicit none
    integer, parameter :: dp = kind(1.d0)
    integer  :: n
    real(dp) :: a(n, n)
    A = 0.d0
  end function create_matrix

end module Mtemporaries  

!------------------------
module Mvars
  implicit none
  integer, parameter       :: dp = kind(1.d0)
  real(dp), allocatable    :: am(:, :)
  
end module Mvars

When compiled with gfortran (GNU Fortran (Homebrew GCC 13.2.0) 13.2.0 Copyright (C) 2023 Free Software Foundation, Inc.) with the -Warray-temporaries option, I get that temporary array is created only in one case, namely when the array is declared in a different module. No such warning when the array is declared in the main program.

I would like to know the logic behind and how to deal with this problem, i.e., avoid creation of temporary arrays.

I don’t see any temporary at runtime. I’m using gcc version 13.2.0 (Homebrew GCC 13.2.0).

$ gfortran -O2 -fcheck=array-temps temporary_arrays.f90 
$ ./a.out
$ gfortran -O1 -fcheck=array-temps temporary_arrays.f90 
$ ./a.out
$ gfortran -fcheck=array-temps temporary_arrays.f90 
$ ./a.out
$

I have the main program and modules in all different files, maybe that is the reason?

Also, I noticed that changing optimisation level to O1 or O2 does not change anything. However, replacing -Warray-temporaries with -fcheck=array-temps does make a difference, which is not surprising because fcheck is the run-time check.

The difference might be that the program unit can not be accessed from elsewhere, so the compiler can be 100% sure, that bm is unallocated, when you call bm = create_matrix(n). In the case of am, that’s not the warranted (e.g. the routine create_matrix() could in theory (as a nasty side effect) import the module MVars and allocate am).

But apparently, the warning does not necessary mean, that an actual temporary copy is made at run-time…

I think you are right, giving the dummy argument n attribute intent(in) makes the function effectively pure and the warning goes away.

But what is the most strange, the following does not generate any warnings

  function create_matrix(n) result(A)
    use Mvars, only: am
    implicit none
    integer, parameter :: dp = kind(1.d0)
    integer, intent(in):: n
    real(dp) :: a(n, n)
    A = 0.0D0
  end function create_matrix

I think it is just a bug in gfortran.

Which kind of warning would you expect here? intent(in) has been added to the declaration of n, which effectively suppresses the array temporary warning. Why the use of Mvars should change that ?

This was in response to @aradi comment, that create_matrix might import variables from Mvars and that it necessitates the creation of the temporary copy.

I think that I learned two things from this thread:

  1. -Warray-temporaries warnings should be verified with -fcheck=array-temps. Once I know that, I can live with it
  2. intent(in) is more important than I thought.

Still, there’s a problem with gfortran I think. Once the routine is declared as pure, gfortran does no longer create a temporary array… but it should. Here is a simplified version of your code:

module Mvars
  implicit none
  integer, allocatable    :: am(:, :)
contains
  pure function create_matrix(n) result(a)
    integer, intent(in) :: n
    integer :: a(n, n)
    a = transpose(am)
  end function create_matrix
end module Mvars

program temporary_arrays
  use Mvars
  implicit none
  integer :: i, n=3

  allocate(am(n,n))
  am(1,:) = [11,12,13]
  am(2,:) = [21,22,23]
  am(3,:) = [31,32,33]

  am = create_matrix(n)

  do i = 1, n
    print*, am(i,:)
  end do

end program temporary_arrays

It’s a poor design, but valid (standard conforming) I think.

gfortran gets it wrong, because it doesn’t see this is actually an in-place transpose:

Program returned: 0
Program stdout

          11          12          13
          12          22          23
          13          23          33
1 Like

Good catch! My test shows the same behaviour without the pure attribute. Do you know if ifort also does not issue any warnings?

By the way, your code can be rectified by removing the intent(in) attribute of n. gfortran issues a warning, returns the correct result, however, does not issue a run-time error according to -fcheck=array-temps.

However, despite this all, this still is a standard conforming code, and this is still not a bug but a usability issue. :slightly_smiling_face:

It’s very likely a bug. The standard requires the RHS (here create_matrix(n)) to be fully evaluated before being assigned to the LHS (am). So the end result should definitly be the transpose of the initial am. gfortran here has wrongly optimized out the temporary array that is normally required for the full evaluation before assignment. This illustrates how difficult can be the optimization for compilers.

I do not know, at least in the “Modern Fortran explained” book I read

the expression is interpreted as being fully evaluated before the assignment commences

and not

the expression must be fully evaluated before the assignment commences

Either way, it would be very good if the issue can be corrected in future releases.

Yes, the standard expresses this as an “as if”. Compilers are free to do whatever they want, as long as it doesn’t change the results.

1 Like