Compaq COBOL
User Manual


Previous Contents Index


Legend: Y = Subsequent stream executes successful I-O operation 
        N = Subsequent stream I-O operation is unsuccessful (File Status 92) 

Example 8-6 uses manual record locking. The file is opened with the ALLOWING ALL clause. The records are read but do not become available to other access streams because of the lock applied by the READ statement (READ...ALLOWING NO OTHERS). When the UNLOCK is executed, the records can be read by another access stream if that stream opens the file allowing writers.

Example 8-6 Sample Program Using Manual Record Locking (Compaq Standard)

FILE-CONTROL. 
    SELECT FILE-1 
         ORGANIZATION IS RELATIVE 
         ASSIGN "SHAREDAT.DAT". 
          . 
          . 
          . 
    I-O-CONTROL. 
         APPLY LOCK-HOLDING ON FILE-1. 
          . 
          . 
          . 
PROCEDURE DIVISION. 
BEGIN. 
     OPEN I-O FILE-1 ALLOWING ALL. 
          . 
          . 
          . 
     READ FILE-1 ALLOWING NO OTHERS AT END DISPLAY "end". 
          . 
          . 
          . 
     REWRITE FILE-1-REC ALLOWING NO OTHERS. 
          . 
          . 
          . 
     UNLOCK FILE-1 ALL RECORDS. 
     CLOSE FILE-1. 
     STOP RUN. 

In manual record locking, you release record locks by the UNLOCK statement or when you close the file (either explicitly or implicitly; when you close a file, any existing record lock is released automatically). The UNLOCK statement provides for either releasing the lock on the current record (on OpenVMS Alpha systems with UNLOCK RECORD) or releasing all locks currently held by the access stream on the file (UNLOCK ALL RECORDS). (On Tru64 UNIX and Windows NT systems for indexed files only, there is no current record lock.)

When you access a shared file with ACCESS MODE IS SEQUENTIAL and use manual record locking, the UNLOCK statement can cause you to violate either of the following statements: (1) the REWRITE statement rule that states that the last input-output statement executed before the REWRITE must be a READ or START statement, or (2) the DELETE statement rule that states that the last input/output statement executed before the DELETE statement must be a READ. You must lock the record before it can be rewritten or deleted.

Releasing Locks on Deleted Records

In automatic record locking, the DELETE operation releases the lock on the record. In manual record-locking mode, you can delete a record using the DELETE statement but still retain a record lock. You must use the UNLOCK ALL RECORDS statement to release the lock on a deleted record.

If a second stream attempts to access a deleted record that retains a lock, the second stream will receive either a "record not found" exception or a hard lock condition. (See Section 8.4.3 for information on hard lock conditions.)

On OpenVMS, If another stream attempts to REWRITE a deleted record for which there is a retained lock, the type of exception that access stream receives depends on its file organization. If the file organization is RELATIVE, the access stream receives the "record locked" status. If the file organization is INDEXED, the access stream succeeds (receives the success status).

In relative files, the lock is on the relative cell (record) and cannot be rewritten until the lock is released. On indexed files, the lock is on the record's file address (RFA) of the deleted record, so a new record (with a new RFA) can be written to the file. <>

Bypassing a Record Lock

When you use manual record locking, you can apply a READ REGARDLESS or START REGARDLESS statement to bypass any record lock that exists. READ REGARDLESS reads the record and applies no locks to the record. START REGARDLESS positions to the record and applies no locks to the record. If the record is currently locked by another access stream, a soft record lock condition can be detected by a USE procedure. (See Section 8.4.3 for information on soft record locks.)

You use READ REGARDLESS or START REGARDLESS when: (1) a record is locked against readers because the record is about to be written, but (2) your access program needs the existing record regardless of the possible change in its data.

Note

You should recognize that READ REGARDLESS and START REGARDLESS are of limited usefulness. They can only reliably tell the user whether a record exists with a given key value. They cannot guarantee the current contents of the data in the record. You prevent the use of READ REGARDLESS or START REGARDLESS at the file protection level when you prevent readers from referencing the file.

