Implementing FD interception


The following steps assume that your application program uses the logical-unit-of-work (LUW) methodology and currently issues SQL COMMITs at appropriate points.For more information on these topics, see Using.

The numbers in parentheses in the following steps—for example, (1)—refer to the sample program elements of the APIDEMO (see the following figure) provided in QSTART.SAMPLIB.

  IDENTIFICATION DIVISION.
  PROGRAM-ID. APIDEMO.
***************************************************************
*
*  SAMPLE PROGRAM THAT CAN BE USED TO TEST QUICKSTART'S
*  API MODE. IT READS AN 80 CHARACTER INPUT FILE (DD=INFILE)
*  AND CREATES AN 80 CHARACTER OUTPUT FILE (DD=OUTFILE)
*  BY USING A FILE WITH AT LEAST 30000 RECORDS.
*
*  THE DB2 CHECKPOINT ROUTINE IS INVOKED EXPLICITLY AFTER
*  EACH WRITE OF THE OUTPUT FILE.
***************************************************************
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SOURCE-COMPUTER. IBM-370.
 OBJECT-COMPUTER. IBM-370.
 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
     SELECT INFILE ASSIGN TO INFILE.
     SELECT OUTFILE ASSIGN TO OUTFILE.
 DATA DIVISION.
 FILE SECTION.
 FD INFILE
     RECORD CONTAINS 80 CHARACTERS
     BLOCK CONTAINS 0 RECORDS
 01 IN-REC                      PIC X(80).
 FD OUTFILE
     RECORD CONTAINS 80 CHARACTERS
     BLOCK CONTAINS 0 RECORDS
 01 OUT-REC                     PIC X(80).

 WORKING-STORAGE SECTION.
 01 WORK-EYE                    PIC X(15) VALUE 'PROGRAM=APIDEMO'.

 COPY QSWSLIT.
*
   ******************* START OF SAVE AREA *******************

 COPY QSWSBEG.
*** THE FOLLOWING APPLICATION FIELDS WILL BE CHECKPOINTED

01 WS-FIELD1
05 EOF-FLAG            PIC X(01) VALUE ‘N’.
05 REC-CNTR            PIC 9(07) VALUE 0.
05 OTHERDATA           PIC X(30) VALUE 'ABCABCABCABCABCABCABCABCAB'.
*                           :
*                           :    THE END OF SAVED W/S HERE
*                           :
   COPY QSWSEND.
****************** END OF SAVE AREA *******************
*                           :
*                           : W/S AFTER HERE IS NOT SAVED
*                           : AS IT IS NOT NECESSARY FOR
*                           : A SUCCESSFUL RESTART.
 01 NOT-SAVED          PIC X(30) VALUE 'ABCABCABCABCABCABCABCABCAB'.


   PROCEDURE DIVISION.
        MOVE 'APIDEMO' TO CKPT-PGM-NAME.
        PERFORM CKPT-RTN THRU CKPT-RTN-EXIT.

        IF PROGRAM-IS-RESTARTING
           DISPLAY 'RESTART IN PROGRESS AT RECORD ', REC-CNTR
        ELSE
           DISPLAY 'RECORD COUNTER=' REC-CNTR
      END-IF

      COPY QSOPENI REPLACING MYFD BY INFILE.
      COPY QSOPENO REPLACING MYFD BY OUTFILE.
 
      PERFORM LUW UNTIL EOF-FLAG = 'Y'.

      COPY QSCLOSE REPLACING MYFD BY INFILE.
      COPY QSCLOSE REPLACING MYFD BY OUTFILE.

      MOVE 'E' TO CKPT-REQUEST-TYPE.
      PERFORM CKPT-RTN THRU CKPT-RTN-EXIT.
      DISPLAY 'PROGRAM TERMINATING AFTER ',
         REC-CNTR, ' RECORDS.'.
      GOBACK.
*
  LUW.
      READ INFILE
          AT END MOVE 'Y' TO EOF-FLAG.
      IF EOF-FLAG IS NOT = 'Y'
         ADD 1 TO REC-CNTR
         MOVE IN-REC TO OUT-REC
*
* CAUSE ABEND TO TEST RESTARTS.  PROGRAM WILL ONLY ACTUALLY
* ABEND IF A "//QSCABEND DD DUMMY" CARD EXISTS IN THE JCL.
* FOR THIS TEST, AN INPUT FILE OF AT LEAST 30,000 RECORDS IS
* SUGGESTED.
*
          IF REC-CNTR = 20152
             CALL QSCABEND
          END-IF
          WRITE OUT-REC
          PERFORM CKPT-RTN THRU CKPT-RTN-EXIT
      END-IF.
      EXIT.
*
  CKPT-RTN.
     *
**  THE FOLLOWING CALL TO CKPTRTN HANDLES ALL CHECKPOINTING
**  NEEDS, INCLUDING SAVING SEQUENTIAL FILES POSITIONS, SAVING
**  WORKING STORAGE, AND ISSUING A DB2 COMMIT.
*
      CALL CKPTRTN USING CKPT-SAVE-AREA, CKPT-AREA-END.
*
    CKPT-RTN-EXIT.
      EXIT .
  1. Convert Sequential Files to QUICKSAM Format

    To provide restart capabilities, QUICKSTART must manage all activity for the sequential file that are to be repositioned in case of an abend. Depending on your application, this may not include all sequential files. Even if a file does not need to be repositioned, you can use QUICKSTART to manage the input/output activity.To enable QUICKSTART to manage sequential file activity, you must make the following changes to your program:
  2. Identify the files that are to be repositioned by QUICKSTART during a restart.
  3. Convert the repositionable files to QUICKSAM format by replacing OPEN and CLOSE statements for all QUICKSTART-controlled files with the QSOPENI (1),QSOPENO (2), and QSCLOSE (3) copybooks. These copybooks are provided in QSTART.SAMPLIB).
  4. Modify Working Storage
    Make the following changes to your program’s working storage section:
    • Include the information needed by QUICKSTART. Usually, this is done by including copybook QSWSLIT (4).
    • Indicate the application working storage variables that need to be managed by QUICKSTART so they can be restored when an ABEND occurs. For example, you need to indicate the total fields or flags that need to be saved and restored in case of an ABEND. In most cases, only some portions of working storage need to be saved. QUICKSTART allows you to specify the variables that need to be saved by inserting two “eye catchers” surrounding the areas that need to be saved. This is normally done by including the QSWSBEG (5) and QSWSEND (6) copybooks. You can save all working storage, but checkpointing large amounts of working storage could affect performance. For information about multiple save areas, which QUICKSTART supports, see Using.
  5. Perform the CKPT-RTN Routine
    Perform the QUICKSTART CKPT-RTN routine at the following places in the procedure division:

    • At the beginning of the program to initialize QUICKSTART and to check for a restart in progress. This is usually done immediately after the execution of the program (7).
    • At the point where your program currently issues, or should issue, a COMMIT so QUICKSTART can perform its checkpoint activities (7).
    • Just before the normal end of a program to terminate QUICKSTART processing and register the normal completion of the application program (8).

Related topic


 

Tip: For faster searching, add an asterisk to the end of your partial query. Example: cert*

QUICKSTART for MVS 3.4