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 Chris Miller on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Small cobol run-time errors, please help 2

Status
Not open for further replies.

Guest_imported

New member
Jan 1, 1970
0
i have this small program, and it seems to have runtime errors, can someone please help, THANKS
IDENTIFICATION DIVISION.
PROGRAM-ID. Project-2.
AUTHOR. Nathan.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT ORDER-TRANSACTION-FILE ASSIGN TO
'C:\cobol\PRJ02-01.DAT'
ORGANIZATION IS LINE SEQUENTIAL.
SELECT PRINT-FILE ASSIGN TO 'C:\cobol\output.txt'.
DATA DIVISION.
FILE SECTION.
FD ORDER-TRANSACTION-FILE
RECORD CONTAINS 17 CHARACTERS
DATA RECORD IS ORDER-TRANSACTION-RECORD.
01 ORDER-IN.
05 CUST-NO PIC X(8).
05 FILLER PIC X(1).
05 ORD-QTY PIC XXX.
05 ITEM-NUMBER.
10 ITEM-SERIES PIC X.
10 REST-NUMBERS PIC X(4).

FD PRINT-FILE
RECORD CONTAINS 132 CHARACTERS
DATA RECORD IS PRINT-LINE.
01 PRINT-LINE.
05 FILLER PIC X.
05 PRINT-NO PIC X(8).
05 FILLER PIC X(2).
05 PRINT-ITEM-NO PIC X(5).
05 FILLER PIC X(3).
05 PRINT-QTY PIC 9(3).
05 FILLER PIC X(7).
05 PRINT-DISCOUNT PIC 99.
05 FILLER PIC X(101).

WORKING-STORAGE SECTION.
01 END-OF-DATA-FLAG PIC X(3) VALUE SPACES.
01 HEADING-LINE.
05 FILLER PIC X.
05 CUSTOMER-NO PIC X(8) VALUE 'Customer'.
05 FILLER PIC XX.
05 ITEM PIC X(4) VALUE 'Item'.
05 FILLER PIC X(4).
05 QTY PIC X(3) VALUE 'Qty'.
05 FILLER PIC X(3).
05 DISCOUNT PIC X(8) VALUE 'Discount'.
01 DETAIL-LINE.
05 FILLER PIC XX.
05 NUM PIC X(6) VALUE 'Number'.
05 FILLER PIC XX.
05 NUM2 PIC X(6) VALUE 'Number'.
05 FILLER PIC X.
05 ORDERED PIC X(7) VALUE 'Ordered'.
05 FILLER PIC XX.
05 PERCENT PIC X(7) VALUE 'Percent'.

PROCEDURE DIVISION.
100-PREPARE-PROGRAMMER-REPORT.
OPEN INPUT ORDER-TRANSACTION-FILE
OUTPUT PRINT-FILE.
PERFORM 300-WRITE-HEADER
READ ORDER-TRANSACTION-FILE
AT END MOVE 'YES' TO END-OF-DATA-FLAG
END-READ.
PERFORM 200-PROCESS-CUST-RECORDS
UNTIL END-OF-DATA-FLAG = 'YES'.
CLOSE ORDER-TRANSACTION-FILE
PRINT-FILE.
STOP RUN.

200-PROCESS-CUST-RECORDS.
IF ITEM-SERIES = '1' OR ITEM-SERIES = '2'
IF ORD-QTY <= 100
MOVE '00' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
ELSE
IF ORD-QTY > 100 AND ORD-QTY <= 500
MOVE '10' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
ELSE
IF ORD-QTY > 500 AND ORD-QTY <= 999
MOVE '20' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
END-IF
WRITE PRINT-LINE

ELSE
IF ITEM-SERIES = '3' OR ITEM-SERIES = '4' OR ITEM-SERIES =
'5'
IF ORD-QTY <= 50
MOVE '00' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
ELSE
IF ORD-QTY > 50 AND ORD-QTY <= 100
MOVE '15' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
ELSE
IF ORD-QTY > 100 AND ORD-QTY <= 500
MOVE '20' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
ELSE
IF ORD-QTY > 500 AND ORD-QTY <=999
MOVE '25' TO PRINT-DISCOUNT
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO
END-IF
WRITE PRINT-LINE
END-IF
READ ORDER-TRANSACTION-FILE
AT END MOVE 'YES' TO END-OF-DATA-FLAG
END-READ.
300-WRITE-HEADER.
MOVE HEADING-LINE TO PRINT-LINE
WRITE PRINT-LINE.
MOVE DETAIL-LINE TO PRINT-LINE
WRITE PRINT-LINE.
 