You can use READ REGARDLESS and START REGARDLESS during sequential file access to force the File Position Indicator.

When you close a file, any existing record lock is released automatically. The UNLOCK RECORD statement releases the lock only on the current record on OpenVMS Alpha systems, which is the last record you successfully accessed. On Tru64 UNIX systems for indexed files only, there is no current record lock.

8.4.3 Error Handling for Record Locking

This section describes the locking error conditions and the two kinds of locks: hard and soft.

Note

Soft record locks are available for Compaq standard record locking but are not part of X/Open standard. Soft record lock conditions also do not occur on the Tru64 UNIX system for indexed files.

Any record contention error results in an unsuccessful statement for which a USE procedure will be invoked. A "record-locked" condition results in an I-O status code of 92.

Interpreting Locking Error Conditions

Two record-locking conditions (hard and soft record lock) indicate whether a record was transferred to the record buffer. Compaq COBOL provides the success, failure, or informational status of an I/O operation in the file status variable.

Hard Record Locks

A hard record lock condition, which causes the file status variable to be set to 92, indicates that the record operation failed and the record was not transferred to the buffer. A hard record lock results from a scenario such as the one shown in the following steps, which uses Compaq standard manual record-locking mode:

  1. Program A opens the file I-O ALLOWING ALL.
  2. Program A reads a record ALLOWING NO OTHERS.
  3. Program B opens the file I-O ALLOWING ALL.
  4. Program B tries to access the same record as A.
  5. Program B receives a hard record lock condition.
  6. The record is not accessible to Program B.
  7. Program B's File Status variable is set to 92.
  8. Program B's USE procedure is invoked.
  9. Program A continues.

The record was not available to Program B.

On Tru64 UNIX, for INDEXED files, READ with the ALLOWING UPDATERS clause as well as any START statement will not detect a locked record. Potential conflicts do not trigger a hard lock condition, only actual conflicts do. <>

Soft Record Locks

Soft record locks can occur only with Compaq standard record locking. A soft record lock condition, which causes the file status variable to be set to 90, indicates that the record operation was successful, the record was transferred to the buffer, and a prior access stream holds a lock on that record. A soft record lock can be detected by a USE procedure. This condition occurs in either of the following two situations:

For example, a soft record lock results from a situation such as the following, which uses automatic record-locking mode:

  1. Program A opens the file I-O ALLOWING READERS.
  2. Program A reads a record.
  3. Program B opens the file INPUT ALLOWING ALL.
  4. Program B reads the same record.
  5. Program B receives a soft record lock condition. The record is accessible to Program B.
  6. Program B's File Status variable is set to 90.
  7. On OpenVMS, Program B's USE procedure (if any) is invoked. <>
  8. Programs A and B continue.

The record was available to Program B.

Note

A file (and thus the records in it) cannot be shared if automatic or manual record locking is not specified by the user.

A manual record-locking environment is required in order for the REGARDLESS and ALLOWING options to be used on a READ statement. The READ REGARDLESS and START REGARDLESS statements should be used only when the access program clearly needs the existing record regardless of the possible imminent change in its data. For a full description of the OPEN, READ, and START statements and their options, see the Compaq COBOL Reference Manual.

Soft Record Locks and Declarative USE Procedures

If a soft record lock occurs, the values of the following variables for the current file are undefined until the execution of any applicable Declarative USE procedure is complete:

These variables remain undefined if the Declarative USE procedure terminates with an EXIT PROGRAM statement.

Hard Record Locks and File Position During Sequential Access

If a hard record lock condition occurs for a sequential READ statement, the file position indicator is unaffected. If the application must continue reading records, the following actions may be taken:

Error Handling Example

Example 8-7 is an example of processing locked record conditions.

Example 8-7 Program Segment for Record-Locking Exceptions

FILE-CONTROL. 
    SELECT file-name ASSIGN TO "fshare.dat" 
           FILE STATUS IS file-stat. 
 
WORKING-STORAGE SECTION. 
01  file-stat PIC XX. 
    88 record-ok     VALUES "00", "02", "04". 
    88 record-locked VALUE  "92". 
