Using the COBOL SORT verb


When designing a COBOL restartable program which uses the “SORT” Verb, there are the following additional considerations:

  • If INPUT PROCEDURE and OUTPUT PROCEDURE Clauses are specified, they should not contain QUICKSTART checkpoint requests. This is because the “SORT” Verb does not constitute a QUICKSTART restartable entity.
  • When writing or modifying a COBOL program which includes a “SORT” Verb, the program should issue a “Forced checkpoint” to QUICKSTART immediately before and immediately after the “SORT” Verb.
  • Before issuing the “Forced checkpoint”, the program should set a corresponding field within the Saved Area of Working Storage Section to indicate the status of the “SORT” within the processing scheme of the application program.
  • For example, this “SORT” status indicator field can have the value of 'B' “before” the “SORT”, and the value 'A' “after” the “SORT”. Using this field during a restart, the program can navigate to the proper location within the application program and successfully resume execution.
  • The COBOL “SORT” Verb must use the USING and GIVING Clauses. This is the only case in which a COBOL “FD Section” must be coded under a QUICKSTART implementation.
  • Furthermore, the files defined for the USING and the GIVING Clauses must be of different “FDs”, since restartability cannot be successful if they reference the same “FDs”.
  • The COBOL Verbs “OPEN”, “CLOSE”, “READ”, and “WRITE” should not be used by the application program in conjunction with these files. The files may only be used internally by the COBOL “SORT” processor.
  • QUICKSAM must be “CALLed”, as needed, to perform any “WRITEs” before the “SORT” and any “READs” after the “SORT”.
    The following is a COBOL application stub demonstrating the recommended use of the COBOL “SORT” Verb. Only one SAM DEFINITION area is used as only one file is open at any one time. First we WRITE the records to the SORT's input file. Then we close the file and force a checkpoint before performing the SORT. After the SORT, we need to OPEN the output of the SORT as an input file.

    FILE-CONTROL.
    SELECT SORT-INPUT ASSIGN TO UT-S-INSORT.
    SELECT SORT-OUTPUT ASSIGN TO UT-S-OUTSORT.
    SELECT SORTFILE ASSIGN TO UT-S-SORT1.
    DATA DIVISION.
    FILE SECTION.
    FD SORT-INPUT, RECORDING MODE IS F, BLOCK CONTAINS 0 RECORDS,
    RECORD CONTAINS nn CHARACTERS, LABEL RECORDS ARE STANDARD,
    DATA RECORD IS SORTIN-RECORD.
    01 SORTIN-RECORD PIC X(nn).
    FD SORT-OUTPUT, RECORDING MODE IS F, BLOCK CONTAINS 0 RECORDS,
    RECORD CONTAINS nn CHARACTERS, LABEL RECORDS ARE STANDARD,
    DATA RECORD IS SORTOUT-RECORD.
    01 SORTOUT-RECORD PIC X(nn).
    SD SORTFILE, RECORDING MODE IS F, RECORD CONTAINS nn CHARACTERS,
    DATA RECORD IS SORT-RECORD.
    01 SORT-RECORD PIC X(nn).
    WORKING-STORAGE SECTION.
    01 CKPT-SAVE-AREA . . .
    05 SAM1-DEFINITION.
    10 SAM1-DDNAME PIC X(08) VALUE 'INSORT'.
    10 SAM1-REQUEST-TYPE PIC X(06) VALUE 'OPEN'.
    10 SAM1-FILE-TYPE PIC X(01) VALUE 'O'.
    10 SAM1-RETURN-CODE PIC X(03) VALUE SPACES.
    10 FILLER PIC X(62) VALUE SPACES.
    *
    * NOTE: By using the field PROCESSING-PHASE, the program is
    * fully restartable without any navigational code.
    * The PERFORMs all use the UNTIL clause, which checks the
    * condition before executing for the first time.
    * Selection of the first paragraph to actually execute is based
    * on the processing status prior to any intermediate ABEND, which
    * may have occurred.
    01 PROCESSING-PHASE PIC X(1) VALUE ' '.
    88 GENERATE-DONE VALUE 'G','S','A'.
    88 SORT-DONE VALUE 'S','A'.
    88 ALL-DONE VALUE 'A'.
    PROCEDURE DIVISION.
    PERFORM CKPT-RTN THRU CKPT-EXIT.
    PERFORM GENERATE-SORT-RECORDS
    UNTIL GENERATE-DONE.
    IF NOT SORT-DONE THEN
    MOVE 'G' TO PROCESSING-PHASE
    MOVE 'F' TO CKPT-REQUEST-TYPE
    MOVE 'CLOSE ' TO SAM1-REQUEST-TYPE
    CALL QUICKSAM USING SAM1-DEFINITION, IO-AREA
    PERFORM CKPT-RTN THRU CKPT-RTN-EXIT
    SORT SORT-FILE ON ASCENDING KEY SORT-KEY,
    USING SORT-IN, GIVING SORT-OUT
    MOVE 'OUTSORT' TO SAM1-DDNAME
    MOVE 'I' TO SAM1-FILE-TYPE
    MOVE 'OPEN' TO SAM1-REQUEST-TYPE
    CALL QUICKSAM USING SAM1-DEFINITION, IO-AREA
    MOVE 'S' TO PROCESSING-PHASE
    MOVE 'F' TO CKPT-REQUEST-TYPE
    PERFORM CKPT-RTN THRU CKPT-RTN-EXIT
    MOVE ' ' TO CKPT-REQUEST-TYPE.
    PERFORM PROCESS-SORTED-RECORDS UNTIL ALL-DONE.
    MOVE 'E' TO CKPT-REQUEST-TYPE.
    PERFORM CKPT-RTN THRU CKPT-RTN-EXIT.
    GOBACK.
    GENERATE-SORT-RECORDS.
    . . .
    MOVE 'WRITE' TO SAM1-REQUEST-TYPE.
    CALL QUICKSAM USING SAM1-REQUEST-TYPE,
    IO-AREA.
    . . .
    PROCESS-SORTED-RECORDS.
    . . .
    MOVE 'READ' TO SAM1-REQUEST-TYPE.
    CALL QUICKSAM USING SAM1-REQUEST-TYPE,
    IO-AREA.

Related topic


 

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