Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations TouchToneTommy on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

why my prog enter loop?

Status
Not open for further replies.

HUJ

Programmer
Dec 18, 2003
20
CN
when i read variable length records QSA file, if i add the line "RECORD CONTAINS 0 CHARACTERS" in the prog, this prog will enter loop status. if i comment it, i get my result.
why?

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. READVQ1.
000300 AUTHOR. HCQ.
000400
000500 ENVIRONMENT DIVISION.
000600 CONFIGURATION SECTION.
000700 SPECIAL-NAMES.
000800 CONSOLE IS CNSL.
000900 INPUT-OUTPUT SECTION.
001000 FILE-CONTROL.
001100 SELECT VQFILE ASSIGN TO VQF1
001200 FILE STATUS IS F-STA
001300 ORGANIZATION IS SEQUENTIAL
001400 ACCESS MODE IS SEQUENTIAL.
001500
001600 DATA DIVISION.
001700 FILE SECTION.
001800 FD VQFILE
001900 LABEL RECORDS ARE STANDARD
002000* RECORD CONTAINS 0 CHARACTERS
002100 RECORD IS VARYING IN SIZE
002200 FROM 1
002201 DEPENDING ON VQF-LEN
002202 RECORDING MODE IS V.
002203 01 VQF-REC.
002400 05 VQF-DATA PIC X(80).
003400 WORKING-STORAGE SECTION.
003410 77 VQF-LEN PIC 9(8) BINARY.
003500 77 F-STA PIC X(2).
003700 01 E-O-F PIC X.
003800 88 EOF-N VALUE 'N'.
003900 88 EOF-Y VALUE 'Y'.
004000*01 VQF-REC-DISP.
004100* 05 REC-LEN PIC 9(2).
004200* 05 FILLER PIC X.
004300* 05 REC-DATA PIC X(78).
004400* 05 FILLER PIC X VALUE ';'.
004500
006200 PROCEDURE DIVISION.
006300 MAIN-ROUTINE.
006400 PERFORM 1000-OPEN-FILE THRU 1000-EXIT.
006500 PERFORM 2000-PROCESS THRU 2000-EXIT.
006600 PERFORM 3000-CLOSE-FILE THRU 3000-EXIT.
006700 STOP RUN.
006800
006900 1000-OPEN-FILE.
007000 OPEN INPUT VQFILE.
007100 1000-EXIT.
007200 EXIT.
007300
007400 2000-PROCESS.
007500 READ VQFILE AT END SET EOF-Y TO TRUE
007600 DISPLAY 'VQFILE: END OF FILE' UPON CNSL.
007700 PERFORM 2100-READ-FILE THRU 2100-EXIT UNTIL EOF-Y.
007800 2000-EXIT.
007900 EXIT.
008000
008100
008200 2100-READ-FILE.
008400 DISPLAY VQF-LEN ' ' VQF-DATA UPON CNSL.
009800 READ VQFILE AT END SET EOF-Y TO TRUE
009900 DISPLAY 'VQFILE: END OF FILE' UPON CNSL.
010000 2100-EXIT.
010100 EXIT.
010200
010300 3000-CLOSE-FILE.
010400 CLOSE VQFILE.
010500 3000-EXIT.
010600 EXIT.


this is my jcl.

//IGYWCL JOB 123,HCQ,CLASS=A,MSGCLASS=A,MSGLEVEL=(1,1)
//COBPROC JCLLIB ORDER=(COBOL.V2R1M0.SIGYPROC)
//STEP1 EXEC IGYWCLG
//COBOL.SYSIN DD DSN=DSZDV2.SAMPLE.SRC(READVQ1),DISP=SHR
//GO.VQF1 DD DSN=DSZDV2.SAMPLE.VFILE,DISP=SHR,
//

 
You are only checking the file status for end of file. An error is occurring and the file status is being set, but you are not picking it up.

Add a further line after the read to check the file status for not being equal to 0, and display it if it isn't (incorporate the end of file porcessing in this logic).

Marc
 
PERFORM 2100-READ-FILE THRU 2100-EXIT UNTIL EOF-Y
OR F-STA IN NOT = " "
That's better. And check the File-Status also after the OPEN and CLOSE Command
 
Perix -

Don't you mean
Code:
  OR F-STA NOT = "00"

Also, since FILE-STATUS will be set to "10" at end of file, the EOF-Y switch check is unnecessary.

As an aside, I find 88-levels very useful with file status - it means you can write code like:
Code:
PERFORM xxxxx
    UNTIL NOT IO-SUCCESSFUL

IF KEY-NOT-FOUND . . .
where IO-SUCCESSFUL is an 88-level with VALUE "00" and KEY-NOT-FOUND has VALUE "23".

Regards.

Glenn
 
Adding the RECORD CONTAINS 0 CHARACTERS to the variable file is obviously causing the error. I think it's probably best to put some form of helpful error diagnostic processing into the program so that it puts out a meaningful message when it hit's the file status that it is not expecting.

Marc
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top