John Anthony Rinehart
John Anthony Rinehart

Reputation: 35

Get specific entries from .dat file with COBOL

I'm new to COBOL and having trouble to search specific entries in a .dat file. The idea is to search the file for all the records that have a certain code in one of the fields.

I've tried to find the answer in google but everywhere I went the answer was different and I don't know why I could not adapt those to my problem.

I also found this question:

How to insert records in a table in a text file using COBOL and search and display record(s) which satisfy a condition?

But the answer doesn't go into details.

This is my code:

IDENTIFICATION DIVISION.
   program-id. AR AS "A.AR".

   environment division.
   configuration section.
   special-names.  DECIMAL-POINT   IS  COMMA.
   INPUT-OUTPUT    SECTION.
   FILE-CONTROL.
       SELECT  ARQ-ATUALIZACAO  ASSIGN  "C:\temp\atualizacao.dat"
       ORGANIZATION    IS  INDEXED
       ACCESS  MODE    IS  SEQUENTIAL
       RECORD  KEY     IS ID-ATUALIZACAO
       ALTERNATE RECORD KEY IS COD-RASTREIO
       FILE    STATUS  IS  ST-ATUALIZACAO.

   data division.
   FILE    SECTION.
   FD  ARQ-ATUALIZACAO.
   01  REG-ATUALIZACAO.
       05  ID-ATUALIZACAO  PIC 9(10).
       05  COD-RASTREIO    PIC X(13).
       05  TITULO          PIC X(15).
       05  DESCRICAO       PIC X(30).
       05  FILLER          PIC X(30).
   working-storage section.
   01 WS-RECORD.
       03 ENTRIES OCCURS 18 TIMES INDEXED BY I.
           05 WS-ID   PIC 9(10).
           05 WS-RAST PIC X(13).
           05 WS-TIT  PIC X(15).
           05 WS-DESC PIC X(30).
   77  ARE-THERE-MORE-RECORDS PIC XXX VALUE "YES".
   77  NAME-COUNT          PIC 99.
   77  PROCURA             PIC X(13).
   77  ST-ATUALIZACAO      PIC XX  VALUE   SPACES.

   procedure division.
   OPEN INPUT ARQ-ATUALIZACAO
       PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
           READ ARQ-ATUALIZACAO
               AT END
                   MOVE 'NO ' TO ARE-THERE-MORE-RECORDS
               NOT AT END
                   PERFORM 300-STORE-NAME
           END-READ
       END-PERFORM
   CLOSE ARQ-ATUALIZACAO.

   300-STORE-NAME.
   ADD 1 TO NAME-COUNT
   MOVE REG-ATUALIZACAO TO ENTRIES OF WS-RECORD(NAME-COUNT).

   OPEN    I-O ARQ-ATUALIZACAO

       DISPLAY "CODIGO DA ENCOMENDA.:" AT  1010
       DISPLAY "STATUS:"       AT  2433
       DISPLAY ST-ATUALIZACAO   AT  2440
       ACCEPT  PROCURA    AT 1030 WITH REQUIRED FULL
       SEARCH ENTRIES
           AT END DISPLAY "CODIGO NAO ENCONTRADO" AT 0210
           WHEN  WS-RAST(I) = PROCURA
           DISPLAY "REGISTROS ENCONTRADOS" AT 0210
           DISPLAY WS-RAST(I)  AT 0310
           DISPLAY WS-ID(I)    AT 0410
           DISPLAY WS-TIT(I)   AT 0510
           DISPLAY WS-DESC(I)  AT 0610
       END-SEARCH
   CLOSE ARQ-ATUALIZACAO
   EXIT PROGRAM.

