Compaq COBOL
Reference Manual


Previous Contents Index

Format 2

  1. The SORT statement sorts the table referenced by table-name and presents the sorted table in table-name either in the order determined by the ASCENDING or DESCENDING phrases, if specified, or in the order determined by the KEY phrase associated with table_name.
  2. To determine the relative order in which the table elements are stored after sorting, the contents of corresponding key data items are compared according to the rules for comparison of operands in a relation condition, starting with the most significant key data item.

Additional References

Examples

The following examples all illustrate the use of table sorting (Format 2). For examples on Format 1 sorting, see the Compaq COBOL User Manual.

The first example is a simple sort in which the table is sorted by the key definitions in the OCCURS clause of data item tabl. elem-item2 is the major key (ascending) and elem-item1 is the secondary key (descending). A SEARCH ALL statement is used.


        identification division. 
        program-id. EXAMPLE1. 
        data division. 
        working-storage section. 
        01 group-item. 
           05 tabl occurs 10 times 
         ascending elem-item2 
         descending elem-item1 
         indexed by ind. 
              10 elem-item1 pic x. 
              10 elem-item2 pic x. 
        procedure division. 
        1. display "Example 1". 
         move "13n3m3p3o3x1x1x1x1x1" to group-item. 
         sort tabl. 
         search all tabl 
             at end 
          display "not found" 
             when elem-item1 (ind) = "m" 
          if (elem-item1 (ind - 1) = "n") 
          and (elem-item1 (ind + 1) = "1") 
              display "elem-item1 is descending order - 2nd key" 
          else 
              display "sort failed" 
          end-if 
             end-search. 
         exit program. 
        end program EXAMPLE1. 

The following example is also a simple sort in which the table is sorted by the key definitions in the OCCURS clause of data item tabl. elem-item2 is the major key (ascending) and elem-item1 is the secondary key (descending). A SEARCH ALL statement is used.


        identification division. 
        program-id. EXAMPLE2. 
        data division. 
        working-storage section. 
        01 group-item. 
           05 tabl occurs 10 times. 
              10 elem-item1 pic x. 
              10 elem-item2 pic x. 
        procedure division. 
        2. display "Example 2". 
         move "13n3m3p3o3x1x1x1x1x1" to group-item. 
         sort tabl ascending. 
         if tabl (1) = "13" 
         and tabl (2) = "m3" 
             display "tabl is ascending order" 
         else 
             display "sort failed" 
         end-if. 
         exit program. 
        end program EXAMPLE2. 

This following example is a simple sort in which the table is sorted in ascend- ing order using each entire element of the table (data item tabl) to determine the sequence.


        identification division. 
        program-id. EXAMPLE3. 
        data division. 
        working-storage section. 
        01 group-item. 
           05 tabl occurs 10 times 
         ascending elem-item3 
         descending elem-item1. 
              10 elem-item1 pic x. 
              10 elem-item2 pic x. 
              10 elem-item3 pic x. 
        procedure division. 
        3. display "Example 3". 
         move "13bn3cm3ap3do3fx1ex1ix1hx1gx1a" to group-item. 
         sort tabl descending elem-item2 elem-item3. 
         if tabl (1) = "o3f" 
         and tabl (2) = "p3d" 
             display "tabl is descending order" 
         else 
             display "sort failed" 
         end-if. 
         exit program. 
        end program EXAMPLE3. 