01  RETRY-COUNT  PIC 9(2). 
01  MAX-RETRY    pic 9(2) VALUE 10.    
    . 
    . 
    . 
PROCEDURE DIVISION. 
DECLARATIVES. 
FILE-USE SECTION.  USE AFTER STANDARD EXCEPTION PROCEDURE ON file-name. 
FILE-ERR. 
* need declaratives to trap condition, but let main code process it. 
* invalid key clause does not apply 
 
        IF record-locked 
           continue 
        ELSE 
           . 
           . 
           . 
        END-IF. 
END DECLARATIVES. 
MAIN-BODY SECTION. 
BEGIN. 
    DISPLAY "From main-body". 
 
    . 
    . 
    . 
GET-RECORD. 
      READ file-name. 
      IF NOT record-ok 
         PERFORM check-read. 
      . 
      . 
      . 
CHECK-READ. 
      IF record-locked 
         MOVE 1 to retry-count 
         PERFORM retry-read UNTIL record-ok OR 
                                  retry-count > max-retry 
         IF record-locked AND retry-count > max-retry 
            DISPLAY "Record is unavailable...enter new record to retrieve: " 
                     WITH NO ADVANCING 
            ACCEPT record-id 
            GO TO get-record 
         END-IF 
      END-IF. 
 
* handle other possible errors here 
       
RETRY-READ. 
     READ file-name. 
     add 1 to retry-count. 


Chapter 9
Using the SORT and MERGE Statements

This chapter includes the following information about using the SORT and MERGE statements to sort and merge records for sequential, line sequential, relative, and indexed files:

9.1 Sorting Data with the SORT Statement

The SORT statement provides a wide range of sorting capabilities and options. To establish a SORT routine, you do the following:

  1. Declare the sort file with an Environment Division SELECT statement.
  2. Use a Data Division Sort Description (SD) entry to define the sort file's characteristics.
  3. Use a Procedure Division SORT statement.

The following program segments demonstrate SORT program coding:

SELECT Statement (Environment Division)


SELECT SORT-FILE ASSIGN TO "SRTFIL" 

An SD File Description Entry (Data Division)


SD  SORT-FILE. 
01  SORT-RECORD. 
     05 SORT-KEY1    PIC X(5). 
     05 SOME-DATA    PIC X(25). 
     05 SORT-KEY2    PIC XX. 

Note

You can place the sort file anywhere in the FILE SECTION, but you must use a Sort Description (SD) level indicator, not a File Description (FD) level indicator. Also, you cannot use the SD file for any other purpose in the COBOL program.

SORT Statement (Procedure Division)


SORT SORT-FILE 
     ASCENDING KEY S-NAME 
     USING NAME-FILE 
     GIVING NEW-FILE. 

The SORT statement names a sort file, sort keys, an input file, and an output file. An explanation of sort keys follows.

Sorting Concepts

Records are sorted based on the data values in the sort keys. Sort keys identify the location of a record or the ordering of data. The following example depicts unsorted employee name and address records used for creating mailing labels:
Smith, Joe 234 Ash St. New Boston NH 04356
Jones, Bill 12 Birch St. Gardner MA 01430
Baker, Tom 78 Oak St. Ayer MA 01510
Thomas, Pete 555 Maple St. Maynard MA 01234
Morris, Dick 21 Harris St. Acton ME 05670

If you sort the addresses in the previous example in ascending order using the zip code as the sort key, the mailing labels are printed in the order shown in the following example:
          SORT KEY
Thomas, Pete 555 Maple St. Maynard MA 01234
Jones, Bill 12 Birch St. Gardner MA 01430
Baker, Tom 78 Oak St. Ayer MA 01510
Smith, Joe 234 Ash St. New Boston NH 04356
Morris, Dick 21 Harris St. Acton ME 05670

Also, records can be sorted on more that one key at a time. If you need an alphabetical listing of all employees within each state, you can sort on the state code first (major sort key) and employee name second (minor sort key).

For example, if you sort the file in ascending order by state and last name, the employee names and addresses appear in the order shown in the following example:
SORT KEY
(minor)
      SORT KEY
(major)
 
