XL Fortran for AIX 8.1

Language Reference

SNAPSHOT

Purpose

You can use the SNAPSHOT directive to specify a safe location where a breakpoint can be set with a debug program, and provide a set of variables that must remain visible to the debug program. The SNAPSHOT directive provides support for the -qsmp compiler option, though you can use it in a non-multi-threaded program.

There may be a slight performance hit at the point where the SNAPSHOT directive is set, because the variables must be kept in memory for the debug program to access. Variables made visible by the SNAPSHOT directive are read-only. Undefined behavior will occur if these variables are modified through the debugger. Use with discretion.

Format



>>-SNAPSHOT--(--named_variable_list--)-------------------------><
 
 

named_variable
is a named variable that must be accessible in the current scope.

Rules

To use the SNAPSHOT directive, you must specify the -qdbg compiler option at compilation.

Examples

Example 1: In the following example, the SNAPSHOT directive is used to monitor the value of private variables.

     INTEGER :: IDX
     INTEGER :: OMP_GET_NUM_THREADS, OMP_GET_THREAD_NUM
     INTEGER, ALLOCATABLE :: ARR(:)
!     ...
 
!$OMP PARALLEL, PRIVATE(IDX)
!$OMP MASTER
     ALLOCATE(ARR(OMP_GET_NUM_THREADS()))
!$OMP END MASTER
!$OMP BARRIER
 
    IDX = OMP_GET_THREAD_NUM() + 1
 
!IBM* SNAPSHOT(IDX)                 ! The PRIVATE variable IDX is made visible
                                    ! to the debugger.
    ARR(IDX) = 2*IDX + 1
 
!$OMP END PARALLEL
 

Example 2: In the following example, the SNAPSHOT directive is used to monitor the intermediate values in debugging the program.

      SUBROUTINE SHUFFLE(NTH, XDAT)
        INTEGER, INTENT(IN) :: NTH
        REAL, INTENT(INOUT) :: XDAT(:)
        INTEGER :: I_TH, IDX, PART(1), I, J, LB, UB
        INTEGER :: OMP_GET_THREAD_NUM
        INTEGER(8) :: Y=1
        REAL :: TEMP
 
        CALL OMP_SET_NUM_THREADS(NTH)
        PART = UBOUND(XDAT)/NTH
 
!$OMP   PARALLEL, PRIVATE(NUM_TH, I, J, LB, UB, IDX, TEMP), SHARED(XDAT)
          NUM_TH = OMP_GET_THREAD_NUM() + 1
          LB = (NUM_TH - 1)*PART(1) + 1
          UB = NUM_TH*PART(1)
 
          DO I=LB, UB
!$OMP       CRITICAL
              Y = MOD(65539_8*y, 2_8**31)
              IDX = INT(REAL(Y)/REAL(2_8**31)*(UB - LB) + LB)
 
!SMP$         SNAPSHOT(i, y, idx, num_th, lb, ub)
 
!$OMP       END CRITICAL
            TEMP = XDAT(I)
            XDAT(I) = XDAT(IDX)
            XDAT(IDX) = TEMP
         ENDDO
 
!SMP$    SNAPSHOT(TEMP)                   ! The user can examine the value of the
                                          ! TEMP variable
 
!$OMP  END PARALLEL
     END
 

Related Information

See the User's Guide for details on the -qdbg compiler option.


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