Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Temporary array creation

Michael_C_5
Beginner
2,159 Views

I'm getting the famous warning of a temporary array created, forrtl: warning (406): fort: (1): In call to XXXX, an array temporary was created for argument #N. However, I create simple code to mimic the larger code, and I don't get the same warning. See code below. Essentially I'm passing in a subset array into subroutine XXXX, and indexing on the last index, which should give me a contiguous memory chunk. What else could cause this temporary array creation? ifort version 16.0.0

Code:

program testArrayPassSubroutine                                                 
        integer :: sze,i                                                        
        real, dimension(3,3,2) :: arr
        real, dimension(2,3,3) :: arr2

        !do k=1,2
        !       do j=1,3
        !               do i=1,3
        !                       arr(i,j,k) = (k-1)*9 + (j-1)*3 + i
        !               enddo
        !       enddo
        !enddo

        !do k=1,3
        !        do j=1,3
        !                do i=1,2
        !                        arr2(i,j,k) = (k-1)*9 + (j-1)*3 + i
        !                enddo
        !        enddo
        !enddo

        !This is like the original code, which throws the warning(406):...temporary array creation
        write(*,*) "Test1 start"
        call test(arr(:,:,1))
        write(*,*) "Test1 done"

        !This is where I would expect a warning(406), and indeed see it
        write(*,*) "Test2 start"
        call test(arr2(1,:,:))
        write(*,*) "Test2 done"

        contains
        subroutine test(a)
        integer :: i,j
        real, dimension(3,3) :: a

        do i=1,3
                do j=1,3
                        a(j,i) = j*i
                enddo
        enddo

        write(*,*) "Array",(a)
        write(*,*) ""
        end subroutine test
end program testArrayPassSubroutine

Output:

Test1 start

 Array   1.000000       2.000000       3.000000       2.000000
   4.000000       6.000000       3.000000       6.000000       9.000000

 Test1 done
 Test2 start
forrtl: warning (406): fort: (1): In call to TEST, an array temporary was created for argument #1

Image              PC                Routine            Line        Source
a.out              0000000000403876  Unknown               Unknown  Unknown
a.out              0000000000400689  MAIN__                     29  testArrayPassSubroutine.F90
a.out              00000000004004AE  Unknown               Unknown  Unknown
a.out              000000000048D9F1  Unknown               Unknown  Unknown
a.out              0000000000400389  Unknown               Unknown  Unknown
 Array   1.000000       2.000000       3.000000       2.000000
   4.000000       6.000000       3.000000       6.000000       9.000000

 Test2 done

0 Kudos
21 Replies
jimdempseyatthecove
Honored Contributor III
1,913 Views

Your output shows no array temporary in Test1 (expected result). Section arr(:,:,1) is contiguous

And shows array temporary in Test 2 (expected result). Section arr2(1,:,:) is not contiguous.

Jim Dempsey

0 Kudos
Michael_C_5
Beginner
1,913 Views

Yes, that's the point, perhaps my code comments weren't clear. This code is derived from a larger code. The larger code effectively does Test1, which as this smaller code shows should not create array temporarys. But for some reason in the larger code I am getting an array temporary. Is there another reason array temporary's would be created?

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

Generally, if the thing you're passing is not contiguous and the called routine expects contiguity, a copy will be made. My guess is that you are not correctly representing what the "larger code" does. I do know that there are some cases where the compiler doesn't even check and always makes a copy. The cases I have seen are where the index expressions include derived-type components, and should be improved in future versions.

Please show us the actual call line that makes the copy.

0 Kudos
Michael_C_5
Beginner
1,913 Views

OK, here is a snippet of the larger code, I've tried to reduce it to the call and variables being passed in, hopefully this is clear enough. The warning is on the call col_f_f_df in the main subroutine.

There is a derived-type object (ci) being passed in, and in the subroutine indexed and input into the array being complained about (fi_half, through delr). Could this be the reason?

 

