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

Trouble with multiline OpenMP directives

Ioannis_K_
New Contributor I
1,579 Views

Hello,

I am trying to compile a fixed-form Fortran program, and I need to call a very long openMP directive. I tried to write it as a multi-line statement as follows:

      !$OMP PARALLEL PRIVATE(ithr1,igpIP,Tmats,TmatB,x8H,x8Ho,u8H) & 
      !$OMP& PRIVATE(v8H,a8H,kC8H,kini8H,fC8H,mC8H,dhistCB,dhistmatCB) & 
      !$OMP& PRIVATE(genstrs,genstrn,hnmatCB,h1matCB,qlam,depsAV) & 
      !$OMP& PRIVATE(sumweight,elsiz,elCvel,matCvel,Swmid,dt_el,y_Pc) & 
      !$OMP& PRIVATE(aw,w_cr,iSUPG, dloc,K_chksi,K_Cheta,K_Chzeta) & 
      !$OMP& PRIVATE(Porosity,rvC,Sw,Temperature,Tetaw,dspin1,Rrot) & 
      !$OMP& PRIVATE(Rold,Vten,Vold,Lten,nhmatNL,epsXYZ,epsROT) & 
      !$OMP& PRIVATE(sigMatNEW,initmatstif,isSolidMech) 
 
 
These are lines 1138-1145 for a routine isolve.for, of a project fe_program
My compilation always fails, and I am given the following messages:
 
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1138): error #5082: Syntax error, found '&' when expecting one of: PRIVATE REDUCTION FIRSTPRIVATE NUM_THREADS LASTPRIVATE ORDERED SCHEDULE COLLAPSE ...
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1139): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1140): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1141): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1142): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1143): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1144): error #7844: Invalid directive.
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1145): error #7844: Invalid directive.
 