Baker, Tom 78 Oak St. Ayer MA 01510
Jones, Bill 12 Birch St. Gardner MA 01430
Thomas, Pete 555 Maple St. Maynard MA 01234
Morris, Dick 21 Harris St. Acton ME 05670
Smith, Joe 234 Ash St. New Boston NH 04356

9.1.1 File Organization Considerations for Sorting

You can sort any file regardless of its organization; furthermore, the organization of the output file can differ from that of the input file. For example, a sort can have a sequential input file and a relative output file. In this case, the relative key for the first record returned from the sort is 1; the second record's relative key is 2; and so forth. However, if an indexed file is described as output in the GIVING or OUTPUT PROCEDURE phrases, the first sort key associated with the ASCENDING phrase must specify the same character positions specified by the RECORD KEY phrase for that file.

Sections 9.1.2, 9.1.3, and 9.1.4 describe the ASCENDING and DESCENDING KEY phrases, the USING and GIVING phrases, and the INPUT PROCEDURE and OUTPUT PROCEDURE phrases for sorting.

9.1.2 Specifying Sort Parameters with the ASCENDING and DESCENDING KEY Phrases

Use the Data Division ASCENDING and DESCENDING KEY phrases to specify your sort parameters. The order of data names determines the sort hierarchy; that is, the major sort key is the first data name entered, while the minor sort key is the last data name entered.

In the following example, the hierarchy of the sort is SORT-KEY-1, SORT-KEY-2, SORT-KEY-3.


SORT SORT-FILE 
    ASCENDING KEY SORT-KEY-1 SORT-KEY-2 
    DESCENDING KEY SORT-KEY-3 

9.1.3 Resequencing Files with the USING and GIVING Phrases

If you only need to resequence a file, use the USING and GIVING phrases of the SORT statement. The USING phrase opens the input file, then reads and releases its records to the sort. The GIVING phrase opens and writes sorted records to the output file.

Note that you cannot manipulate data with either the USING or the GIVING phrases.

Consider this SORT statement:


SORT SORT-FILE ON ASCENDING KEY SORT-KEY-1 
     USING INPUT-FILE GIVING OUTPUT-FILE. 

It does the following:

  1. Opens INPUT-FILE
  2. Reads all records in INPUT-FILE and releases them to the sort
  3. Sorts the records in ascending sequence using the data in SORT-KEY-1
  4. Opens the output file and writes the sorted records to OUTPUT-FILE
  5. Closes all files used in the SORT statement

9.1.4 Manipulating Data Before and After Sorting with the INPUT PROCEDURE and OUTPUT PROCEDURE Phrases

You can manipulate data before and after sorting by using the INPUT PROCEDURE and OUTPUT PROCEDURE phrases, and sort only some of the information in a file. For example, these phrases allow you to use only those input records and/or input data fields you need.

The INPUT PROCEDURE phrase replaces the USING phrase when you want to manipulate data entering the sort. The SORT statement transfers control to the sections or paragraphs named in the INPUT PROCEDURE phrase. You then use COBOL statements to open and read files, and manipulate the data. You use the RELEASE statement to transfer records to the sort. After the last statement of the input procedure executes, control is given to the sort, and the records are subsequently sorted.

After the records are sorted, the SORT statement transfers control to the sections or paragraphs named in the OUTPUT PROCEDURE phrase. This phrase replaces the GIVING phrase when you want to manipulate data in the sort. You can use COBOL statements to open files and manipulate data. You use the RETURN statement to transfer records from the sort. For example, you can use the RETURN statement to retrieve the sorted records for printing a report.

Example 9-1 shows a sample sort using the INPUT and OUTPUT procedures.

Example 9-1 INPUT and OUTPUT PROCEDURE Phrases

IDENTIFICATION DIVISION. 
PROGRAM-ID.  EX0901. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
 
FILE-CONTROL. 
    SELECT INPUT-FILE   ASSIGN TO "input.dat". 
    SELECT OUTPUT-FILE  ASSIGN TO "output.dat". 
    SELECT SORT-FILE    ASSIGN TO "sort.dat". 
 