subroutine main()
...
real (kind=8), dimension(col_f_nvr, col_f_nvz) :: dist_ni,dfi, dist_iteri   ! local
real (kind=8),dimension((col_f_nvr-1),(col_f_nvz-1),2) :: fi_half,dfidr,dfidz,fe_half,dfedr,dfedz
...
type(col_f_core_type) :: ci, ce

...
do iter_inter=1, vpic_inner_iter_max
	...
	call col_f_f_df(ci, 1, dist_iteri, fi_half(:,:,1), dfidr(:,:,1), dfidz(:,:,1))  !i-i
	...
enddo



subroutine col_f_f_df(cs, op_mode, f, f_half, dfdr, dfdz)
...

type(col_f_core_type), intent(in) :: cs
integer, intent(in) :: op_mode
real(kind=8) :: mesh_dr, mesh_dz
real(kind=8), dimension(col_f_nvr, col_f_nvz) :: f
real(kind=8), dimension(col_f_nvr-1, col_f_nvz-1) :: f_half, dfdr, dfdz
real(kind=8) :: tmpr1, tmpr2, tmpr3, tmpr4
integer :: index_I, index_J
real (kind=8) :: delr, cdelr, delz, cdelz

do index_I=1,col_f_nvz-1
       do index_J=1, col_f_nvr-1
       	   delr = cs%delta_r(index_J,op_mode)
           cdelr = 1D0-delr
           delz = cs%delta_z(index_I,op_mode)
           cdelz = 1D0-delz

           tmpr1 = f(index_J, index_I)
           tmpr2 = f(index_J+1, index_I)
           tmpr3 = f(index_J,index_I+1)
           tmpr4 = f(index_J+1,index_I+1)
       		f_half(index_J, index_I) = tmpr1 * delr*delz &
                                     + tmpr3 * delr*cdelz &
                                     + tmpr2 * cdelr*delz &
                                     + tmpr4 * cdelr*cdelz

			...
		enddo
enddo


 

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

What is the message that comes out - which argument does it complain about?  How you fill in the arrays is of no consequence.

0 Kudos
Michael_C_5
Beginner
1,913 Views

It's the fourth argument, fi_half:

forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #4

0 Kudos
Michael_C_5
Beginner
1,913 Views