The following example sorts only the third instance of tabl2, that is, tabl1(3). The qualified data item, elem-item1 of group2 is its key. In normal PROCEDURE DIVISION reference, elem-item1 of group2 requires two levels of subscripting/indexing, whereas here it has none. Similarly, tabl2 normally requires one level of subscripting, but cannot be subscripted as data-name2 in the SORT statement. Instead it uses the value of t1-ind for determining which instance is sorted.


        identification division. 
        program-id. EXAMPLE4. 
        data division. 
        working-storage section. 
        01 group-item. 
           05 tabl1 occurs 3 times 
         indexed by t1-ind t2-ind. 
              10 tabl2 occurs 5 times. 
                 15 group1. 
                    20 elem-item1 pic x. 
                 15 group2. 
                    20 elem-item1 pic 9. 
        procedure division. 
        4. display "Example 4". 
         move "x5z4y6z6x4a3b2b1a2c1j7j8k8l7j9" to group-item. 
         set t1-ind to 3. 
         sort tabl2 descending elem-item1 of group2. 
         if group1 (3 1) = "j" 
         and group2 (3 1) = "9" 
         and tabl1 (1) = "x5z4y6z6x4" 
         and tabl1 (2) = "a3b2b1a2c1" 
             display "tabl1 (3) is descending order" 
         else 
             display "sort failed" 
         end-if. 
         exit program. 
        end program EXAMPLE4. 

6.8.34 START

Function

The START statement establishes the logical position of the File Position Indicator in an indexed or relative file. The logical position affects subsequent sequential record retrieval.


file-name

is the name of an indexed or relative file with sequential or dynamic access. It cannot be the name of a sort or merge file.

key-data

is one of the following:

It can be qualified.

stment

is an imperative statement executed for an invalid key condition.

stment2

is an imperative statement executed for a not invalid key condition.

Syntax Rules

  1. To use the REGARDLESS or ALLOWING options, the program must include these entries:
  2. There must be an INVALID KEY phrase if file-name does not have an applicable USE AFTER EXCEPTION procedure.
  3. For a relative file, key-data must be the file's RELATIVE KEY data item.
  4. For an indexed file, key-data can be either:
  5. The REGARDLESS and ALLOWING options are Compaq standard syntax, and cannot be used for a file connector that has had X/Open standard syntax (WITH [NO] LOCK or LOCK MODE) specified.

General Rules

