Software Archive
Read-only legacy content
17061 Discussions

help understanding alignment report

conor_p_
Beginner
658 Views

Hello, I am having some issues trying to understand why I am not using aligned arrays in one of my subroutines. The code is shown below. I checked the alignment using

ifort -align array64byte -vec-report6 global.f90 mod_force.f90

module mod_force
use global
contains


  subroutine force_vlist_MIC(step)
    implicit none
    double precision :: force,forcelj
    double precision :: x1,y1,z1,x2,y2,z2
    double precision :: dx,dy,dz,dr,dr2,dr2i,dr6i,dr12i
    double precision :: filter
    double precision :: fxl,fyl,fzl
    integer :: i,j,step
    integer :: itype,jtype,neigh
    integer :: tid,num
    integer :: offset
    integer :: T1,T2,clock_rate,clock_max,rep
    integer :: h

   
    
    potential = 0.0d0
    ff(:) = 0.0d0


    !dir$ offload begin target(mic:0) in(r,numneigh,vlist) inout(ff,potential)
    !$omp parallel do reduction(+: fxl,fyl,fzl,potential) schedule(dynamic),&
    !$omp& default(private) shared(r,numneigh,neigh_alloc,vlist,rcut2,box,np)
    
    
    do i = 1 ,np
       
       x1  = r(3*i-2); y1 = r(3*i-1); z1 = r(3*i);
       fxl = 0.0d0; fyl = 0.0d0; fzl = 0.0d0
       
       
       !dir$ simd
       !dir$ vector aligned
       do j=1,numneigh(i)
          
          
          !---look up neighboring particle
          neigh = vlist(j+neigh_alloc*(i-1)) 

          !---load particle data
          x2 = r(3*neigh-2); y2 = r(3*neigh-1); z2 = r(3*neigh);

          dx = x1-x2; dy = y1-y2; dz = z1-z2
          dx = dx-box*nint(dx/box)
          dy = dy-box*nint(dy/box)
          dz = dz-box*nint(dz/box)
          
          dr2 = dx*dx + dy*dy + dz*dz
          
          filter = 0.0d0
          if(dr2.lt.rcut2)filter = 1.0d0
          
          dr2i = 1.0d0/dr2
          dr6i = dr2i*dr2i*dr2i
          
    
          force    = 48.0d0*dr6i*(dr6i-0.50d0)
          force   = forcelj*dr2i
          
          fxl = fxl + dx*force
          fyl = fyl + dy*force
          fzl = fzl + dz*force
          
            
          potential = potential + dr6i*(dr6i-1.0d0)*filter
       enddo
       ff(3*i-2) = fxl; ff(3*i-1) = fyl; ff(3*i) = fzl
       
    enddo
    !$omp end parallel do
    !dir$ end offload
    
    call system_clock(T2,clock_rate,clock_max)
    potential = 4.0d0 *potential
       
    print*,'mic TIME',rep,real(T2-T1)/real(clock_rate),potential 
   
  end subroutine force_vlist_MIC


  

end module mod_force
  implicit none

!---------------------------------------------------------------------
!*** simulation parameters
!*** read at run time

  !dir$ attributes offload:mic::r
  double precision, allocatable :: r(:)
  double precision, allocatable :: rs(:)
  !dir$ attributes offload:mic::ff
  double precision, allocatable :: ff(:)
  double precision, allocatable :: ffs(:)
  double precision, allocatable :: drx(:),dry(:),drz(:)
  !dir$ attributes offload:mic::potential
  double precision :: potential
  double precision :: rcut
  !dir$ attributes offload:mic::rcut2
  double precision :: rcut2
  !dir$ attributes offload:mic::box
  double precision :: vol,box,hbox,ibox
  !dir$ attributes offload:mic::np
  integer :: np  
 
  
   
  !-----------------------------------------------------------------------
  !*** LL and Vlist 
  !*** 
 
  !dir$ attributes offload:mic::vlist
  integer,allocatable :: vlist(:)
  !dir$ attributes offload:mic::numneigh
  integer,allocatable :: numneigh(:)
  
  !dir$ attributes offload:mic::neigh_alloc
  integer :: neigh_alloc
 
end module global

the compiler output is

