XL Fortran for AIX 8.1

Language Reference

SINGLE / END SINGLE

Purpose

You can use the SINGLE / END SINGLE directive construct to specify that the enclosed code should only be executed by one thread in the team.

The SINGLE directive only takes effect if you specify the -qsmp compiler option.

Format



           .--------------------------.
           V                          |
>>-SINGLE----+----------------------+-+------------------------><
             '-+---+--single_clause-'
               '-,-'
 
 
>>-block-------------------------------------------------------><
 
 
>>-END SINGLE--+-------------------+---------------------------><
               +-NOWAIT------------+
               '-end_single_clause-'
 
 

where single_clause is:



>>-+-private_clause------+-------------------------------------><
   '-firstprivate_clause-'
 
 

private_clause
See -- PRIVATE.

firstprivate_clause
See -- FIRSTPRIVATE.

where end_single_clause is:



   .---------------------------.
   V                           |
>>---copyprivate_clause--+---+-+-------------------------------><
                         '-,-'
 
 

NOWAIT

copyprivate_clause
See -- COPYPRIVATE.

Rules

It is illegal to branch into or out of a block that is enclosed within the SINGLE construct.

The SINGLE construct must be encountered by all threads in a team or by none of the threads in a team. All work-sharing constructs and BARRIER directives that are encountered must be encountered in the same order by all threads in the team.

If you specify NOWAIT on the END SINGLE directive, the threads that are not executing the SINGLE construct will proceed to the instructions following the SINGLE construct. If you do not specify the NOWAIT clause, each thread will wait at the END SINGLE directive until the thread executing the construct reaches the END SINGLE directive. You may not specify NOWAIT and COPYPRIVATE as part of the same END SINGLE directive.

There is no implied BARRIER at the start of the SINGLE construct. If you do not specify the NOWAIT clause, the BARRIER directive is implied at the END SINGLE directive.

You cannot nest SECTIONS, DO and SINGLE directives inside one another if they bind to the same PARALLEL directive.

SINGLE directives are not permitted within the dynamic extent of CRITICAL and MASTER directives. BARRIER and MASTER directives are not permitted within the dynamic extent of SINGLE directives.

If you have specified a variable as PRIVATE, FIRSTPRIVATE, LASTPRIVATE or REDUCTION in the PARALLEL construct which encloses your SINGLE construct, you cannot specify the same variable in the PRIVATE or FIRSTPRIVATE clause of the SINGLE construct.

The SINGLE directive binds to the closest dynamically enclosing PARALLEL directive, if one exists.

Examples

Example 1: In this example, the BARRIER directive is used to ensure that all threads finish their work before entering the SINGLE construct.

      REAL :: X(100), Y(50)
!     ...
!$OMP PARALLEL DEFAULT(SHARED)
      CALL WORK(X)
 
!$OMP BARRIER
!$OMP SINGLE
      CALL OUTPUT(X)
      CALL INPUT(Y)
!$OMP END SINGLE
 
      CALL WORK(Y)
!$OMP END PARALLEL
 

Example 2: In this example, the SINGLE construct ensures that only one thread is executing a block of code. In this case, array B is initialized in the DO (work-sharing) construct. After the initialization, a single thread is employed to perform the summation.

      INTEGER :: I, J
      REAL :: B(500,500), SM
!     ...
 
      J = ...
      SM = 0.0
!$OMP PARALLEL
!$OMP DO PRIVATE(I)
      DO I=1, 500
        CALL INITARR(B(I,:), I)       ! initialize the array B
      ENDDO
!$OMP END DO
 
!$OMP SINGLE                          ! employ only one thread
      DO I=1, 500
        SM = SM + SUM(B(J:J+1,I))
      ENDDO
!$OMP END SINGLE
 
!$OMP DO PRIVATE(I)
      DO I=500, 1, -1
        CALL INITARR(B(I,:), 501-I)   ! re-initialize the array B
      ENDDO
!$OMP END PARALLEL
 

Example 3: This example shows a valid use of the PRIVATE clause. Array X is PRIVATE to the SINGLE construct. If you were to reference array X outside of the construct, it would be undefined.

      REAL :: X(2000), A(1000), B(1000)
 
!$OMP PARALLEL
!     ...
!$OMP SINGLE PRIVATE(X)
      CALL READ_IN_DATA(X)
      A = X(1::2)
      B = X(2::2)
!$OMP END SINGLE
!     ...
!$OMP END PARALLEL
 

Example 4: In this example, the LASTPRIVATE variable I is used in allocating TMP, the PRIVATE variable in the SINGLE construct.

      SUBROUTINE ADD(A, UPPERBOUND)
        INTEGER :: A(UPPERBOUND), I, UPPERBOUND
        INTEGER, ALLOCATABLE :: TMP(:)
!  ...
!$OMP   PARALLEL
!$OMP   DO LASTPRIVATE(I)
        DO I=1, UPPERBOUND
          A(I) = I + 1
        ENDDO
!$OMP   END DO
 
!$OMP   SINGLE FIRSTPRIVATE(I), PRIVATE(TMP)
        ALLOCATE(TMP(0:I-1))
        TMP = (/ (A(J),J=I,1,-1) /)
!  ...
        DEALLOCATE(TMP)
!$OMP   END SINGLE
!$OMP   END PARALLEL
!  ...
      END SUBROUTINE ADD
 

Example 5: In this example, a value for the variable I is entered by the user. This value is then copied into the corresponding variable I for all other threads in the team using a COPYPRIVATE clause on an END SINGLE directive.

        INTEGER I
  !$OMP PARALLEL PRIVATE (I)
  !     ...
  !$OMP SINGLE
        READ (*, *) I
  !$OMP END SINGLE COPYPRIVATE (I)   ! In all threads in the team, I is equal to
                                     ! the value that you entered.
  !     ...
  !$OMP END PARALLEL

Example 6: In this example, variable J with a POINTER attribute is specified in a COPYPRIVATE clause on an END SINGLE directive. The value of J, not the value of the object that it points to, is copied into the corresponding variable J for all other threads in the team. The object itself is shared among all the threads in the team.

        INTEGER, POINTER :: J
  !$OMP PARALLEL PRIVATE (J)
  ! ...
  !$OMP SINGLE
        ALLOCATE (J)
        READ (*, *) J
  !$OMP END SINGLE COPYPRIVATE (J)
  !$OMP ATOMIC
        J = J + OMP_GET_THREAD_NUM()
  !$OMP BARRIER
  !$OMP SINGLE
        WRITE (*, *) 'J = ', J   ! The result is the sum of all values added to
                                 ! J. This result shows that the pointer object
                                 ! is shared by all threads in the team.
        DEALLOCATE (J)
  !$OMP END SINGLE
  !$OMP END PARALLEL
 

Related Information


[ Top of Page | Previous Page | Next Page | Table of Contents | Index ]