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

Warning 406: In call to FUNCTION, an array temporary was created for argument #n

tidges
Beginner
1,148 Views

I'm getting this warning from my code, and I think I understand generally what it means (a temporary array is created because the one provided is not contiguous in memory), but I'm confused because I thought all of my array slices were already contiguous, as they're of the form (n:m,j).

 

The function is (approximately) as follows:

    function schrodStep(EJ0, EJ1, EJ2, psi, B)
    !Calculate the 9-level Schrodinger eqn
        real(RK), intent(in) :: EJ0, EJ1, EJ2
        real(RK), dimension(nPhis_overall, 3), intent(in) :: B
		real(RK), dimension(nPhis_overall) :: Bx, By, Bz
        complex(RK), dimension(nPhis_overall, nStates), intent(in) :: psi
        complex(RK), dimension(nPhis_overall, nStates) :: schrodStep
        complex(RK), dimension(nPhis_overall) :: psiJ0m0, psiJ1mn1, psiJ1m0, psiJ1m1, psiJ2mn2, psiJ2mn1, psiJ2m0, psiJ2m1, psiJ2m2

		Bx = B(1:nPhis_overall, 1)
		By = B(1:nPhis_overall, 2)
		Bz = B(1:nPhis_overall, 3)

		psiJ0m0 = psi(1:nPhis_overall, 1)
                !and so on, until
		psiJ2m2 = psi(1:nPhis_overall, 9)

        schrodStep(1:nPhis_overall, 1) = (xi*psiJ1mn1*(Bx-ci*By)/SQRT(3.0_RK) - xi*psiJ1m1*(Bx+ci*By)/SQRT(3.0_RK) &
        + SQRT(2.0_RK/3.0_RK)*xi*psiJ1m0*Bz + psiJ0m0*EJ0)*-ci/hbar
        !And similar lines for the other 8 levels
end function

 I get the warning for both array arguments (psi and B). This is the core function of a numerical integration, so if it's causing any inefficiency it would be a big deal.

 

Thanks

Labels (3)
0 Kudos
1 Solution
Steve_Lionel
Honored Contributor III
1,091 Views

Thanks - I can reproduce this and it's a bug. The compiler is improperly calculating the shape for expressions such as B+B_Background for the purpose of the contiguity check. A workaround is to declare an additional allocatable array, I called it BX and then do something like this:

 

 

BX = B+B_background; k1 = schrodStep(EJ0, EJ1, EJ2, psi, BX)

 

 

You don't have to explicitly allocate BX. 

Let me see if I can come up with a minimal test case.

View solution in original post

0 Kudos
7 Replies
IanH
Honored Contributor II
1,133 Views

Which line (or lines) is the warning specifically reported for? 

From what I can tell, there are no non-intrinsic function references within the code that you show.... is the warning being reported against references to schrodStep?  If so, please show the declarations for the actual arguments in the function reference and the source of the reference itself.

 

 

0 Kudos
tidges
Beginner
1,062 Views

I attached the full code in my reply to Steve, but I've tried to keep only the relevant lines here to make it easier to parse (though obviously it's not longer working code):

 

 