Edit - I changed the code a lot so I'll post the new one here:

   IDENTIFICATION DIVISION.
   program-id. ATUALIZACAOR AS "ATUALIZACAO.ATUALIZACAOR".
   environment division.
   configuration section.
   special-names.  DECIMAL-POINT   IS  COMMA.
   INPUT-OUTPUT    SECTION.
   FILE-CONTROL.
       SELECT  ARQ-ATUALIZACAO  ASSIGN  "C:\temp\atualizacao.dat"
       ORGANIZATION    IS  INDEXED
       RECORD  KEY     IS  ID-ATUALIZACAO
       ALTERNATE RECORD KEY IS COD-RASTREIO
       ACCESS  MODE    IS  RANDOM
       FILE    STATUS  IS  ST-ATUALIZACAO.

   data division.
   FILE    SECTION.
   FD  ARQ-ATUALIZACAO.
   01  REG-ATUALIZACAO.
       05  ID-ATUALIZACAO  PIC 9(10).
       05  COD-RASTREIO    PIC X(13).
       05  TITULO          PIC X(15).
       05  DESCRICAO       PIC X(30).
       05  FILLER          PIC X(30).
   working-storage section.
   01  ST-ATUALIZACAO      PIC XX.
       88 end-of-input-file    VALUE   "10".
       88  INPUT-FILE-OK       VALUE ZERO "10".
   77  PROCURA             PIC X(13). 
   77  RESP                PIC X   VALUE   SPACE.

   procedure division.
   INICIO.
       PERFORM WITH    TEST    AFTER   UNTIL   RESP    =   "N"
           DISPLAY "CODIGO DA ENCOMENDA.:" AT  1010 ERASE SCREEN
           DISPLAY "STATUS:"       AT  2433
           DISPLAY ST-ATUALIZACAO   AT  2440
           ACCEPT  PROCURA    AT 1030 WITH REQUIRED FULL
           OPEN I-O ARQ-ATUALIZACAO
           PERFORM                      priming-READ-input-file
               PERFORM
                   UNTIL end-of-input-file
               PERFORM                  process-input
               PERFORM                  READ-input-file
           END-PERFORM
           DISPLAY "DESEJA CONSULTAR OUTRA ATUALIZACAO? (S/N)"   
               AT 2001                                                  
               ACCEPT  RESP        AT  2044    WITH    UPPER
       END-PERFORM
       CLOSE ARQ-ATUALIZACAO
       EXIT PROGRAM
   .

   priming-READ-input-file.
       PERFORM     READ-input-file
       IF end-of-input-file
           DISPLAY "END OF FILE" AT 2510
       END-IF
   .

   READ-input-file.
       READ ARQ-ATUALIZACAO
           IF NOT INPUT-FILE-OK
               DISPLAY "FILE NOT OK" AT 2310
               DISPLAY ST-ATUALIZACAO   AT  2440
               STOP " "
           END-IF
   .

   process-input.
       IF COD-RASTREIO = PROCURA
           DISPLAY ID-ATUALIZACAO AT 2410 
           STOP " "
       END-IF
   .

The sample data that I have in the file 'atualizacao.dat' is:

ID-ATUALIZACAO: 0000000001
COD-RASTREIO: qweqweqweqweqwee
TITULO: test
DESCRICAO: description

ID-ATUALIZACAO: 0000000002
COD-RASTREIO: qweqweqweqweqwee
TITULO: test2
DESCRICAO: description2

Upvotes: 2

Views: 1160

Answers (1)

Bill Woodger
Bill Woodger

Reputation: 13076

Because you have ACCESS RANDOM in your SELECT, the default action for READ file-name (with no NEXT or KEY) is a keyed read.

Change that to ACCESS SEQUENTIAL

Change that to READ file-name NEXT anyway, which is an explicit sequential read.

I always use an explicit NEXT or KEY on a READ, so as not to rely on the default behaviour, which depends on the type of file (and the type of OPEN).

The time I forget to be explicit is when I copy someone else's example without being careful enough, I'm sorry I missed that you did not have the NEXT originally.

