Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Sorting two-digit year numbers with a century window

General description

This description applies both to file sorting and to table sorting. The century window is defined in the same way as in the COBOL function YEAR-TO-YYYY. The last year belonging to the window is specified relative to the current year. The specified value determines the number of years in the future which belong to the century window. For example, the value 50 when run in 1998 represents the period from 1949 through 2048.

A SORT special register SORT-EOW (SORT-END-OF-WINDOW) is defined to determine the century window. It is made available in COBOL programs with the SORT or MERGE statement, and implicitly described by the compiler with PIC 9(7) PACKED-DECIMAL. The value saved in SORT-EOW must be between 0 and 99. The default value is 50.

The ASCENDING/DESCENDING phrases in the SORT and MERGE statements have been extended to enable two-digit year numbers to be used as a SORT key depending on a century window.

In the MERGE statement the position of the century window is determined at the start of processing (evaluation of SORT-EOW and current year). If, for example, files are first sorted with the SORT statement, the same century window must be selected.

Example 12-9

SORT with century window selection

IDENTIFICATION DIVISION.
PROGRAM-ID.SORTIERY.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
   SELECT MASTER-FILE ASSIGN TO "MASTER-FILE".
   SELECT OUTPUT-FILE ASSIGN TO "OUTPUT-FILE".
   SELECT SORT-FILE ASSIGN TO "SORTWK".
DATA DIVISION.
FILE SECTION.
FD MASTER-FILE.
01 MASTER-RECORD.
   02 E0      PIC X.
   02 EY1     PIC 99.
   02 EY2     PIC 99 USAGE PACKED-DECIMAL.
   02 E3      PIC X(10).
FD OUTPUT-FILE.
01 OUTPUT-RECORD.
   02 A0      PIC X.
   02 AY1     PIC 99.
   02 AY2     PIC 99 USAGE PACKED-DECIMAL.
   02 A3      PIC X(10).

SD SORT-FILE.
01 SORT-RECORD.
   02 S0      PIC X.
   02 SY1     PIC 99.
   02 SY2     PIC 99 USAGE PACKED-DECIMAL.
   02 S3      PIC X(10).
PROCEDURE DIVISION.
P1 SECTION.
SORT.
* Specification of the century window: starting from the
* year 1998, 2008 is the final year of the century window

      MOVE 10 TO SORT-EOW

* The keys SY1 and SY2 are handled as two-digit year
* numbers within the century window of 1909-2008:
* 06 is greater than 75

     SORT SORT-FILE ASCENDING KEY-YY SY1 SY2
                 DESCENDING KEY S3
     USING MASTER-FILE GIVING OUTPUT-FILE.
SORTEND.
     STOP RUN.