All Files

  1. The file must be open in the INPUT or I-O mode when the START statement executes.
  2. If there is no KEY phrase, the implied relational operator is EQUAL.
  3. START statement execution does not change: (a) the contents of the record area or (b) the contents of the data item referred to in the DEPENDING ON phrase of the file's RECORD clause.
  4. The comparison specified by the KEY phrase relational operator occurs between a key for a record in the file and a data item. If the file is indexed, and the operand sizes are unequal, the comparison operates as if the longer one was truncated on the right to the size of the shorter.
  5. START LESS can only be used with a file whose organization is INDEXED and whose access mode is DYNAMIC. The file must be opened for INPUT or I-O.
  6. For indexed files, the file system compares the Key of Reference according to the native collating sequence and the sort order of the Key of Reference. The comparisons IS GREATER THAN, IS GREATER THAN OR EQUAL TO, and IS NOT LESS THAN refer to the logical record order, according to the sort order of the key. For example, if the sort order is descending, the KEY GREATER THAN key-data phrase positions the file at the next record whose key is less than key-data.
    All other numeric or nonnumeric comparison rules apply.
    The File Position Indicator is set to the first logical record in the file whose key satisfies the comparison.
    If no record in the file satisfies the comparison:
  7. START LESS, LESS OR EQUAL, and NOT GREATER set the file position indicator by making reference to the logical record order in the same manner as START GREATER, GREATER OR EQUAL and NOT LESS.
  8. The START verb can use the KEY IS syntax to establish the key field within the file record which is the Key of Reference. An immediately subsequent READ PRIOR will follow the order of the Key of Reference to access the logically previous record in the file according to that Key of Reference. If the KEY IS syntax is not used, the Key of Reference is understood to be the file's primary key field.
  9. When a successful START LESS, LESS OR EQUAL or NOT GREATER has occurred and the Key of Reference has ascending order, the record pointed to by the file position indicator can have the same key value or a smaller key value than the preceding record for the Key of Reference. If the Key of Reference has descending order, the record pointed to can have the same key value or a higher key value for the Key of Reference. The record pointed to can have the same key value if duplicate values for the Key of Reference exist on the file.
  10. When an unsuccessful START LESS, LESS OR EQUAL or NOT GREATER has occurred the key of reference is undefined and a File Status value of 23 is returned, which indicates the INVALID KEY condition, or record not found.
  11. The START statement updates the FILE STATUS data item for the file.
  12. If the File Position Indicator denotes that an optional file is not present when the START statement executes, the invalid key condition exists. START statement execution is then unsuccessful.
  13. The REGARDLESS and ALLOWING options can be used only in a manual record-locking environment. To create a manual record-locking environment, an access stream must specify the APPLY LOCK-HOLDING clause of the I-O-CONTROL paragraph.
  14. The REGARDLESS option allows an access stream to position to a record regardless of any record locks held by other concurrent access streams. The START REGARDLESS option holds no lock on the record positioned to.
    This statement generates a soft record lock condition if the record that is pointed to is locked by another access stream. This condition results in a File Status value of 90 and invokes an applicable USE procedure, if any. Execution of the START REGARDLESS statement is considered successful and execution resumes at the next statement following the START REGARDLESS statement.
    However, on Tru64 UNIX systems, the soft lock condition (file status 90) is not recognized for indexed files. A START REGARDLESS statement for a record locked by another process performs the requested operation on the record and returns a file status of 00. <>
  15. On OpenVMS, the ALLOWING UPDATERS option permits other concurrent access streams in the manual record-locking environment to simultaneously READ, DELETE, START, and REWRITE the current record. This option holds no lock on the current record.
  16. The ALLOWING READERS option permits other concurrent access streams in the manual record-locking environment to simultaneously READ the current record. This option holds a read-lock on each such record read. No access stream can update the current record until it is unlocked.<>
    However, on Windows NT systems there are no read-locks available. The READERS option puts a lock on the record. No access stream can access the record until it is unlocked.<>
  17. On OpenVMS, the ALLOWING NO OTHERS option locks the current record. No other concurrent access stream can access this record until it is unlocked. Only this access stream can update this record. <>
  18. On Tru64 UNIX and Windows NT systems, for indexed files the START statement (with or without the ALLOWING phrase) does not detect or acquire a record lock on the current record. <>
  19. If X/Open file sharing is in effect, the START statement does not detect or acquire a lock.
  20. If Compaq standard record locking is in effect and the ALLOWING or REGARDLESS option is not specified, the default behavior for a START statement is that a lock is acquired if the file is opened in I-O mode and locks are detected in any mode.
  21. If ALLOWING or REGARDLESS is not specified, there is potential for ambiguity regarding Compaq standard record locking or X/Open standard record locking. The selection of X/Open standard (rule 19) or Compaq standard (rule 20) behavior is made as follows by the compiler:
    Any subsequent I-O locking syntax for the same file connector in your program must be consistent: X/Open standard locking and Compaq standard locking (implicit or explicit) cannot be mixed for the same file connector.

Relative Files

  1. The comparison described in General Rule 4 uses the data item referred to by the RELATIVE KEY phrase in the file's ACCESS MODE clause.

Indexed Files

  1. The START statement establishes a Key of Reference as follows:
    The Key of Reference establishes the record ordering for the START statement. (See General Rule 4.) If the execution of the START statement is successful, later sequential READ statements use the same Key of Reference.
  2. If there is a KEY phrase, the comparison described in General Rule 4 uses the contents of key-data.
  3. If there is no KEY phrase, the comparison described in General Rule 4 uses the data item referred to in the file's RECORD KEY clause.
  4. If START statement execution is not successful, the Key of Reference is undefined.
  5. If there is an applicable USE AFTER EXCEPTION procedure, it executes whenever an input or output condition occurs that would result in a nonzero value in the first character of a FILE STATUS data item. However, it does not execute if the condition is invalid key and there is an INVALID KEY phrase.
    See the rules for the INVALID KEY phrase, Section 6.6.10.

Technical Notes

Additional References

6.8.35 STOP

