This is the mail archive of the gcc@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: How to generate AVX512 instructions now (just to look at them).


On 01/03/2014 07:04 PM, Jakub Jelinek wrote:

On Fri, Jan 03, 2014 at 05:04:55PM +0100, Toon Moene wrote:

I am trying to figure out how the top-consuming routines in our
weather models will be compiled when using AVX512 instructions (and
their 32 512 bit registers).

I thought an up-to-date trunk version of gcc, using the command line:

<...>/gfortran -Ofast -S -mavx2 -mavx512f <source code>

would do that.

Unfortunately, I do not see any use of the new zmm.. registers,
which might mean that AVX512 isn't used yet.

This is how the nightly build job builds the trunk gfortran compiler:

configure --prefix=/home/toon/compilers/install --with-gnu-as
--with-gnu-ld --enable-languages=fortran<,other-language>
--disable-multilib --disable-nls --with-arch=core-avx2
--with-tune=core-avx2

Is it the --with-arch=core-avx2 ? Or perhaps the --with-gnu-as
--with-gnu-ld (because the installed ones do not support AVX512 yet
?).

You shouldn't need assembler with AVX512 support just for -S,
if I try say simple:
void f1 (int *__restrict e, int *__restrict f) { int i; for (i = 0; i < 1024; i++) e[i] = f[i] * 7; }

I don't doubt that would work, what I'm interested in, is (cat verintlin.f):

      SUBROUTINE VERINT (
     I   KLON   , KLAT   , KLEV   , KINT  , KHALO
     I , KLON1  , KLON2  , KLAT1  , KLAT2
     I , KP     , KQ     , KR
     R , PARG   , PRES
     R , PALFH  , PBETH
     R , PALFA  , PBETA  , PGAMA   )
C
C*******************************************************************
C
C  VERINT - THREE DIMENSIONAL INTERPOLATION
C
C  PURPOSE:
C
C  THREE DIMENSIONAL INTERPOLATION
C
C  INPUT PARAMETERS:
C
C  KLON      NUMBER OF GRIDPOINTS IN X-DIRECTION
C  KLAT      NUMBER OF GRIDPOINTS IN Y-DIRECTION
C  KLEV      NUMBER OF VERTICAL LEVELS
C  KINT      TYPE OF INTERPOLATION
C            = 1 - LINEAR
C            = 2 - QUADRATIC
C            = 3 - CUBIC
C            = 4 - MIXED CUBIC/LINEAR
C  KLON1     FIRST GRIDPOINT IN X-DIRECTION
C  KLON2     LAST  GRIDPOINT IN X-DIRECTION
C  KLAT1     FIRST GRIDPOINT IN Y-DIRECTION
C  KLAT2     LAST  GRIDPOINT IN Y-DIRECTION
C  KP        ARRAY OF INDEXES FOR HORIZONTAL DISPLACEMENTS
C  KQ        ARRAY OF INDEXES FOR HORIZONTAL DISPLACEMENTS
C  KR        ARRAY OF INDEXES FOR VERTICAL   DISPLACEMENTS
C  PARG      ARRAY OF ARGUMENTS
C  PALFH     ALFA HAT
C  PBETH     BETA HAT
C  PALFA     ARRAY OF WEIGHTS IN X-DIRECTION
C  PBETA     ARRAY OF WEIGHTS IN Y-DIRECTION
C  PGAMA     ARRAY OF WEIGHTS IN VERTICAL DIRECTION
C
C  OUTPUT PARAMETERS:
C
C  PRES      INTERPOLATED FIELD
C
C  HISTORY:
C
C  J.E. HAUGEN       1      1992
C
C*******************************************************************
C
      IMPLICIT NONE
C
      INTEGER KLON   , KLAT   , KLEV   , KINT   , KHALO,
     I        KLON1  , KLON2  , KLAT1  , KLAT2
C
      INTEGER   KP(KLON,KLAT), KQ(KLON,KLAT), KR(KLON,KLAT)
      REAL    PARG(2-KHALO:KLON+KHALO-1,2-KHALO:KLAT+KHALO-1,KLEV)  ,
     R        PRES(KLON,KLAT)     ,
     R       PALFH(KLON,KLAT)     ,  PBETH(KLON,KLAT)  ,
     R       PALFA(KLON,KLAT,4)   ,  PBETA(KLON,KLAT,4),
     R       PGAMA(KLON,KLAT,4)
C
      INTEGER JX, JY, IDX, IDY, ILEV
      REAL Z1MAH, Z1MBH
C
C  LINEAR INTERPOLATION
C
      DO JY = KLAT1,KLAT2
      DO JX = KLON1,KLON2
         IDX  = KP(JX,JY)
         IDY  = KQ(JX,JY)
         ILEV = KR(JX,JY)
C
         PRES(JX,JY) = PGAMA(JX,JY,1)*(
C
     +   PBETA(JX,JY,1)*( PALFA(JX,JY,1)*PARG(IDX-1,IDY-1,ILEV-1)
     +                  + PALFA(JX,JY,2)*PARG(IDX  ,IDY-1,ILEV-1) )
     + + PBETA(JX,JY,2)*( PALFA(JX,JY,1)*PARG(IDX-1,IDY  ,ILEV-1)
     +                  + PALFA(JX,JY,2)*PARG(IDX  ,IDY  ,ILEV-1) ) )
C    +
     +               + PGAMA(JX,JY,2)*(
C    +
     +   PBETA(JX,JY,1)*( PALFA(JX,JY,1)*PARG(IDX-1,IDY-1,ILEV  )
     +                  + PALFA(JX,JY,2)*PARG(IDX  ,IDY-1,ILEV  ) )
     + + PBETA(JX,JY,2)*( PALFA(JX,JY,1)*PARG(IDX-1,IDY  ,ILEV  )
     +                  + PALFA(JX,JY,2)*PARG(IDX  ,IDY  ,ILEV  ) ) )
      ENDDO
      ENDDO
C
      RETURN
      END

i.e., real Fortran code, not just intrinsics :-)

Thanks,

--
Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]