Because you are not making use of the OPEN I-O (you are doing no keyed reads or STARTs, so you don't need RANDOM or DYNAMIC for the ACCESS) just use OPEN ... INPUT.

You've not mentioned what the requirement states for the user input. There is perhaps/probably no need for the user-input to be in a loop.

You are not checking the file-status field after your OPEN. You will find you have a problem there. It is bad practice to open the same file multiple times in the same program even when you close the file multiple times (which you're not doing, so there will be an issue there potentially.


OK, first the READ. OK, step back first to the FILE STATUS on the SELECT.

Using the FILE STATUS on a file gets you a two-byte field which tells you what happened to the last IO operation. If that field contains zero, everything was fine.

I'd recommend using the FILE STATUS for all files you may use, and checking the file-status field (keep them unique per file) after each IO on a file.

Using the FILE STATUS for a file tells the COBOL run-time "I'm going to deal with any problems that arise, you tell me when there was a problem by putting a code in this field".

If you use the FILE STATUS and don't check the file-status field, IO errors quietly disappear.

Now back to the READ.

This reads the next available record.

READ file-name

If end-of-file is encountered, the file-status field will be set to "10".

You can define an 88-level condition-name for the file-status field:

01  input-file-status                   PIC XX.
    88  end-of-input-file               VALUE "10".

Your loop can be:

PERFORM
  UNTIL end-of-input-file
    READ input-file
END-PERFORM

Just reading a file isn't much use, you want to process the data as well. A way to make the code more complex, is to test for end-of-input-file after the READ and PERFORM if it is not:

PERFORM
  UNTIL end-of-input-file
    READ input-file
    IF NOT end-of-input-file
        PERFORM process-input
    END-IF
END-PERFORM

Compare that to the same thing with a "priming read", which means you read the first record (if present) before starting the loop:

READ input-file
PERFORM
  UNTIL end-of-input-file
    PERFORM process-input
    READ input-file
END-PERFORM

Each time through the PERFORM, there is either a record available to process, or end-of-file has been identified at the end of the previous PERFORM.

Compare that with something like you had:

PERFORM 
  UNTIL ARE-THERE-MORE-RECORDS = 'NO '
    READ ARQ-ATUALIZACAO
      AT END
         MOVE 'NO ' TO ARE-THERE-MORE-RECORDS
      NOT AT END
         PERFORM 300-STORE-NAME
    END-READ
END-PERFORM        

I said test the file-status field after each IO. That would make things look messy, so how to avoid that? PERFORM:

PERFORM                      READ-input-file
PERFORM
  UNTIL end-of-input-file
    PERFORM                  process-input
    PERFORM                  READ-input-file
END-PERFORM

Then READ-input-file can check the file-status field (with an 88-level) without making the code cluttered.

Further improvement. You have two PERFORMs of the "read", but they are not the same, so name them differently:

PERFORM                      priming-READ-input-file
PERFORM
  UNTIL end-of-input-file
    PERFORM                  process-input
    PERFORM                  READ-input-file
END-PERFORM

Then:

priming-READ-input-file.
    PERFORM                  READ-input-file
    .

Now the code does the same as before, but tells a better story. And can be further improved, without complicating:

priming-READ-input-file.
    PERFORM                  READ-input-file
    IF end-of-input-file
        do something which says "hey, there should always be records,
        a bad thing has happened" and then crash whilst DISPLAYing
        necessary information
    END-IF
    .

You then have a general, simple, program which reads a file in a loop until end-of-file, which you can use as a base any time you need it.

You can easily extend the code along the same lines to deal with a "file header" on a file, and then some changes to deal with a "file trailer", ensure there is only one of each, that the header is first, the trailer is last, the header is for the correct file and the correct business date and the trailer has the correct record-count and hash-totals.

All without disturbing the control logic of the program.

Then you have a second program you can also use as a base.


For your task, you first need to interact with the user, store the user-data, test the data against each record. This may be one piece of user-input, or several, you didn't say.

You only need to store the records from the file if the input from the user depends on results already shown. That may be the case, you didn't say.

If the user supplies one piece of input to match against one field, simply test for that value (already acquired) as you process each record.


Problems with your original program:

FILE STATUS used on SELECT but no checking of the file-status field (ST-ATUALIZACAO).

A second OPEN of the file, which will fail (the file is already OPEN) in 300-STORE-NAME.

A CLOSE of the file in 300-STORE-NAME. Which will work. But now when you do the next READ, your file is closed. So the READ won't work. How won't it work (as in exactly what will it do)? Well, I think, because I don't know, because I don't code that way, that a READ on a closed file with FILE STATUS specified and an AT END will cause the AT END to be processed. Definitely the content of the 01-level under the FD will be undefined.

You are attempting to SEARCH your table each time you add a record to your table. If you do need to store all your records in a table, only do the SEARCHing once you have got to end-of-file and everything is in the table.

Once you have a working program, there is another StackExchange Site, called Code Review, where you can ask how to make working code better.


Make a very simple program which reads the input file in a loop until end of file.

At the start of that program, obtain the user-input. If there is more than one piece of user-input, store it in a table with OCCURS.

For each record that is read, check against the user-data (single field, or table) and produce your output if you get a match.

Have a look at answers here, Cobol Read statement format. Can it be redone a different way?, and follow the link. Pay attention to how to use a priming read, and how to use the file-status field to actually check for errors and to identify the end of a file whilst it is being read sequentially.

Upvotes: 2

Related Questions