ogin1.stampede(152)$ ifort -align array64byte -vec-report6 global.f90 mod_force.f90
mod_force.f90(23): (col. 5) remark: vectorization support: unroll factor set to 2.
mod_force.f90(23): (col. 5) remark: LOOP WAS VECTORIZED.
mod_force.f90(23): (col. 5) remark: loop was not vectorized: not inner loop.
mod_force.f90(39): (col. 8) remark: SIMD LOOP WAS VECTORIZED.
mod_force.f90(63): (col. 11) remark: loop was not vectorized: not inner loop.
mod_force.f90(46): (col. 11) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(46): (col. 30) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(46): (col. 49) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(43): (col. 11) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  unit-strided, element aligned.
mod_force.f90(46): (col. 11) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(46): (col. 30) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(46): (col. 49) remark: *MIC* vectorization support: gather was generated for the variable global_mp_r_:  indirect access .
mod_force.f90(43): (col. 11) remark: *MIC* vectorization support: reference global_mp_vlist_ has unaligned access.
mod_force.f90(43): (col. 11) remark: *MIC* vectorization support: unaligned access used inside loop body.
mod_force.f90(39): (col. 8) remark: *MIC* SIMD LOOP WAS VECTORIZED.
mod_force.f90(43): (col. 11) remark: *MIC* vectorization support: reference global_mp_vlist_ has unaligned access.
mod_force.f90(43): (col. 11) remark: *MIC* vectorization support: unaligned access used inside loop body.
mod_force.f90(39): (col. 8) remark: *MIC* REMAINDER LOOP WAS VECTORIZED.
mod_force.f90(31): (col. 5) remark: *MIC* loop was not vectorized: not inner loop.

I am having a hard time understanding what this is telling me. My first place of confusion is why line 43, which is using vlist, has unaligned access. Does the -align array64byte not work for global dynamic arrays? I couldn't quite figure out what the consensus was for aligning global dynamic arrays from the data alignment to assist vectorization article intel has available. Also, why is the !dir$ vector aligned not telling the compiler vlist is aligned? When it is telling me indirect access for global_mp_r, does that mean that the data is not aligned, or is that only in reference to non sequential array access being performed? The compiler then tells me that line 43 is unit stride and element aligned. Does that mean r is indeed aligned? Finally I noticed that if instead of using the !dir$ vector aligned, I switched to !dir$ assume_aligned r: 64 that I would get an error saying I could not do this for an array in a common block. However, I do not get such an error with the !dir$ vector aligned. Could someone explain this to me?

0 Kudos
4 Replies
TimP
Honored Contributor III
658 Views

In case you are serious about asserting that the values of neigh_alloc() are such that you never pick up an unaligned array section of vlist(), the compiler still has no way to take advantage of that.  Your stride 3 access to r() still implies use of gather instructions, which don't care about alignment. The assertion refers to the access pattern within the loop, not to the possibility that vlist itself may be aligned.  The milder directive of vector always is already implicit in the simd directive.

If you want to assure that the compiler knows you had align array64byte in effect in declaration of vlist, you could use the assume_aligned assertion.  It doesn't appear likely to make a difference in your context (no difference is better than taking chances).

Use of simd directive without specifying the reductions is unsafe.  If you think you have a reason for taking this risk, you should test carefully simd vs. vector always without simd and with the full simd specification.

!dir$ simd reduction(+: potential) reduction(+: fx1),....

With 4 reductions in the inner loop, there may be no advantage in pushing the compiler to use special code for reduction (e.g. with riffling).

These aggressive directives are rather flaky when misused.

Do you have a reason for using nint() rather than anint() or ieee_rint()?   Perhaps it could vectorize without taking chances on directives. 

I mention ieee_rint() only because in principle it would be a very simple translation to ieee compatible instructions.  If it doesn't work efficiently, that might be a case for submission of a compiler feature request, if the IPS web site has been re-activated.

0 Kudos
conor_p_
Beginner
658 Views

Thank you for your detailed response. I appreciate it. The issue with the !dir$ assume_aligned directive is that the compiler doesn't like it when the variable is a global variable. Thats why I used the !dir$ vector aligned. For some reason, it didn't complain about the global variables then. So let me reiterate what you said to see if I understand. Due to the gather operation, the alignment is no longer an issue. When I do the !dir$ simd reduction(+:potential,fxl,fyl,fzl), do I also put the reduction(+:potential,fxl,fyl,fzl) in the !$omp directive? If I do not, the results are not correct. I was using the nint function, because it was the only one I knew. Do you think the ones you suggested have better vectorizing capability? I am starting to become suspicious of whether the nint is actually getting vectorized.

0 Kudos
TimP
Honored Contributor III
658 Views

If the array is defined as module data, I guess you shouldn't need any alignment assertion.  The align array64byte should take care of it, but you would have other changes to make to get any advantage from it.

Omitting the reduction clause in a simd directive doesn't always give wrong answers, but it's risky.

anint is much the same as nint except that it doesn't involve intermediate integer representation (it uses integral floating point values).  ieee-rint (requiring USE ieee_arithmetic) is different from anint only in applying the IEEE round-to-nearest-even rule.

I was guessing you might have been applying directives to get vectorization which the compiler considers inefficient on account of nint, when it might prefer one of those alternatives.

0 Kudos
conor_p_
Beginner
658 Views

Unfortunately, it doesn't look like anint() can be vectorized either. I just checked using -vec-report6 and the result I got was

"call to function f_ldnint cannot be vectorized"

When I use the !dir$ simd directive, does this remain the case regarding these nearest integer routines? With the inclusion of the simd directive, the compiler says the loop is vectorized and doesn't mention anything regarding the anint(). I am not quite sure if it was then actually vectorized.

0 Kudos
Reply