Library View Topics Framed Contents Revised Topics Previous Topic Next Topic Search Search ResultsPrevious Topic MatchNext Topic Match Notes List Notes Print Download No PDF Handheld DisconnectedHandheld ConnectedHelp

5.3.10.2 ASCENDING/DESCENDING KEY Phrase



Data is arranged in ascending or descending order (depending on the key word specified) according to the values contained in data-name-2. The data-names are listed in their descending order of significance.

The order is determined by the rules for comparison of operands (see "Relation Condition" in topic 6.1.6.4). The ASCENDING and DESCENDING KEY data items are used in OCCURS clauses and the SEARCH ALL statement for a binary search of the table element.

data-name-2
Must be the name of the subject entry, or the name of an entry
X subordinate to the subject entry. Data-name-2 cannot be a windowed
X date field. Data-name-2 can be qualified.

If data-name-2 names the subject entry, that entire entry becomes the ASCENDING/DESCENDING KEY, and is the only key that can be specified for this table element.

If data-name-2 does not name the subject entry, then data-name-2:

  • Must be subordinate to the subject of the table entry itself
  • Must not be subordinate to, or follow, any other entry that contains an OCCURS clause
  • Must not contain an OCCURS clause.
    
    
Data-name-2 must not have subordinate items that contain OCCURS DEPENDING ON clauses.

When the ASCENDING/DESCENDING KEY phrase is specified, the following rules apply:

The following example illustrates the specification of ASCENDING KEY data item:


     WORKING-STORAGE SECTION.
     01  TABLE-RECORD.
       05  EMPLOYEE-TABLE OCCURS 100 TIMES
           ASCENDING KEY IS WAGE-RATE EMPLOYEE-NO
           INDEXED BY A,  B.
         10  EMPLOYEE-NAME                         PIC X(20).
         10  EMPLOYEE-NO                           PIC 9(6).
         10  WAGE-RATE                             PIC 9999V99.
         10  WEEK-RECORD OCCURS 52 TIMES
             ASCENDING KEY IS WEEK-NO INDEXED BY C.
           15  WEEK-NO                             PIC 99.
           15  AUTHORIZED-ABSENCES                 PIC  9.
           15  UNAUTHORIZED-ABSENCES               PIC  9.
           15  LATE-ARRIVALS                       PIC  9.

The keys for EMPLOYEE-TABLE are subordinate to that entry, while the key for WEEK-RECORD is subordinate to that subordinate entry.

In the preceding example, records in EMPLOYEE-TABLE must be arranged in ascending order of WAGE-RATE, and in ascending order of EMPLOYEE-NO within WAGE-RATE. Records in WEEK-RECORD must be arranged in ascending order of WEEK-NO. If they are not, results of any SEARCH ALL statement will be unpredictable.

Previous Topic Next Topic © Copyright IBM Corp. 1991, 1998

IBM Library Server Copyright 1989, 2005 IBM Corporation. All rights reserved.





Return to library:   z/OS | z/OS.e | TPF | z/VSE | z/VM | IBM Hardware | IBM System z Redbooks
Glossary:   IBM terminology
Publications:   How to order publications
Readers:   Download IBM Library Reader | Download IBM Softcopy Reader | Download Adobe® Acrobat® Reader®
Library management:   Download IBM Softcopy Librarian
Contacts:   Contact z/OS


Adobe, the Adobe logo, Acrobat, the Acrobat logo, and Acrobat Reader are registered trademarks of Adobe Systems incorporated.