Function

The STOP statement permanently terminates or temporarily suspends image execution.


disp

is any literal, or any figurative constant except ALL literal.

Syntax Rule

If a STOP RUN statement is in a consecutive sequence of imperative statements in a sentence, it must be the last statement in that sequence.

General Rules

  1. STOP RUN terminates image execution.
  2. STOP disp temporarily suspends the image. It displays the value of disp on the user's standard display device. If the user continues the image, execution resumes with the next executable statement.

Technical Notes

  1. STOP RUN causes all open files to be closed before control returns to the operating system prompt.
  2. STOP disp returns control to the operating system command language interpreter level without terminating the image as follows:

Additional Reference (OpenVMS)

See the OpenVMS documentation set for more information on the Compaq Command Language (DCL). <>

6.8.36 STRING

Function

The STRING statement concatenates the partial or complete contents of one or more data items into a single data item.


src-string

is a nonnumeric literal or identifier of a DISPLAY data item. It is the sending area.

delim

is a nonnumeric literal or the identifier of a DISPLAY data item. It is the delimiter of src-string.

dest-string

is the identifier of a DISPLAY data item. It cannot be reference modified. dest-string is the receiving area that contains the result of the concatenated src-strings.

pointr

is an elementary numeric data item described as an integer. It points to the position in dest-string to contain the next character moved.

stment

is an imperative statement executed for an on overflow condition.

stment2

is an imperative statement executed for a not on overflow condition.

Syntax Rules

  1. pointr cannot define the assumed decimal scaling position character (P) in its PICTURE clause.
  2. Literals can be any figurative constant other than ALL literal.
  3. The description of dest-string cannot: (a) have a JUSTIFIED clause or (b) indicate an edited data item.
  4. The size of pointr must allow it to contain a value one greater than the size of dest-string.

General Rules

  1. delim specifies the characters to delimit the move.
  2. If the size of delim is zero characters, it never matches a src-string delimiter.
  3. If src-string is a variable-length item, SIZE refers to the number of characters currently defined for it.
  4. When src-string or delim is a figurative constant, its size is one character.
  5. The STRING statement moves characters from src-string to dest-string according to the rules for alphanumeric to alphanumeric moves. However, no space-filling occurs.
  6. When the DELIMITED phrase contains delim:
  1. No data movement occurs if the size of src-string is zero characters.
  2. When the DELIMITED phrase contains the SIZE phrase:
  3. When the POINTER phrase appears, the program must set pointr to an initial value greater than zero before executing the STRING statement.
  4. When there is no POINTER phrase, the STRING statement operates as if pointr were set to an initial value of 1.
  5. When the STRING statement transfers characters to dest-string, the moves operate as if:
  6. When the STRING statement ends, only those parts of dest-string referenced during statement execution change. The rest of dest-string contains the same data as before the STRING statement executed.
  7. Before it moves each character to dest-string, the STRING statement tests the value of pointr.
    If pointr is less than 1 or greater than the number of character positions in dest-string, the STRING statement:
    If pointr is not less than 1 or not greater than the number of character positions in dest-string after the data is transferred, the STRING statement:
  8. Subscript evaluation for dest-string and pointr occurs at the beginning of the statement.

Additional References

Examples

The examples assume the following data description entries:


WORKING-STORAGE SECTION. 
01  TEXT-STRING           PIC X(30). 
01  INPUT-MESSAGE         PIC X(60). 
01  NAME-ADDRESS-RECORD. 
    03  CIVIL-TITLE       PIC X(5). 
    03  LAST-NAME         PIC X(10). 
    03  FIRST-NAME        PIC X(10). 
    03  STREET            PIC X(15). 
    03  CITY              PIC X(15). 
* Assume CITY ends with "/" 
    03  STATE             PIC XX. 
    03  ZIP               PIC 9(5). 
01 PTR                    PIC 99. 
01 HOLD-PTR               PIC 99. 
01 LINE-COUNT             PIC 99.