I didn't progam for a while, never used them eather, so I might be wrong, but aren't there some &quot;END-IF&quot;s missing? BigMag, The Netherlands.
someone@euronet.nl (no kidding!)
 
Are they still teaching students to do an initial read? What a waste! And bad style....
Try this:
1. Get rid of the initial read.
2. Put the read in the beginning of paragraph 200-PROCESS-CUST-RECORDS, where it logically belongs.
3. Code the read as

READ ORDER-TRANSACTION-FILE
AT END
MOVE 'YES' TO END-OF-DATA-FLAG
NOT AT END
PERFORM 210-PROCESS-EACH-RECORD
END-READ

4. Put the rest of 200-PROCESS-CUST-RECORDS into 210-PROCESS-EACH-RECORD.

This is MUCH more structured.

Actually, I recommend getting rid of the AT END ... NOT AT END, and replacing them with tests of the FILE STATUS. That will enable you to test for abnormal conditions.

This will not take care of your run-time errors, but it will teach you a better programming style.

Stephen J Spiro
Member, J4 COBOL Standards Committee
check it out at

stephenjspiro@mail.com
 
Nate,

BigMag is right, those if-structures don't look right. I strongly advise using indentation to keep track of which ELSE belongs to which IF; also, if you can use END-IF, which you do, you should terminate every IF with it, not just a few, otherwise the end result gets very shady.
If you can hint at what runtime errors you get, helping to find a solution can become a lot easier.

Regards,
Ronald.
 
Look at your IF - END IF pairings. they may not be matching up and a cause of the problem.
 
Hi Stephen,

I hate to sound pompous, but I think the initial read is superior for the following reasons:

The EOF on 1st read is generally a special condition and is better handled outside the loop.

The test for EOF is better handled in the read pgraph where it doesn't distract the reader from the main purpose of the process loop.

While the end of loop read is diconcerting to some, a short comment at the top of the loop can allay their concerns.

Regards, Jack.
 
Hi Nate,

The general rule for IF stmts w/END-IFs is: that for every IF there must be an END-IF.

I counted 9 IFs and 2 END-IFs.

As a general stmt take a look at the &quot;control break&quot; FAQ. This pgm seems to attempt to solve that problem.

Specifically, that IF construct of yours is formidable. You may want to look at EVALUATE.

In summary, the real solution to your problem lies in the FAQ. It should reduce many of the tests you're doing. Also, take some time to think about the problem, especially in the context of the FAQ.

Regards, Jack.
 
Stephen,

i don't see why the initial read principle is WRONG; i can see that it is DIFFERENT that what you prefer personally. I too was trained to use a structuring technique which centered around the initial read followed by iterated process and read next. Programs that are well written using this technique are just as structured.
As to the file status thing: sure you can, but many exeptions are caught by the operating system; in the program logic, only the at-end situation is relevant.
On top of that i personally find &quot;AT END ...&quot; much more self-explanatory then &quot;IF WS-FILE-STAT = 10&quot; or any similar construction.

Just my two cents,
Ronald.
 
Whenever possible I always avoid nested IF's. I think it makes more sense to say:

if condition perform Discount-Rate-10.

Or set the rates in fields in working storage so you dont use literals. That way if the rate changes you dont have to look for the if statement. Example: discount-rate-1

move discount-rate-1 to discount-rate

That way when you look at a program 1 year later you know what the if statement is testing for. There is nothing wrong with using nested if's, but after a while they are hard to understand what exactly you were doing when you go back and look at it later.

For some reason I never use END-IF in a program. A period ends a statement. It is probably just a matter of personal taste. I stay away from nested if statements like the black plague.

