Page 2 of 2

Re: Error with the IF clause

PostPosted: Fri Jun 27, 2014 5:22 pm
by Aki88
Hello,

what is the normal way then ? am aware of only this way of working.


In that case, you'll have to read manuals, understand the various syntax for the keywords, understand their usage, and learn to apply them logically to build a program.
Here is a hint at what is happening in the below piece you've given:
You read a file sequentially, if end is reached then you've moved the flag 'Y' to WS-CFILE1-EOF-SW1, but at this point your program still doesn't know what to do with this info; if the end-of-file is reached then should it continue reading, or send the control somewhere else or do something else??

A simple google of the error, or file status 46 returned this link, which states:

46: Logic error condition
A sequential READ, READ NEXT or READ PRIOR statement was attempted on a file open in the input or I-O mode and no valid next record had been established because the preceding START statement was unsuccessful, or the preceding READ statement was unsuccessful or caused an at end condition.


You need to understand the usage of various functions before putting them together in a program; optimize the design logic by understanding the algorthm's flow; that should give you a clean program.

For a beginner, best place to look at is a manual and Google (for any queries).

Re: Error with the IF clause

PostPosted: Fri Jun 27, 2014 6:58 pm
by SS00127783
Thanks akki.... i'll work out on manuals and google..and get back with a better code :-)

Re: Error with the IF clause

PostPosted: Fri Jun 27, 2014 7:06 pm
by Robert Sample
As you code more programs, you will develop your own style. A typical overview of the PROCEDURE DIVISION:
PROCEDURE DIVISION.
START-UP.
    PERFORM INITIALIZATION.
    PERFORM READ-INPUT.
    PERFORM PROCESS-DATA
        UNTIL END-OF-INPUT
    END-PERFORM.
    PERFORM POST-PROCESS.
For what you are wanting to do, you need to find out about the SEARCH statement and use it -- SEARCH ALL would be better but even SEARCH will do what you want. You also should IMMEDIATELY find out about file status variables.

Your code should be something like (warning -- this code has NOT been tested on a z/OS system):
 DATA DIVISION.
 FILE SECTION.

 FD  INPUT-FILE.
 01  INPUT-RECD.
      05 BAID-NAME PIC X(04).
           88  BVALUE VALUE "BAID".
      05  FILLER PIC X(02).
      05  BAID-NUMBER PIC X(12).
      05  FILLER PIC X(42).
      05  ORDER-NUMBER PIC X(08).
      05  FILLER PIC X(12).

 FD  TABLE-FILE.
 01  TF-TABLE-REC.
       02  TF-ORDERN PIC X(8).
       02  FILLER PIC X(72).

 FD  OUTPUT-FILE.
 01  OF-OUTPUT-REC.
       02  BAID PIC X(12).
       02  FILLER PIC X(5).
       02  ORDERNUMBER PIC X(8).
       02  FILLER PIC X(55).

 WORKING-STORAGE SECTION.
 01  WS-CFILE1-EOF-SW1 PIC X(01) VALUE 'N'.
       88  WS-CFILE1-EOF1 VALUE 'Y'.
 01  WS-END-OF-FILE-SW PIC X(01) VALUE 'N'.
      88  WS-END-OF-FILE VALUE 'Y'.

 01  WS-ORDERN-TABLE.
       05  WS-OT-ENTRIES          OCCURS 99
                                             INDEXED BY OT-INDEX
                                             PIC X(08).

****************************************************************

 PROCEDURE DIVISION.
 1000-MAIN-PARA.
 PERFORM INIT.
 PERFORM RINPTF THRU INNERF
      UNTIL WS-CFILE1-EOF1.
 PERFORM POST-PROC.
 STOP RUN.

 INIT.
 OPEN INPUT INPUT-FILE
                   TABLE-FILE
        OUTPUT OUTPUT-FILE.
 MOVE HIGH-VALUES TO  WS-ORDERN-TABLE.
 SET OT-INDEX TO 1.
 READ TABLE-FILE
     AT END DISPLAY ''NO TABLE RECORDS '
            CLOSE INPUT-FILE OUTPUT-FILE TABLE-FILE
            EXIT-PROGRAM
 END-READ.

 PERFORM
     UNTIL WS-END-OF-FILE
          OR TF-INDEX > 99
     MOVE TF-ORDERN TO WS-OT-ENTRIES (TF-INDEX)
     SET TF-INDEX UP BY 1
     READ TABLE-FILE
         AT END SET WS-END-OF-FILE TO TRUE
     END-READ
 END-PERFORM.
 IF TF-INDEX > 99
     DISPLAY 'TABLE LIMIT REACHED'
     CLOSE INPUT-FILE
               TABLE-FILE
               OUTPUT-FILE
     EXIT PROGRAM
 END-IF.

 POST-PROC.
 CLOSE INPUT-FILE
       TABLE-FILE
       OUTPUT-FILE.

 RINPTF.
 READ INPUT-FILE
 AT END MOVE 'Y' TO WS-CFILE1-EOF-SW1.

 INNERF.
 IF  BVALUE
      SET TF-INDEX TO 1
      SEARCH WS-OT-ENTRIES
         AT END DISPLAY 'ORDER NUMBER ' ORDER-NUMBER ' NOT FOUND'
         WHEN WS-OT-ENTRIES (TF-INDEX) = ORDER-NUMBER
            MOVE BAID-NUMBER TO BAID
            MOVE ORDER-NUMBER TO ORDERNUMBER
            WRITE WS-OUTPUT-REC
     END-SEARCH
 END-IF.
Note that your code needs to be re-thought so it will handle the last record correctly. Once you hit the end of file, you do NOT want to process as if it were a good record; this is why I read the first record of the table file and then process that record, reading at the end of the loop.

Re: Error with the IF clause

PostPosted: Fri Jun 27, 2014 11:09 pm
by NicC
Please use the code tags to present your code. I have coded your posts for you - note how the indentation is preserved. Search the forum for how to use the code tags.

In addition to what Terry wrote, below, you can click on the 'Quote' button on a post that has coded text and study the code tags there. Note that in Terry's post they are nested between Quote tags.

Re: Error with the IF clause

PostPosted: Fri Jun 27, 2014 11:30 pm
by Terry Heinze
Hint: See FAQ and use the POSTREPLY button instead of the Quick Reply.
This message is between the code tags.