Sorry, its the fourth, fifth, and sixth (I'm using MPI, so several warning show up, esp. since this is in a loop):

forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #4
forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #5
forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #6

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

How and where are col_f_nvr and col_f_nvz declared? I haven't been able yet to construct a test case that reproduces the problem.

0 Kudos
FortranFan
Honored Contributor II
1,913 Views

Michael C. wrote:

Sorry, its the fourth, fifth, and sixth (I'm using MPI, so several warning show up, esp. since this is in a loop):

forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #4
forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #5
forrtl: warning (406): fort: (1): In call to COL_F_F_DF, an array temporary was created for argument #6

Looking at your code snippet in Message #5, it seems as though you might be doing something along the lines in the code shown below.  In such cases, as explained by Jim and Steve, the compiler might suspect the array section is not contiguous and add code to create an array temporary.  As Steve indicated, you need to supply a proper reproducer or share actual code with Intel to get good advice.

program p

   implicit none

   integer, parameter :: M = 3
   integer :: N

   real :: r(M,M,2)

   N = M-1

   call foo( r(1:N,1:N,:) )

   print *, " r = ", r

   stop

contains

   subroutine foo( r )

      real, intent(inout) :: r(N,N,2)  !.. N is some host-associated variable

      integer :: i

      do i = 1, size(r, dim=3)
         call bar( r(:,:,i) )
      end do

      return

   end subroutine foo

   subroutine bar( s )

      real, intent(inout) :: s(N,N)   !.. N is some host-associated variable

      s = 0.0

      return

   end subroutine bar

end program

Upon execution on Windows,

forrtl: warning (406): fort: (1): In call to FOO, an array temporary was created
 for argument #1

Image              PC                Routine            Line        Source

p64.exe            000000013FE152DE  Unknown               Unknown  Unknown
p64.exe            000000013FE11197  MAIN__                     12  p.f90
p64.exe            000000013FEAD77E  Unknown               Unknown  Unknown
p64.exe            000000013FEAE0AC  Unknown               Unknown  Unknown
p64.exe            000000013FEAE1EE  Unknown               Unknown  Unknown
kernel32.dll       0000000076F859DD  Unknown               Unknown  Unknown
ntdll.dll          00000000771BA631  Unknown               Unknown  Unknown
  r =  0.000000 0.000000 0.000000 0.000000
 0.000000 0.000000 0.000000 0.000000 0.000000
 0.000000 0.000000 0.000000 0.000000 0.000000
 0.000000 0.000000 0.000000 0.000000
Press any key to continue . . .

 

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

The problem is that a subscript of (:,:,1) is always contiguous for an array that started out as contiguous, which, if the declaration shown is representative, is the case. I would very much like to see an actual test case, as I suspect there is something important that hasn't been shown.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,913 Views

In your #10 example, N is not the full size of the first two dimensions of r.

You requested to transmit r(1:M-1,1:M-1,i)  i=1,2

Where M is the size of the first two dimensions of r. This section is not contiguous because

sections r(M,1:M,i) and r(1:M,M,i) (last row and last column) are not passed (thus must be effectively compressed out via temporary).

If you want to avoid the array temporary, pass the entire array section (1:M,1:M,i) to foo. Perform similar fix to bar.

Jim Dempsey

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

#10 is FortranFan's. He's trying to help, but his example isn't representative of Michael C's code as shown in this thread.

0 Kudos
FortranFan
Honored Contributor II
1,913 Views

jimdempseyatthecove wrote:

In your #10 example, N is not the full size of the first two dimensions of r. ..

Steve Lionel (Intel) wrote:

#10 is FortranFan's. He's trying to help, but his example isn't representative of Michael C's code as shown in this thread.

Yes, as mentioned by Steve, I was simply trying to suggest to OP that information on array dimensions (col_f_nvr, col_f_nvz) and how they are defined need to be provided as they do play a role, as shown by the simple code in Message #10.

0 Kudos
Michael_C_5
Beginner
1,913 Views

Steve Lionel (Intel) wrote:

How and where are col_f_nvr and col_f_nvz declared? I haven't been able yet to construct a test case that reproduces the problem.

There is a module read in at the beginning of the subroutine I called "main":

subroutine main()
use col_f_module

In col_f_module are defined col_f_nvr and col_f_nvz:

integer :: col_f_nvr, col_f_nvz

And they are instantiated in a setup routine called prior to this "main" subroutine (sorry, shouldn't have used "main" for the subroutine name). Values are derived from an input file; for the simulation I'm running they are:

col_f_nvr = 32
col_f_nvz = 31

After the initial setup, these never change, so I don't think it should be an issue pointed out in #10.

0 Kudos
FortranFan
Honored Contributor II
1,913 Views

Michael C. wrote:

.. In col_f_module are defined col_f_nvr and col_f_nvz: .. After the initial setup, these never change, so I don't think it should be an issue pointed out in #10.

I think your situation is akin to:

program p

   implicit none

   integer :: N

   N = 3

   call foo()

   stop

contains

   subroutine foo( )

      real :: r((N-1),(N-1),2)

      call bar( r(:,:,1) )

      return

   end subroutine foo

   subroutine bar( s )

      real, intent(inout) :: s(N-1,N-1)

      s = 0.0

      return

   end subroutine bar

end program

Upon execution on Windows,

forrtl: warning (406): fort: (1): In call to BAR, an array temporary was created
 for argument #1

Image              PC                Routine            Line        Source

p64.exe            000000013FAF827E  Unknown               Unknown  Unknown
p64.exe            000000013FAF128C  P_ip_FOO                   19  p.f90
p64.exe            000000013FAF1040  MAIN__                      9  p.f90
p64.exe            000000013FB84C7E  Unknown               Unknown  Unknown
p64.exe            000000013FB855AC  Unknown               Unknown  Unknown
p64.exe            000000013FB856EE  Unknown               Unknown  Unknown
kernel32.dll       0000000076F859DD  Unknown               Unknown  Unknown
ntdll.dll          00000000771BA631  Unknown               Unknown  Unknown
Press any key to continue . . .

Note if one makes a small change to code as shown below, no run-time warning about array temporary is issued:

program p

   implicit none

   integer :: N
   integer :: M

   N = 3
   M = N-1

   call foo()

   stop

contains

   subroutine foo( )

      real :: r(M,M,2)

      call bar( r(:,:,1) )

      return

   end subroutine foo

   subroutine bar( s )

      real, intent(inout) :: s(M,M)

      s = 0.0

      return

   end subroutine bar

end program

I think I have noticed this before.  I'll leave it up to you and Intel to follow-up.

0 Kudos
FortranFan
Honored Contributor II
1,913 Views

Or you can consider the following:

module m

   implicit none

   integer :: N

end module m

subroutine foo( )

   use m, only : N

   real :: r((N-1),(N-1),2)

   call bar( r(:,:,1) )

   return

end subroutine foo

subroutine bar( s )

   use m, only : N

   real, intent(inout) :: s(N-1,N-1)

   s = 0.0

   return

end subroutine bar
program p

   use m, only : N

   implicit none

   N = 3

   call foo()

   stop

end program

Upon execution,

forrtl: warning (406): fort: (1): In call to BAR, an array temporary was created
 for argument #1

Image              PC                Routine            Line        Source

p64.exe            000000013F78427E  Unknown               Unknown  Unknown
p64.exe            000000013F781325  FOO                        15  m.f90
p64.exe            000000013F78198C  MAIN__                      9  p.f90
p64.exe            000000013F814C3E  Unknown               Unknown  Unknown
p64.exe            000000013F81556C  Unknown               Unknown  Unknown
p64.exe            000000013F8156AE  Unknown               Unknown  Unknown
kernel32.dll       0000000076F859DD  Unknown               Unknown  Unknown
ntdll.dll          00000000771BA631  Unknown               Unknown  Unknown
Press any key to continue . . .

 

0 Kudos
FortranFan
Honored Contributor II
1,913 Views

Michael C. wrote:

..

subroutine main()
...
real (kind=8), dimension(col_f_nvr, col_f_nvz) :: dist_ni,dfi, dist_iteri   ! local
real (kind=8),dimension((col_f_nvr-1),(col_f_nvz-1),2) :: fi_half,dfidr,dfidz,fe_half,dfedr,dfedz
...
..

 

Try removing the parenthesis around col_f_nvr-1 and col_f_nvz-1 in your actual code!

0 Kudos
Steven_L_Intel1
Employee
1,913 Views

Thanks to FortranFan for coming up with a complete reproducer. I have escalated this as issue DPD200380709. Indeed, the parentheses in the declaration trigger the problem - apparently the compiler decides that the declaration is "too complex" to do the run-time test, even though the subscript syntax in the call should indicate that the argument will always be contiguous.

0 Kudos
Michael_C_5
Beginner
1,913 Views

Yes, thanks FortranFan, removing the parenthesis removed the array temporary warning. Thanks to all for looking into this.

Just to be sure, this was just a bug in the warning system from the compiler right? There weren't actually array temporarys being created, correct?

0 Kudos
Steven_L_Intel1
Employee
1,730 Views

No, there were copies being made.The compiler thought it was too complex to generate the checking code, so it made the copy unconditionally, when without the parentheses it realized it didn't need to check as a copy would never be needed.

0 Kudos
Reply