You also keep repeating the same moves dont you? Isn't structured programming suppose to eliminate repeating the same code over and over in a program? If every single time you are going to move 3 things do that after all of the if statements.
MOVE CUST-NO TO PRINT-NO
MOVE ORD-QTY TO PRINT-QTY
MOVE ITEM-NUMBER TO PRINT-ITEM-NO

That way all of the if statements are grouped closer together. This makes them easier to find. It makes for less code also.

Even if you don't like my avoiding nested if's and my preference for not using END-IF, you did use the Same Move statements over and over.

Who am I to talk, I always use one read and use a GO TO to handle that part. If you read 7 different files for every record you write it works better that way.


If you do not like my post feel free to point out your opinion or my errors.
 
I can't resist a chance to put in my own two cents.

Prime READ:
The prime READ is different from the other READ because of the different AT END treatment. I am a full time COBOL programmer and a part time COBOL instructor and I always code and teach it this way.

AT END / NOT AT END vs file status check:
I like the status check, because it has the flexibility of checking for everything that could go wrong. I use 88's on all the file status conditions, enabling me to be self-documenting for those who don't have them all memorized.

Periods vs. END-IF:
Not so much a personal choice as a hold-over from COBOL 74 vs. COBOL 85. END-IF's didn't exist in COBOL 74 and we were stuck with only the period.

END-IF:
Code them all. That way the compiler will be able to let you know when you've included an extraneous period where it doesn't belong. Otherwise you'll have to figure it out at run time, much harder to do.

Betty Scherber
Brainbench MVP for COBOL II
 
quote: Are they still teaching students to do an initial read? What a waste! And bad style....
end-quote......

I am surprised! It is completely the other way around.

The initial read is very import in all kinds of structured designs.....

JSP, VSP, you name it and it is used!


s-) s-) s-) s-) s-) s-) s-) s-) s-) s-) s-) s-)
 
ha, you guys are the best. Of all the other forums I am registered to, only this one develops (consistently) into some pseudo-philosophical discussion about the rights and wrongs of a language. I keep expecting one of you to call the other &quot;GrassHopper&quot;.

Why are Cobol programmers ALWAYS like this? even I am but just hate to admit it.

Keep it up.
 
Instead of nested if statements you could do something like this:

PROCEDURE DIVISION.
100-PREPARE-PROGRAMMER-REPORT.
OPEN INPUT ORDER-TRANSACTION-FILE
OUTPUT PRINT-FILE.
PERFORM 300-WRITE-HEADER
READ ORDER-TRANSACTION-FILE
AT END MOVE 'YES' TO END-OF-DATA-FLAG
END-READ.
PERFORM 200-PROCESS-CUST-RECORDS
UNTIL END-OF-DATA-FLAG = 'YES'.
CLOSE ORDER-TRANSACTION-FILE
PRINT-FILE.
STOP RUN.

200-PROCESS-CUST-RECORDS.
EVALUATE ITEM-SERIES
WHEN 1
PERFORM DISC-RATE-TEST-1
WHEN 2
PERFORM DISC-RATE-TEST-1
WHEN 3
PERFORM DISC-RATE-TEST-2
WHEN 4
PERFORM DISC-RATE-TEST-2
WHEN 5
PERFORM DISC-RATE-TEST-2
END-EVALUATE
MOVE CUST-NO TO PRINT-NO.
MOVE ORD-QTY TO PRINT-QTY.
MOVE ITEM-NUMBER TO PRINT-ITEM-NO.
WRITE PRINT-LINE.

DISC-RATE-TEST-1.
IF ORD-QTY <= 100
MOVE '00' TO PRINT-DISCOUNT
ELSE
IF ORD-QTY > 100 AND ORD-QTY <= 500
MOVE '10' TO PRINT-DISCOUNT
ELSE
IF ORD-QTY > 500 AND ORD-QTY <= 999
MOVE '20' TO PRINT-DISCOUNT
END-IF



