[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP COBOL
Reference Manual


Previous Contents Index


SET SOPHOMORE TO TRUE                               02
SET MASTERS TO TRUE                                 05
SET GRAD TO TRUE                                    10
SET NON-DEGREE-GRAD TO TRUE                         10
  • Format 4---Setting external switches. The truth value shows the result of the IF statements:


    TRUTH VALUE


    SET UPDATE-RUN TO ON.
    SET REPORT-RUN TO OFF.
    SET NEW-YEAR TO ON.
    IF DO-UPDATE ...                                   true
    IF DO-REPORT ...                                   false
    IF CONTINUE-YEAR...                                false
    SET REPORT-RUN TO ON.
    IF DO-REPORT ...                                   true
    IF SKIP-REPORT ...                                 false
    
  • Format 5---Setting POINTER-VAR to the address of the subscripted table item named Z(I,J,K).


    SET POINTER-VAR TO REFERENCE OF Z(I,J,K).
    
  • Format 6---On OpenVMS Alpha and I64, initializing RETURN-STATUS to FAILURE before calling subprogram SUBPROGA and a Run-Time Library Procedure, then checking for SUCCESS from each.


         .
         .
         .
        SET RETURN-STATUS TO FAILURE.
        CALL "SUBPROGA" GIVING RETURN-STATUS.
        IF RETURN-STATUS IS SUCCESS
            THEN
                GO TO A0200-PARA
            ELSE
                DISPLAY "SUBPROGA failed"
                STOP RUN.
    A0200-PARA.
        SET RETURN-STATUS TO FAILURE.
        CALL "SCR$SET_CURSOR" USING BY VALUE 4, 22 GIVING RETURN-STATUS.
        IF RETURN-STATUS IS SUCCESS
            THEN
                DISPLAY "UPDATE ROUTINE COMPLETED"
            ELSE
                DISPLAY "Cursor positioning failed"
                STOP RUN.
         .
         .
         .
    
    IDENTIFICATION DIVISION.
    PROGRAM-ID. SUBPROGA.
         .
         .
         .
    01    PROGRAM-STATUS    PIC S9(9) COMP.
         .
         .
         .
    PROCEDURE DIVISION GIVING PROGRAM-STATUS.
    A000-BEGIN.
         .
         .
         .
    
        IF ... SET PROGRAM-STATUS TO SUCCESS
          ELSE SET PROGRAM-STATUS TO FAILURE.
        EXIT PROGRAM.    <>
    

    6.8.33 SORT

    Function

    The SORT statement (Format 1) creates a sort file by executing input procedures or transferring records from an input file. It sorts the records in the sort file using one or more keys that you specify. Finally, it returns each record from the sort file, in sorted order, to output procedures or an output file.

    SORT (Format 2) orders the elements in a table. This is especially useful for tables used with SEARCH ALL. The table elements are sorted based on the keys as specified in the OCCURS for the table unless you override them by specifying keys in the SORT statement. If no key is specified, the table elements are the SORT keys.


    sortfile

    is a file-name described in a sort-merge file description (SD) entry in the Data Division.

    sortkey

    (Format 1) is the data-name of a data item in a record associated with sortfile.
    (Format 2) is the data-name of a data item in the table-name table.

    first-proc

    is the section-name or paragraph-name of the first (or only) section or paragraph of the INPUT or OUTPUT procedure range.

    end-proc

    is the section-name or paragraph-name of the last section or paragraph of the INPUT or OUTPUT procedure range.

    infile

    is the file-name of the input file. It must be described in a file description (FD) entry in the Data Division.

    outfile

    is the file-name of the output file. It must be described in a file description (FD) entry in the Data Division.

    table-name (Alpha, I64)

    is a table described with OCCURS in the Data Division. <>

    alpha

    is an alphabet-name defined in the SPECIAL-NAMES paragraph of the Environment Division.

    Syntax Rules

    All Formats

    1. You can use SORT statements anywhere in the Procedure Division except in:
      • Declaratives (Format 1)
      • SORT or MERGE statement input or output procedures
    2. sortkey can be qualified.
    3. sortkey cannot be in a group item that contains variable occurrence data items.
    4. The sortkey description cannot contain an OCCURS clause or be subordinate to a data description entry that does.

    Format 1

    1. If sortfile contains variable-length records, infile records must not be smaller than the smallest in sortfile nor larger than the largest.
    2. If sortfile contains fixed-length records, infile records must not be larger than the largest record described for sortfile.
    3. If outfile contains variable-length records, sortfile records must not be smaller than the smallest in outfile nor larger than the largest.
    4. If outfile contains fixed-length records, sortfile records must not be larger than the largest record described for outfile.
    5. sortfile can have more than one record description. However, sortkey needs to be described in only one of the record descriptions. The character positions referenced by sortkey are used as the key for all the file's records.
    6. The words THRU and THROUGH are equivalent.
    7. If outfile is an indexed file, the first sortkey must be in the ASCENDING phrase. It must specify the same character positions in its record as the prime record key for outfile.

    Format 2 (Alpha, I64)

    1. table-name may be qualified and must have an OCCURS clause in its data description entry. If table-name is subject to more than one level of OCCURS clauses, subscripts must be specified for all levels with OCCURS INDEXED BY.
    2. table-name is a key data-name, subject to the following rules:
      • The data item identified by a key data-name must be the same as, or subordinate to, the data item referenced by table-name.
      • Key data items may be qualified.
      • The data items identified by key data-names must not be variable-length data items.
      • If the data item identified by a key data-name is subordinate to table-name, it must not be described with an OCCURS clause, and it must not be subordinate to an entry that is also subordinate to table-name and contains an OCCURS clause.
    3. The KEY phrase may be omitted only if the description of the table referenced by table-name contains a KEY phrase. <>

    General Rules

    All Formats

    1. The first sortkey you specify is the major key, the next sortkey you specify is the next most significant key, and so forth. The significance of sortkey data items is not affected by how you divide them into KEY phrases. Only first-to-last order determines significance.
    2. The ASCENDING phrase causes the sorted sequence to be from the lowest to highest sortkey value.
    3. The DESCENDING phrase causes the sorted sequence to be from the highest to the lowest sortkey value.
    4. Sort sequence follows the rules for relation condition comparisons.
    5. The DUPLICATES phrase affects the return order of records or table elements whose corresponding sortkey values are equal.
      • When there is a USING phrase, return order is the same as the order of appearance of infile names in the SORT statement.
      • When there is an INPUT PROCEDURE, return order is the same as the order in which the records were released.
      • When table elements are returned, the order is the relative order of the contents of these table elements before sorting.
    6. If there is no DUPLICATES phrase, the return order for records or table elements with equal corresponding sortkey values is unpredictable.
    7. The SORT statement determines the comparison collating sequence for nonnumeric sortkey items when it begins execution. If there is a COLLATING SEQUENCE phrase in the SORT statement, SORT uses that sequence. Otherwise, it uses the program collating sequence described in the OBJECT-COMPUTER paragraph.

    Format 1

    1. If sortfile contains fixed-length records, any shorter infile records are space-filled on the right, following the last character. Space-filling occurs before the infile record is released to sortfile.
    2. The INPUT PROCEDURE range consists of one or more sections or paragraphs that:
      • Appear contiguously in the source program
      • Do not form a part of an OUTPUT PROCEDURE range
    3. The statements in the INPUT PROCEDURE range must include at least one RELEASE statement to transfer records to sortfile.
    4. The INPUT PROCEDURE range can consist of any procedure needed to select, modify, or copy the next record made available by the RELEASE statement to the file referenced by sortfile.
    5. The range of the INPUT PROCEDURE additionally includes all statements executed as a result of a CALL, EXIT, GO TO, or PERFORM statement. The range of the INPUT PROCEDURE also includes all statements in the Declaratives Section that can be executed if control is transferred from statements in the range of the INPUT PROCEDURE.
    6. The INPUT PROCEDURE range must not contain MERGE, RETURN, or SORT statements.
    7. If there is an INPUT PROCEDURE phrase, control transfers to the first statement in its range before the SORT statement sequences the sortfile records. When control passes the last statement in the INPUT PROCEDURE range, the records released to sortfile are sorted.
    8. During execution of the INPUT or OUTPUT procedures, or any USE AFTER EXCEPTION procedure implicitly invoked during the SORT statement, no outside statement can manipulate the files or record areas associated with infile or outfile.
    9. If there is a USING phrase, the SORT statement transfers all records in infile to sortfile. This transfer is an implied SORT statement input procedure. When the SORT statement executes, infile must not be open.
    10. For each infile, the SORT statement:
      • Initiates file processing as if the program had executed an OPEN statement with the INPUT phrase.
      • Gets the logical records and releases them to the sort operation. SORT obtains each record as if the program had executed a READ statement with the NEXT and AT END phrases.
      • Terminates file processing as if the program had executed a CLOSE statement with no optional phrases. The SORT statement ends file processing before it executes any output procedure.

      These implicit OPEN, READ, and CLOSE operations cause associated USE procedures to execute when an exception condition occurs.
    11. OUTPUT PROCEDURE consists of one or more sections or paragraphs that:
      • Appear contiguously in the source program
      • Do not form part of an INPUT PROCEDURE range
    12. When the SORT statement begins the OUTPUT PROCEDURE phrase, it is ready to select the next record in sorted order. The statements in the OUTPUT PROCEDURE range must include at least one RETURN statement to make records available for processing.
    13. When the MERGE statement enters the OUTPUT PROCEDURE range, it is ready to select the next record in merged order. Statements in the OUTPUT PROCEDURE range must execute at least one RETURN statement to make records available for processing.
    14. The OUTPUT PROCEDURE can consist of any procedure needed to select, modify, or copy the next record made available by the RETURN statement in sorted order from the file referenced by sortfile.
    15. The range of the OUTPUT PROCEDURE additionally includes all statements executed as a result of a CALL, EXIT, GO TO, or PERFORM statement. The range of the OUTPUT PROCEDURE also includes all statements in the Declarative USE procedures that can be executed if control is transferred from statements in the range of the OUTPUT PROCEDURE.
    16. The OUTPUT PROCEDURE range must not include MERGE, RELEASE, or SORT statements.
    17. If there is an OUTPUT PROCEDURE phrase, control passes to the first statement in its range after the SORT statement sequences the records in sortfile. When control passes the last statement in the OUTPUT PROCEDURE range, the SORT statement ends. Control then transfers to the next executable statement after the SORT statement.
    18. If there is a GIVING phrase, the SORT statement writes all sorted records to each outfile. This transfer is an implied SORT output procedure. When the SORT statement executes, outfile must not be open.
    19. The SORT statement initiates outfile processing as if the program had executed an OPEN statement with the OUTPUT phrase. The SORT statement does not initiate outfile processing until after INPUT PROCEDURE execution.
    20. The SORT statement obtains the sorted logical records and writes them to each outfile. SORT writes each record as if the program had executed a WRITE statement with no optional phrases.
      For relative files, the value of the relative key data item is 1 for the first returned record, 2 for the second, and so on. When the SORT statement ends, the value of the relative key data item indicates the number of outfile records.
    21. The SORT statement terminates outfile processing as if the program had executed a CLOSE statement with no optional phrases.
    22. These implicit OPEN, WRITE, and CLOSE operations can cause associated USE procedures to execute if they are present. If a USE procedure is present, processing terminates after the USE procedure has completed execution. If a USE procedure is not present, processing terminates as if the program had executed a CLOSE statement with no optional phrases.
    23. If outfile contains fixed-length records, any shorter sortfile records are space-filled on the right, after the last character. Space-filling occurs before the sortfile record is released to outfile.
    24. If the SORT statement is in a fixed segment, its input and output procedures must be completely in either:
      • Fixed segments
      • One independent segment
    25. If the SORT statement is in an independent segment, its input and output procedures must be completely in either:
      • Fixed segments
      • The same independent segment as the SORT statement itself


    Previous Next Contents Index