I tried to retain a single PRIVATE() statement, and break the lines accordingly. For example, lines 1139-1140 would be:
 
      !$OMP PARALLEL PRIVATE(ithr1,igpIP,Tmats,TmatB,x8H,x8Ho,u8H, & 
      !$OMP& v8H,a8H,kC8H,kini8H,fC8H,mC8H,dhistCB,dhistmatCB, & 
 
When I tried compiling, I got the error:  
 
 
1>C:\fe_program\v4-CONSTRAINT\iSolve.for(1138): error #5082: Syntax error, found '&' when expecting one of: <IDENTIFIER> <CHAR_CON_KIND_PARAM> <CHAR_NAM_KIND_PARAM> <CHARACTER_CONSTANT> /
 

I would be grateful if anyone could inform me on how to actually write the multi-line directive.

Thanks in advance!

0 Kudos
14 Replies
Steve_Lionel
Honored Contributor III
1,579 Views

Take out the trailing & on the lines - that's not part of the fixed-form continuation syntax.

0 Kudos
Ioannis_K_
New Contributor I
1,579 Views

Hi Steve,

Thank you very much for the prompt response! I tried your suggestion, but it did not work. The only approach that I found to work for the specific, fixed-form source file, was to create line breaks in the same way that I would for a Fortran statement:

!$OMP PARALLEL DO PRIVATE(ithr1,igpIP,Tmats,TmatB,x8H,x8Ho,u8H,
     *  v8H,a8H,kC8H,kini8H,fC8H,mC8H,dhistCB,dhistmatCB,
     *  genstrs,genstrn,hnmatCB,h1matCB,qlam,depsAV,
     *  sumweight,elsiz,elCvel,matCvel,Swmid,dt_el,y_Pc,
     *  aw,w_cr,iSUPG, dloc,K_chksi,K_Cheta,K_Chzeta, 
     *  Porosity,rvC,Sw,Temperature,Tetaw,dspin1,Rrot, 
     * Rold,Vten,Vold,Lten,nhmatNL,epsXYZ,epsROT, 
     * sigMatNEW,initmatstif,isSolidMech,ennum) 
 
Please note that the asterisks in each of the above lines are in column 6. This is the only approach for which my compiler did not complain, but I am not 100% sure that it works the way it should.... Any thoughts would be welcome.
 
Once again, thank you for your help,
 
Yannis
0 Kudos
Steve_Lionel
Honored Contributor III
1,579 Views

Which compiler version are you using? I have a vague memory of a bug in the implementation of OMP directive continuation in fixed-form source.

0 Kudos
Ioannis_K_
New Contributor I
1,579 Views

I am using Visual Fortran Compiler XE 14.0.0.103 .

0 Kudos
Steve_Lionel
Honored Contributor III
1,579 Views

That's probably it, then. Please try a newer compiler.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,579 Views

If you are having issues with syntax in #3, try:

!$OMP PARALLEL DO PRIVATE(ithr1,igpIP,Tmats,TmatB,x8H,x8Ho,u8H,
!$   *  v8H,a8H,kC8H,kini8H,fC8H,mC8H,dhistCB,dhistmatCB,
!$   *  genstrs,genstrn,hnmatCB,h1matCB,qlam,depsAV,
!$   *  sumweight,elsiz,elCvel,matCvel,Swmid,dt_el,y_Pc,
!$   *  aw,w_cr,iSUPG, dloc,K_chksi,K_Cheta,K_Chzeta, 
!$   *  Porosity,rvC,Sw,Temperature,Tetaw,dspin1,Rrot, 
!$   * Rold,Vten,Vold,Lten,nhmatNL,epsXYZ,epsROT, 
!$   * sigMatNEW,initmatstif,isSolidMech,ennum) 

Jim Dempsey

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,579 Views

Note, the "*" is on column 6, not 6+2

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,579 Views

That's not valid OpenMP syntax, however. My recollection is that the Intel documentation was wrong on this point as well.

Quoting from the OpenMP 4.0 specification:

The following sentinels are recognized in fixed form source files:

!$omp | c$omp | *$omp

Sentinels must start in column 1 and appear as a single word with no intervening characters. Fortran fixed form line length, white space, continuation, and column rules apply to the directive line. Initial directive lines must have a space or zero in column 6, and continuation directive lines must have a character other than a space or a zero in column 6.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,579 Views

The sentinal

!$

without omp is a conditional compile line that gets expanded when compiling with -openmp. When compiled with -openmp, in fixed form, !$ is replaced with two spaces.

!$omp on the other hand is a special variation on this in that not only does the command expand with -openmp, but due to the presence os "omp" immediately following !$, it is also a compiler directive of class OpenMP.

See IVF documentation under conditional compilation rules (Search all words: openmp continue)

Jim Dempsey

0 Kudos
John_Campbell
New Contributor II
1,579 Views

Jim,

I had trouble with using your example from another post using '!$' for directives. I combined your example with fixed format and required the following syntax for success. From my testing it appears that:
1)  !$  needs to be replaced by !$omp or !$omp&  for fixed format.
2)  shared(chunk_subs) appears to be required, as default(none) was specified, although fix_hack was not ?
3)  your "if" syntax worked. I also successfully ran with : fix_hack = parallel .and. (nbsubnet.gt.100)

The following adaptation of your example worked in my testing with gFortran 7.2.
I am not sure of the use of !$ in this situation.

It would be good to know what the OpenMP specification requires and what is an ifort extension. This was my 3+ try!

C  file ompc.for
C 
      call try_3
      end

      subroutine try_3
      use omp_lib
      implicit none

      logical :: parallel = .TRUE.
      logical :: fix_hack
      integer, parameter :: nbsubnet = 100
      real  :: vector0(nbsubnet),vector1(nbsubnet),vector2(nbsubnet),
     +         vector3(nbsubnet),vector4(nbsubnet)
    
      integer :: ivector, counter_eval, chunk_subs
      integer :: i,j,k,l,m
      ivector = 100
      chunk_subs = 10
      fix_hack = parallel .and. (nbsubnet.gt.0)
      counter_eval = nbsubnet