program hello
    use iso_fortran_env, only: int16, int32, real64
    use ifport
    implicit none

    integer, parameter :: RK=real64, Ishort=int16, Ilong=int32

    integer(Ilong) :: nFreqs, nPhis, nPhis_overall, expNum, parLoopInd, folStat
    integer(Ishort) :: init_i, nStates=9
    real(RK), dimension(:), allocatable :: phis, phis_loop, phis_overall, freqs_loop, loopArr, chirpScales
    real(RK) :: t_max, h, t, tT, tD
    complex(RK), parameter :: ci=(0.0_RK,1.0_RK), c0=(0.0_RK,0.0_RK), c1=(1.0_RK,0.0_RK)
    complex(RK), dimension(:,:), allocatable :: psi, psi_new, k, k1, k2, k3, k4
    real(RK), dimension(:,:), allocatable :: B, B_Step, B_halfStep, B_background
    complex(RK), dimension(:), allocatable :: psi_vec

    allocate(psi_vec(nStates))
    psi_vec = SQRT([c0, c0, c1, c0, c0, c0, c0, c0, c0])
    allocate(B_background(nPhis_overall,3))
    B_background(1:nPhis_overall, 1) = 0.0_RK !Residual background B field (x,y,z)
    B_background(1:nPhis_overall, 2) = 0.0_RK
    B_background(1:nPhis_overall, 3) = 0.0_RK

	do parLoopInd=1,SIZE(loopArr) !Whole run loop for changing parameters
		allocate(psi_new(nPhis_overall,nStates), psi(nPhis_overall,nStates))
		allocate(B(nPhis_overall,3), B_Step(nPhis_overall,3), B_halfStep(nPhis_overall,3))
		do expNum=1,size(expTypes) !A/B experiment loop
			do j=1,nPhis !Phis pulse loop
				do i=1,nFreqs !Freqs loop
					!Runge-Kutta initialising
					t = 0.0_RK
					do init_i=1,nPhis_overall
						psi_new(init_i, 1:nStates) = psi_vec
					end do
                    B_step(1:nPhis_overall, 1) = 0.0_RK
                    B_step(1:nPhis_overall, 2) = 0.0_RK
                    B_step(1:nPhis_overall, 3) = Bz0
					do while (t.LT.t_max) !Runge-Kutta loop
						!z-polarised microwaves with some y component, and z-aligned DC B field. Use previous stepped value to save on calculations
						psi = psi_new
						B = B_step
						B_halfStep(1:nPhis_overall, 1) = 0.0_RK
						B_halfStep(1:nPhis_overall, 2) = getB_mw(t+h/2.0_RK)*SIND(theta_MW)
						B_halfStep(1:nPhis_overall, 3) = Bz0 + getB_mw(t+h/2.0_RK)*COSD(theta_MW)
						B_step(1:nPhis_overall, 1) = 0.0_RK
						B_step(1:nPhis_overall, 2) = getB_mw(t+h)*SIND(theta_MW)
						B_step(1:nPhis_overall, 3) = Bz0 + getB_mw(t+h)*COSD(theta_MW)

						k1 = schrodStep(EJ0, EJ1, EJ2, psi, B+B_background)
						k2 = schrodStep(EJ0, EJ1, EJ2, psi+h*k1/2.0_RK, B_halfStep+B_background)
						k3 = schrodStep(EJ0, EJ1, EJ2, psi+h*k2/2.0_RK, B_halfStep+B_background)
						k4 = schrodStep(EJ0, EJ1, EJ2, psi+h*k3, B_step+B_background)
						k = (k1 + 2.0_RK*k2 + 2.0_RK*k3 + k4)/6.0_RK

						psi_new = psi + h*k
						t = t+h
					end do !Runge-Kutta time loop
				end do !Freqs loop
			end do !Phis pulse loop
			deallocate(phis)
		end do !A/B experiment loop
		deallocate(B, B_halfStep, B_Step, psi, psi_new)
	end do !Whole run loop for changing parameters
end program

 

 and getB_mw() looks like this (nothing interesting, just returns a vector of dimension nPhis_overall because that's the dimension of the 'phis' variable in the argument of the sine at the end)

 

    function getB_mw(t)
    !Gives two-pulse profile, scaled
        real(RK), intent(in) :: t
        real(RK), dimension(nPhis_overall) :: getB_mw

        if (expType .EQ. 'A') then
            amp = (TANH(t-10.0_RK)-TANH(t-tD-10.0_RK)+TANH(t-tT-10.0_RK)-TANH(t-tT-tD-10.0_RK))/2 + &
                   0.008_RK*powerLvl*(EXP(-(t-9.0_RK)**2.0_RK/2.0_RK))!+EXP(-(t-309.0_RK)**2.0_RK/2.0_RK))
        else if (expType .EQ. 'B') then
            amp = (TANH(t-10.0_RK)-TANH(t-tD-10.0_RK)+TANH(t-tT-10.0_RK)-TANH(t-tT-tD-10.0_RK))/2 + &
                   0.008_RK*powerLvl*EXP(-(t-309.0_RK)**2.0_RK/2.0_RK)
        end if
        getB_mw = amp*SIN(2*pi*freqRF*t+phis)
    end function

 

The warning points to the Runge-Kutta lines, 49-52 in the first excerpt here.

0 Kudos
Steve_Lionel
Honored Contributor III
1,108 Views

The excerpt you provided is not compilable. If you can provide (ideally as an attachment rather than inline) a source that compiles on its own, we can check to see where this warning may be coming from.

0 Kudos
tidges
Beginner
1,101 Views

Sure, there's a "resultsStem" parameter which will need to be changed to a writeable directory in order to run but I think that's the only change needed. The calls to my function are lines 192-195, and that is where the warning points to.

0 Kudos
Steve_Lionel
Honored Contributor III
1,092 Views

Thanks - I can reproduce this and it's a bug. The compiler is improperly calculating the shape for expressions such as B+B_Background for the purpose of the contiguity check. A workaround is to declare an additional allocatable array, I called it BX and then do something like this:

 

 

BX = B+B_background; k1 = schrodStep(EJ0, EJ1, EJ2, psi, BX)

 

 

You don't have to explicitly allocate BX. 

Let me see if I can come up with a minimal test case.

0 Kudos
tidges
Beginner
1,087 Views

Ah I see, I made that change for both psi and B and it did indeed get rid of the warning. Thanks

0 Kudos
Steve_Lionel
Honored Contributor III
1,082 Views

I have a small reproducer, but I'm uncertain that it's a bug. In reality, the compiler IS creating an array temporary to hold the expression B+B_background, and is not incorrectly calculating the shape. I might argue that this warning ought not to be issued for expressions, but maybe the programmer would like to know if any temporary copy is made. I know there are cases in I/O statements where this warning can inexplicably be generated.

Of course, this warning is only generated if you explicitly ask for /check:arg_temp_created, as that's not the default. Maybe you could just turn this off.

 

0 Kudos
Reply