DISC-RATE-TEST-2.
IF ORD-QTY <= 50
MOVE '00' TO PRINT-DISCOUNT
ELSE
IF ORD-QTY > 50 AND ORD-QTY <= 100
MOVE '15' TO PRINT-DISCOUNT
ELSE
IF ORD-QTY > 100 AND ORD-QTY <= 500
MOVE '20' TO PRINT-DISCOUNT
ELSE
IF ORD-QTY > 500 AND ORD-QTY <=999
MOVE '25' TO PRINT-DISCOUNT
END-IF

This is another approach to your problem but it presents a problem. With the END-IF there is no period to end the paragraph. Normally I would prefer an &quot;IF, ELSE IF, ELSE&quot; structure. The compiler might complain. You could put an &quot;EXIT.&quot; command by itself.

I was board so I was looking at this.

If you do not like my post feel free to point out your opinion or my errors.
 
DATA RECORD IS ORDER-TRANSACTION-RECORD.
01 ORDER-IN.

Hi. I noticed a simple item in the beginning of your program that might account for errors. (By the way, could
your share your errors with us and tell us which COBOL you
are using.. that generated those errors).

You programmed the above... &quot;data record is&quot; clause (which I never use, by the way), and it wants to use the order-transaction-record for it data. Your &quot;01&quot; is Order-in. Your data record clause should read &quot;data record is order-in&quot;.

Good Luck,

Steve Millman
 
Here's my 2 cents here.

When you do a read, as you read each record, you process it. Then go to the next record and process it. And so forth, until End-Of-File.

Whenever you use &quot;IF...ELSE&quot; statements, be sure to include an &quot;END-IF.&quot; I know that older versions of COBOL didn't allow the END-IF, but now most compilers will do so.

Make sure your &quot;IF,s&quot;, &quot;ELSE's&quot; and &quot;END-IF's&quot; line up with each other. Otherwise you might wind up with the wrong &quot;IF&quot;, the wrong &quot;ELSE&quot;, and/or the wrong &quot;END-IF&quot; paired with each other -- and then your program might do wondrous things that have nothing to do with what you want it to do.

Also, always check for status each time you open, read, or close a file. I am assuming for the following that you have a ERROR-ROUTINE paragraph at the end which will stop the program after processing the error; also that you have a Working Storage field which gives an error message.

Also, I've replaced the nested IF...ELSE..END-IF's with nested EVALUATE statements. And before the EVALUATE'S, I check for bizarre sorts of entries such as if the order quantity is less than or equal to zero. When you do testing, you never know what will come up.

And there are certain actions you take regardless of what happens in all of the EVALUATE's. So these are placed after the nested EVALUATE's.

Also, something must be done if the ORD-QTY is greater than 999. Every condition must be covered.

I would write it like this:

100-PREPARE-PROGRAMMER-REPORT.

OPEN INPUT ORDER-TRANSACTION-FILE.
IF RETURN-CODE > 0
MOVE 'ERROR AT OPENING' TO ERROR-MSG
GO TO ERROR-ROUTINE
END-IF.
OPEN OUTPUT PRINT-FILE.
IF RETURN-CODE > 0
MOVE 'ERROR AT OPENING' TO ERROR-MSG
GO TO ERROR-ROUTINE
END-IF.

PERFORM 300-WRITE-HEADER
READ ORDER-TRANSACTION-FILE
AT END MOVE 'YES' TO END-OF-DATA-FLAG
NOT AT END
IF RETURN-CODE > 0
MOVE 'ERROR AT READ' TO ERROR-MSG
GO TO ERROR-ROUTINE
<<which will have a STOP RUN
and will end everything with an abend.>>
ELSE
PERFORM 200-PROCESS-CUST-RECORDS
UNTIL END-OF-DATA-FLAG = 'YES'
END-IF
END-READ.

200-PROCESS-CUST-RECORDS.

IF ORD-QTY <= 00
MOVE 'ERROR: QTY LESS THAN OR EQUAL TO ZERO'
TO ERROR-MSG
GO TO ERROR-ROUTINE
END-IF.

