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

loop reported as vectorized and not vectorized

jespersen
Beginner
635 Views
What does it mean if the compiler tells you "LOOP WAS VECTORIZED" and, at the
same line, "loop was not vectorized; not inner loop"?
Here is a dumb little subroutine (extracted and shrunk from a larger code):

SUBROUTINE JUNK ( J,L,FSO,DELTA,Q,VGAMMA,IB2,IBMIX,JD,KD,LD,TERM )
C
IMPLICIT NONE
INTEGER, INTENT (IN) :: J,L,JD,KD,LD
REAL(8), INTENT (IN) :: FSO,DELTA
REAL(8), DIMENSION(JD,KD,LD,5), INTENT (IN) :: Q
REAL(8), DIMENSION(JD,KD,LD), INTENT (IN) :: VGAMMA
INTEGER, DIMENSION(KD), INTENT (IN) :: IB2,IBMIX
REAL(8), DIMENSION(KD,2), INTENT (INOUT) :: TERM
C
INTEGER :: K,N
REAL(8) :: EPS,FSOLIM,C2,DQF2,ANUMER,DENOM
REAL(8), DIMENSION(KD,2) :: QF,DQF
REAL(8), PARAMETER :: EPSREF=0.008, ONE=1., THREE=3.
C
EPS = DELTA*EPSREF
FSOLIM = MAX( MIN( FSO,THREE ), ONE )
C2 = 0.5*MIN(FSOLIM-1.,ONE)
C
DO K = 1,KD
QF(K,1) = Q(J,K,L,1)
QF(K,2) = Q(J,K,L,2)/Q(J,K,L,1)
ENDDO
C
DO K = 1,KD-1
DQF(K,1) = QF(K+1,1) - QF(K,1)
DQF(K,2) = QF(K+1,2) - QF(K,2)
ENDDO
C
IF (DELTA.GE.0.) THEN
DO N = 1,2
DO K = 2,KD-1
DQF2 = DQF(K-1,N)*DQF(K,N)
ANUMER = 3.*(DQF2 + EPS)
DENOM = 2.*(DQF(K,N) - DQF(K-1,N))**2 + ANUMER
IF (DENOM.NE.0.) ANUMER = ANUMER/DENOM
TERM(K,N) = ANUMER*IBMIX(K)
ENDDO
ENDDO
ENDIF
C
RETURN
END

"ifort -V" gives:
Intel Fortran Intel 64 Compiler XE for applications running on Intel 64, Version 12.1 Build 20111011
Copyright (C) 1985-2011 Intel Corporation. All rights reserved.

"ifort -c -O3 -vec-report3 junk.f" gives
junk.f(20): (col. 7) remark: FUSED LOOP WAS VECTORIZED.
junk.f(32): (col. 10) remark: LOOP WAS VECTORIZED.
junk.f(32): (col. 10) remark: loop was not vectorized: not inner loop.

What does it mean that the loop at line 32 is both vectorized and not vectorized?
0 Kudos
2 Replies
Anonymous66
Valued Contributor I
635 Views
This means that the code line 32 contains nested loops and inner loop at line 32 was vectorized, but the outer loop was not vectorized.
0 Kudos
jimdempseyatthecove
Honored Contributor III
635 Views
>>junk.f(20): (col. 7) remark: FUSED LOOP WAS VECTORIZED.

I would be concerned about fuzing the loops at 20+25 since 25 (as fuzed) depends on future value of QF.

Note, the compiler could fuze these loops if it is smart enough to skew the two loops. Cannot say if it is smart enough or not. Better verify.

The loop at 32 (K loop) may have problem vectorizing because you are referencing (product and difference of) adjacent entries. Further you have the IF test within the loop. These tend not to vectorize well.

Jim Dempsey
0 Kudos
Reply