Appendix B - Probe Routines

When the dynamic analysis or coverage analysis facility of plusFORT is used, it is necessary to link a set of probe routines into your executable file. Suitable routines are contained in the source code file probes.f90 in the plusFORT installation directory. This document describes those routines. The supplied source code is well commented, and it should be quite possible for experienced users to modify the routines to suit local requirements.

Dynamic Analysis

For each data type in a program, three routines are required:

Routines suitable for use with the INTEGER*4 data type are shown below. The probe source file probes.f90 contains a definition of the 'undefined' value I4UNDF.

!=======================================================================
      SUBROUTINE UD$I4(I4var)                     !  Undefine an INTEGER(I4KIND) variable (ENTRYs for LOGICAL*4 and REAL*4)
      USE PROBE$DATA,ONLY:I4UNDF
      IMPLICIT NONE
      INTEGER(I4KIND) :: I4var

      I4var = I4UNDF
      END SUBROUTINE UD$I4
!=======================================================================
      SUBROUTINE UD$AI4(Nel,I4arr)                !  Undefine an array of INTEGER(I4KIND) (ENTRYs for REAL*4 and LOGICAL*4)
      USE PROBE$DATA,ONLY:I4UNDF
      IMPLICIT NONE
      INTEGER :: Nel
      INTEGER(I4KIND) :: I4arr(Nel)
      INTEGER :: i

      DO 10 i = 1 , Nel
         I4arr(i) = I4UNDF
 10   CONTINUE
      END SUBROUTINE UD$AI4
!=======================================================================
      SUBROUTINE QD$I4(Zname,I4var,Lnum)          !  Check that an INTEGER(I4KIND) item is defined.  If it is not, log and error
                                                  !  and set it to zero.  (ENTRYs for LOGICAL*4 and REAL*4)
      USE PROBE$DATA,ONLY:I4UNDF,LINnum,LVNest
      IMPLICIT NONE
      CHARACTER(*) :: Zname
      INTEGER :: Lnum
      INTEGER(I4KIND) :: I4var
      LINnum(LVNest) = Lnum
      IF ( I4var.EQ.I4UNDF ) THEN
         CALL RP$NDF(Zname)
         I4var = 0
      ENDIF
      END SUBROUTINE QD$I4

Other data types supported by the supplied routines are shown below:

          INTEGER*1            UD$I1, UD$AI1 and QD$I1
          INTEGER*2            UD$I2, UD$AI2 and QD$I2
          INTEGER*4            UD$I4, UD$AI4 and QD$I4
          INTEGER*8            UD$I8, UD$AI8 and QD$I8
          BYTE                 UD$B1, UD$AB1 and QD$B1
          LOGICAL*1            UD$L1, UD$AL1 and QD$L1
          LOGICAL*2            UD$L2, UD$AL2 and QD$L2
          LOGICAL*4            UD$L4, UD$AL4 and QD$L4
          REAL*4               UD$R4, UD$AR4 and QD$R4
          REAL*8               UD$R8, UD$AR8 and QD$R8
          DOUBLE PRECISION     UD$D8, UD$AD8 and QD$D8
          COMPLEX*8            UD$X8, UD$AX8 and QD$X8
          COMPLEX*16           UD$16, UD$A16 and QD$16
          CHARACTER*(*)        UD$CH, UD$ACH and QD$CH

Apart from the declaration of the variable or array being processed, these routines have identical specifications to UD$I4, UD$AI4 and QD$I4. Note that the first three characters of the subroutine names can be changed from the defaults (QD$ and UD$) by setting items 240 and 242 of the SPAG configuration data.

Apart from the above routines, SPAG will insert a call to subroutine QD$LNM just before a CALL statement if there are no other probes there. The purpose of this call is to ensure that the current line number in every active routine is available to the probe routines.

                SUBROUTINE QD$LNM(Lnum)
                INTEGER Lnum

Note that Dynamic Analysis cannot be applied to Fortran 95 programs containing derived types, pointers, allocatable arrays, and array language.

Coverage Analysis

If coverage analysis is active, SPAG inserts the following statements to trace program execution:

These routines call other routines to handle the input, storage and output of coverage data:

CV$INIT

called by PR$ENT

initialises the coverage data system.

CV$SLOT

called by PR$ENT and SB$ENT

uses a hashing algorithm to compute a unique number for each subprogram.

CV$READ

called by PR$ENT and SB$ENT

read data from a coverage data file.

CV$WRITE

called by PR$EXI

writes updated versions of coverage data files.

CV$OPEN

called by CV$READ and CV$WRITE

locates and opens a coverage data file.

Subprogram Timing Analysis

The versions of PR$ENT, PR$EXI, SB$ENT and SB$EXI supplied with plusFORT include calls to routines which measure the time spent in each subprogram, and, at the end of the run, produce a histogram showing the subprograms which take most time. These routines are:

CK$INI

called by PR$ENT

initialises the timing sub-system.

CK$ON(Zname)

called by PR$ENT and SB$ENT

turns specified clock on.

CK$OFF

called by SB$EXI and PR$EXI

turns off the last clock to be switched on.

CK$RPT

called by PR$EXI

writes timing reports to the log file. An sample report is shown below.

CP$TIC

called by all CK$ routines

returns the current CPU usage in 'ticks'.

Example Timing Report

  ------------------------------------------------
 |                 Timing Reports                 |
 |     Job completed after      35.71 seconds     |
 |    Routines taking >1% of total shown below    |
  ------------------------------------------------

              MATTEST          4 calls   0% --------------------------------------------------
                   NF          1 calls   0% --------------------------------------------------
                 NFCG          4 calls   4% **------------------------------------------------
           NF3DPRECON        137 calls   3% **----------------------------------------
           NF2DPRECON      27381 calls   9% *****-----------------------------------
             TRISOLVE    5763813 calls  72% ************************************
              SPMMULT        141 calls  11% ******
              GETGI3D          4 calls   0% -
              GETGI2D        396 calls   0% -

(* excludes called routines, - includes them)
    5791881 Intervals timed

Note the distinction between times including and excluding called routines. For example, 6% of the total time is spent executing NF3DPRECON (represented by 3 '*'s), but another 70% is spent in routines called by NF3DPRECON (represented by 35 '-'s). Inspection of the code reveals that NF2DPRECON is called from NF3DPRECON, and TRISOLVE is called from NF2DPRECON.

If there is a very large number of calls to a particular routine, it is quite possible that the probes themselves will significantly affect execution times. The effect can be reduced by selectively removing calls to SB$ENT and SB$EXI from low level routines.