EVALUATE TRUE
WHEN (ITEM-SERIES = '1' OR ITEM SERIES = '2')
EVALUATE TRUE
WHEN (ORD-QTY > 0 AND ORD-QTY <= 100)
MOVE '00' TO PRINT-DISCOUNT
WHEN (ORD-QTY > 100 AND AND ORD-QTY <= 500)
MOVE '10' TO PRINT-DISCOUNT
WHEN (ORD-QTY > 500 AND ORD-QTY <= 999)
MOVE '20' TO PRINT-DISCOUNT
WHEN OTHER
MOVE '30' TO PRINT-DISCOUNT
<<or whatever you do if the number is greater
than 1000>>
END-EVALUATE
WHEN (ITEM-SERIES = '3' OR ITEM-SERIES = '4'
OR ITEM-SERIES = '5')
EVALUATE TRUE
WHEN ORD-QTY <=50
MOVE '00' TO PRINT-DISCOUNT
WHEN (ORD-QTY > 50 AND ORD-QTY <= 100)
MOVE '15' TO PRINT-DISCOUNT
WHEN (ORD-QTY > 100 AND ORD-QTY <= 500)
MOVE '20' TO PRINT-DISCOUNT
WHEN (ORD-QTY > 500 AND ORD-QTY <=999)
MOVE '25' TO PRINT-DISCOUNT
WHEN ORD-QTY > 999
MOVE '30' TO PRINT-DISCOUNT
<<or whatever you do if the number is greater
than 999>>
END-EVALUATE
END-EVALUATE.
<<The following, you do no matter what>>
MOVE CUST-NO TO PRINT-NO.
MOVE ORD-QTY TO PRINT-QTY.
MOVE ITEM-NUMBER TO PRINT-ITEM-NO.
MOVE DETAIL-LINE TO PRINT-LINE.
WRITE PRINT-LINE.

300-WRITE-HEADER.
MOVE HEADING-LINE TO PRINT-LINE.
WRITE PRINT-LINE.

Hope this helps. Nina Too

 
Prime READ:
The prime READ is different from the other READ because of the different AT END treatment. I am a full time COBOL programmer and a part time COBOL instructor and I always code and teach it this way.

Question: In COBOL/CICS programming of VSAM files, there is an initial read which is a read-only function. The file is not locked for updating.

Then, if the programmer wants to provide for updating a VSAM file, a CICS READ UPDATE is coded. This locks the VSAM file so that no one else can do anything with it (update or delete) while the current user is updating/deleting. If it turns out that the update/delete does not take place, then a CICS UNLOCK command is issued to release the file to another user.

Is there something like this with an initial read in a batch program? Is the initial read a read-only command, and then the read (with the different AT END treatment) is a read which locks the file for update/delete?

Nina Too
 
Hi Nina,

Nope, a RYO serialization technique can be used, but participation is solely voluntary. SHAREOPTIONS can also be used at the file level.
Also, you may have misspoken, but the VSAM file isn't &quot;locked&quot; in a CICS environment, only the CI. The CI, of course, may contain many records.

Regards, Jack.
 
Jack,
Regarding VSAM files being &quot;locked&quot; during CICS READ UPDATE actions, my project leader was the one who explained this to me as I was working on a VSAM project.

I'm not sure if it's the actual file which gets locked or the CI. But the result is that other users can't get into the file to update/delete as long as the &quot;lock&quot; is on.

When the user whose program is running gets to the point of issuing the update/delete command, the file is automatically released. But if the update/delete doesn' take place (because the data turns out not to need a change, or else because of abend), then a CICS UNLOCK command must be issued to release the file for others.

Okay, now another question: what would be the purpose of an initial read in a batch program? The vast majority of programs I've written/maintained have been CICS.

In the few batch programs I've written/maintained, I've never done anything such as an initial read. Instead, I've done a READ <filename> with the AT END and NOT AT END parameters -- and then, as each record gets read, it gets processed.

Nina Too
 
Nate,

I would appreciate if you could tell us if any of the ideas presented to you are working for you.

Steve Millman
SteveM001@cs.com
 
Hi Nina,

When the CI is locked during a read for update, only those recs in the CI are unavailable until the rewrite/lock for the rec is issued. All other recs in the file are available to other tasks.

Read for update is a CICS function, along w/readprev and others, which are not available to a batch pgm.

Jack
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top