DATA DIVISION. 
FILE SECTION. 
FD  INPUT-FILE. 
01  INPUT-RECORD     PIC X(100). 
FD  OUTPUT-FILE. 
01  OUTPUT-RECORD    PIC X(100). 
SD  SORT-FILE. 
01  SORT-RECORD      PIC X(100). 
01  SORT-KEY-1       PIC XXX. 
01  SORT-KEY-2       PIC XXX. 
 
WORKING-STORAGE SECTION. 
 
PROCEDURE DIVISION. 
000-SORT SECTION. 
010-DO-THE-SORT. 
    SORT SORT-FILE ON ASCENDING KEY SORT-KEY-1 
                   ON DESCENDING KEY SORT-KEY-2 
                   INPUT PROCEDURE IS 050-RETRIEVE-INPUT 
                                THRU 100-DONE-INPUT 
                   OUTPUT PROCEDURE IS 200-WRITE-OUTPUT 
                                THRU 230-DONE-OUTPUT. 
    DISPLAY "END OF SORT". 
    STOP RUN. 
050-RETRIEVE-INPUT SECTION. 
060-OPEN-INPUT. 
    OPEN INPUT INPUT-FILE. 
070-READ-INPUT. 
    READ INPUT-FILE AT END 
        CLOSE INPUT-FILE 
        GO TO 100-DONE-INPUT. 
    MOVE INPUT-RECORD TO SORT-RECORD. 
*********************************************************** 
* You can add, change, or delete records before sorting   * 
* using COBOL data manipulation                           * 
* techniques.                                             * 
*********************************************************** 
    RELEASE SORT-RECORD. 
    GO TO 070-READ-INPUT. 
100-DONE-INPUT SECTION. 
110-EXIT-INPUT. 
    EXIT. 
200-WRITE-OUTPUT SECTION. 
210-OPEN-OUTPUT. 
    OPEN OUTPUT OUTPUT-FILE. 
220-GET-SORTED-RECORDS. 
    RETURN SORT-FILE AT END 
        CLOSE OUTPUT-FILE 
        GO TO 230-DONE-OUTPUT. 
    MOVE SORT-RECORD TO OUTPUT-RECORD. 
*********************************************************** 
* You can add, change, or delete sorted records           * 
* using COBOL data manipulation                           * 
* techniques.                                             * 
*********************************************************** 
    WRITE OUTPUT-RECORD. 
    GO TO 220-GET-SORTED-RECORDS. 
230-DONE-OUTPUT SECTION. 
240-EXIT-OUTPUT. 
    EXIT. 

You can combine the INPUT PROCEDURE with the GIVING phrases, or the USING with the OUTPUT PROCEDURE phrases. In Example 9-2, the USING phrase replaces the INPUT PROCEDURE phrase used in Example 9-1.

Note

You cannot access records released to the sort-file after execution of the SORT statement ends.

Example 9-2 USING Phrase Replaces INPUT PROCEDURE Phrase

. 
. 
. 
PROCEDURE DIVISION. 
000-SORT SECTION. 
010-DO-THE-SORT. 
    SORT SORT-FILE ON ASCENDING KEY SORT-KEY-1 
                   ON DESCENDING KEY SORT-KEY-2 
                   USING INPUT-FILE 
                   OUTPUT PROCEDURE IS 200-WRITE-OUTPUT 
                                  THRU 230-DONE-OUTPUT. 
    DISPLAY "END OF SORT". 
    STOP RUN. 
200-WRITE-OUTPUT SECTION. 
210-OPEN-OUTPUT. 
    OPEN OUTPUT OUTPUT-FILE. 
220-GET-SORTED-RECORDS. 
    RETURN SORT-FILE AT END 
        CLOSE OUTPUT-FILE 
        GO TO 230-DONE-OUTPUT. 
    MOVE SORT-RECORD TO OUTPUT-RECORD. 
    WRITE OUTPUT-RECORD. 
    GO TO 220-GET-SORTED-RECORDS. 
230-DONE-OUTPUT SECTION. 
240-EXIT-OUTPUT. 
    EXIT. 


Previous Next Contents Index