!$omp parallel do if (fix_hack)          
!$omp&         default(none)             
!$omp&         shared(vector0, ivector)  
!$omp&         shared(vector1, vector2)  
!$omp&         shared(vector3, vector4)  
!$omp&         shared(chunk_subs)        
!$omp&         private(i,j,l,m)          
!$omp&         reduction(+:counter_eval) 
!$omp&         schedule(static,chunk_subs)

      do k=0,nbsubnet
         print *,k,omp_get_thread_num ()
         if ( omp_get_thread_num () > 0 ) counter_eval = counter_eval-1
      end do

!$omp end parallel do
      print *,'counter_eval =',counter_eval    
      end subroutine try_3

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,579 Views

IVF 2017u5

Free form:

!  OpenMPContinuation.f90 
    program OpenMPContinuation
    use omp_lib
    implicit none

    logical :: parallel = .TRUE.
    logical :: fix_hack
    integer, parameter :: nbsubnet = 100
    real :: vector0(nbsubnet),vector1(nbsubnet),vector2(nbsubnet),vector3(nbsubnet),vector4(nbsubnet)
    
    integer :: ivector, counter_eval, chunk_subs
    integer :: i,j,k,l,m
    ivector = 100
    chunk_subs = 10
    fix_hack = parallel .and. (nbsubnet.gt.0)
!$omp parallel do default(none) if (fix_hack) &
!$             shared(vector0, ivector) &
!$             shared(vector1, vector2) &
!$             shared(vector3, vector4) &
!$             private(i,j,l,m) &
!$             reduction(+:counter_eval) &
!$             schedule(static,chunk_subs)
            do k=0,nbsubnet
                print *,k
    end do
    
    end program OpenMPContinuation

The above works, now testing Fixed Form

Fixed Form:

!  OpenMPContinuation.for 
      program OpenMPContinuation
      use omp_lib
      implicit none

      logical :: parallel = .TRUE.
      logical :: fix_hack
      integer, parameter :: nbsubnet = 100
      real :: vector0(nbsubnet),vector1(nbsubnet),vector2(nbsubnet)
      real :: vector3(nbsubnet),vector4(nbsubnet)
    
      integer :: ivector, counter_eval, chunk_subs
      integer :: i,j,k,l,m
      ivector = 100
      chunk_subs = 10
      fix_hack = parallel .and. (nbsubnet.gt.0)
!$omp parallel do default(none) if (fix_hack)
!$   *         shared(vector0, ivector)
!$   *         shared(vector1, vector2)
!$   *         shared(vector3, vector4)
!$   *         private(i,j,l,m)
!$   *         reduction(+:counter_eval)
!$   *         schedule(static,chunk_subs)
            do k=0,nbsubnet
                print *,k
      end do
    
      end program OpenMPContinuation

The above works.

Jim Dempsey
 

0 Kudos
Steve_Lionel
Honored Contributor III
1,579 Views

There are no ifort extensions at work here. There WAS a bug in how ifort handled OpenMP directive continuation in fixed-form. That bug is not present in the 17.0 compiler but was in the 14.0 compiler.

0 Kudos
John_Campbell
New Contributor II
1,579 Views

Steve,

Should !$ be accepted on an OpenMP directive continuation line ?
It can produce some rather ambiguous responses from some compilers

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,579 Views

!$ is a conditional compile line that can be used on ordinary statements as well as OpenMP directives (start line) containing omp immediately following !$.

!$      integer :: iThread, nThreads
...
!$      iThread = omp_get_thread_num()
!$     nThreads = omp_get_num_threads()

conditionally compiles with -openmp, and treated as comment when compiled without -openmp

As to if !$ lines are continuation lines, this depends on if the statements follow standard Fortran continuation line rules (Free or Fixed).

Jim Dempsey

0 Kudos
Reply