Search code examples
cobolcobol85

How do you grab a string in COBOL from a file when the position is unknown?


I'm new to the site as well as COBOL. I am trying to write a program that reads in an 80 byte file, and finds a certain string and grabs another string that is positioned right after that. The only issue I'm having with this is that the starting position of the string is not always in the same byte throughout the file. For example, the string I am trying to find below is the LENGTH(#####) string that appears twice throughout the file:

LENGTH(14909135) FILEID(DD:EDIREC) MSGDATE(130723) MSGDATELONG(20130723)
MSGTIME(091053) MSGSEQO(001390) MSGNAME(00008557) MSGSEQNO(00001)
SESSIONKEY(XXXXXXXX) DELIMITED(E) SYSNAME(XXXXX-XX) SYSLEVEL(XXXX) TIMEZONE(L)
DATATYPE(E) EDITYPE(XXX) SENDERFILE(#####) RECFM(????) RECLEN(#) RECDLM(E)
UNIQUEID(XXXXXXXX) SYSTYPE(##) SYSVER(#);
RECEIVED ACCOUNT(XXXX) USERID(XXXXXXXX) CLASS(#E2) CHARGE(3) LENGTH(14911043)
FILEID(DD:EDIREC) MSGDATE(130723) MSGDATELONG(20130723) MSGTIME(093045)
MSGSEQO(001392) MSGSEQNO(00000) SESSIONKEY(XXXXXXXX) DELIMITED(C)
SYSNAME(XXXXX-XX) SYSLEVEL(XXXX) TIMEZONE(L) DATATYPE(E) EDITYPE(UNFORMATTED)
SENDERFILE(XXXXXXXXXXXXX) RECFM(????) RECLEN(0) RECDLM(C) UNIQUEID(XXXXXXXX)
SYSTYPE(24) SYSVER(5);

Notice the two LENGTH(#####) strings. The below code manages to count the amount of times the length string appears as well as grab the final length string count (what I really want, the numbers within the length string), but only when they are in these two positions:

    WORKING-STORAGE SECTION.

    01 WS-INPUT-RECORD   PIC X(80).

    01 WS-STRINGS.

       05 LENGTH-STRING      PIC X(7) VALUE 'LENGTH('.

    01 WS-COUNTERS.

       05 WS-MSG-COUNT  PIC 9(11).

    01 WS-CHAR-TOTALS.

       05 CHAR-TOTAL  PIC 9(11) VALUE ZEROS.

       05 TMP-TOTAL  PIC X(11) VALUE ZEROS.

    ......

    PROCEDURE DIVISION.

    2200-GET-MSG-TOTAL.

        INSPECT WS-INPUT-RECORD
        TALLYING WS-MSG-COUNT FOR ALL LENGTH-STRING.

    2300-CHAR-TOTAL.

        IF WS-INPUT-RECORD(1:7) = LENGTH-STRING

           MOVE WS-INPUT-RECORD(8:9) TO TMP-TOTAL

           UNSTRING TMP-TOTAL DELIMITED BY ')'
           INTO CHAR-TOTAL

        END-IF

        IF WS-INPUT-RECORD(61:7) = LENGTH-STRING

           MOVE WS-INPUT-RECORD(68:9) TO TMP-TOTAL

           UNSTRING TMP-TOTAL DELIMITED BY ')'
               INTO CHAR-TOTAL

        END-IF

The code works great for the two positions shown in the example input above. But it won't work if LENGTH(####) ends up in any other byte position. Other than coding 80 IF statements to check for every byte in the file for the string, is there an easier way to go about getting those values inside of the length parens? I've checked a lot of other posts and I've thought about using pointers or tables but I can't quite seem to figure it out.


Solution

  • You can use a "perform varying" loop to look at each block of the string within each line, where each block is a string the length of the string you are looking for. Here is an example that works in OpenCobol:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. FIND-STRING.
    
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       SELECT IN-FILE ASSIGN TO 'SAMPLE-LEN.TXT'
           ORGANIZATION IS LINE SEQUENTIAL.
    
       DATA DIVISION.
       FILE SECTION.
       FD  IN-FILE.
       01  IN-RECORD                        PIC X(80).
    
       WORKING-STORAGE SECTION.
       01  END-OF-FILE-SWITCH               PIC XXX VALUE 'NO '.
           88  END-OF-FILE                  VALUE 'YES'.
       01  STRING-MARKER                    PIC X(7) VALUE 'LENGTH('.
       01  STRING-MARKER-LENGTH             PIC 99 VALUE 7.
       01  STRING-SOUGHT                    PIC X(11).
       01  STRING-INDEX                     PIC 99.
       01  RECORD-LENGTH                    PIC 99 VALUE 80.
    
       PROCEDURE DIVISION.
       MAIN.
           OPEN INPUT IN-FILE
           PERFORM UNTIL END-OF-FILE
               READ IN-FILE
                   AT END
                       SET END-OF-FILE TO TRUE
                   NOT AT END
                       PERFORM FIND-STRING
               END-READ
           END-PERFORM
           CLOSE IN-FILE
           STOP RUN
           .
    
       FIND-STRING.
           PERFORM VARYING STRING-INDEX FROM 1 BY 1
               UNTIL STRING-INDEX > (RECORD-LENGTH
                                     - STRING-MARKER-LENGTH)
               IF IN-RECORD(STRING-INDEX:STRING-MARKER-LENGTH) =
                  STRING-MARKER
                  UNSTRING IN-RECORD(STRING-INDEX
                                     + STRING-MARKER-LENGTH : 10)
                      DELIMITED BY ')' INTO STRING-SOUGHT 
                  END-UNSTRING 
                  DISPLAY STRING-SOUGHT END-DISPLAY 
               END-IF 
           END-PERFORM 
           .