Skip to main content

Problem:

When using a SEARCH ALL in a COBOL program, Mainframe Express does not find the requested item and the index is always set to the maximum size of the table.  Example coding...  Why doesn't this work?

       identification division.

       program-id.  Shm1.

       environment division.

       data division.

       working-storage section.

       01 WS-ZIP-NO                         PIC X(5).

       01  TABLE-1.

           05 TABLE-RECORD-1   OCCURS 12000 TIMES

                                    ASCENDING KEY IS TBL-ZIP-CODE-1

                                    INDEXED BY INDX1.

              10  TBL-ZIP-CODE-1       PIC X(5).

              10  TBL-REGION-1          PIC X(1).

       procedure division.

       a-control.

           perform load-table.

           move 'RG20 ' to WS-Zip-No.

           perform search-table.

           goback.

       LOAD-TABLE SECTION.

           MOVE 'AAAA' TO TBL-NHDS-ZIP-CODE-1(1).

           MOVE 'BBBB' TO TBL-NHDS-ZIP-CODE-1(2).

           MOVE 'CCCC' TO TBL-NHDS-ZIP-CODE-1(3).

           MOVE 'DDDD' TO TBL-NHDS-ZIP-CODE-1(4).

           MOVE 'EEEE' TO TBL-NHDS-ZIP-CODE-1(5).

           MOVE 'FFFF' TO TBL-NHDS-ZIP-CODE-1(6).

           MOVE 'GGGG' TO TBL-NHDS-ZIP-CODE-1(7).

           MOVE 'HHHH' TO TBL-NHDS-ZIP-CODE-1(8).

           MOVE 'IIII' TO TBL-NHDS-ZIP-CODE-1(9).

           MOVE 'JJJJ' TO TBL-NHDS-ZIP-CODE-1(10).

           MOVE 'KKKK' TO TBL-NHDS-ZIP-CODE-1(11).

           MOVE 'LLLL' TO TBL-NHDS-ZIP-CODE-1(12).

           MOVE 'MMMM' TO TBL-NHDS-ZIP-CODE-1(13).

           MOVE 'NNNN' TO TBL-NHDS-ZIP-CODE-1(14).

           MOVE 'OOOO' TO TBL-NHDS-ZIP-CODE-1(15).

           MOVE 'PPPP' TO TBL-NHDS-ZIP-CODE-1(16).

           MOVE 'RG20' TO TBL-NHDS-ZIP-CODE-1(17).

       search-table section.

           SEARCH ALL TABLE-RECORD-1

           AT END DISPLAY 'END OF TABLE'

             WHEN

               TBL-ZIP-CODE-1(INDX1) = WS-ZIP-NO

           END-SEARCH

           .

Resolution:

The issue here is that the table is not initialised correctly.

There are a number of ways to do this.

1 - INITIALIZE TABLE-1 REPLACING ALPHANUMERIC DATA BY HIGH-VALUES.

   

This is the slowest way of initialising the table.

2 - MOVE HIGH-VALUES TO TABLE-SET-UP-1

This is the next best in terms of perfomance

3 - The declaration of TABLE-RECORD-1 should contain the clause "depending on table-rec-size" where this variable accurately contains the count of items in the table - in this instance 17. Then there is no need to initialize the rest of the table and you can use SEARCH ALL.

This option offers the best performance.

Old KB# 2424

#EnterpriseDeveloper
#MFDS