Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
On 23 Apr 2012 12:36:08 -0700, in bit.listserv.ibm-main you wrote: >Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" >message IGYOP3094-W in the do-nothing program listed below? It is bad COBOL because there is a GO TO PARA-EXIT in SUB-PARA-1 which in this case means that if WS-SUB is less than 6 "MOVE WS-SUB TO RETURN-CODE is not done. If there is a separate EXIT paragraph it should only be reached from the paragraph associated with it in the PERFORM, in this case PARA-1. For the best optimization eliminate all PERFORM ... THRU statements and I have gone the route of having GOBACK / STOP RUN only in the main line first paragraph and no GO TO statements in the program. Technically there can not be a loop but given the way PERFORM is implemented in some cases the results might not be what you would expect if SUB=PARA-1 were reached by something other than a PERFORM. Clark Morris > >TIA for curing my ignorance. > >Peter > >PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date >04/23/2012 Time 15 > LineID PL SL > +-*A-1-B--+2+3+4+5+6+7-|--+8 > 01 * PROPRIETARY COMMENT ON LINE 1 REMOVED FOR PRIVACY > > 02ID DIVISION. > > 03PROGRAM-ID. TESTGOTO. > > 04ENVIRONMENT DIVISION. > > 05DATA DIVISION. > > 06WORKING-STORAGE SECTION. > > 0701 WS-WORK-AREA. > > 0805 WS-SUBPIC S9(4) USAGE IS > BINARY. > 09 > > 10LINKAGE SECTION. > > 1101 PARM-AREA. > > 1205 PARM-LEN PIC S9(4) BINARY. > > 1305 PARM-DATA. > > 1410 PARM-CC PIC 9(02). > > 1510 PARM-YY PIC 9(02). > > 1610 PARM-MM PIC 9(02). > > 1710 PARM-DD PIC 9(02). > > 18 > >PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date >04/23/2012 Time 15 > LineID PL SL > +-*A-1-B--+2+3+4+5+6+7-|--+8 > 20PROCEDURE DIVISION USING PARM-AREA. > > 21 *LINES 22-30 PROPRIETARY COPY CODE REMOVED FOR > PRIVACY > 31 > > 32MOVE PARM-DD TO WS-SUB. > > 33PERFORM PARA-1 THRU PARA-EXIT. > > 34GO TO RETURN-TO-CALLER. > > 35 > > 36PARA-1. > > 37IF PARM-MM > 06 > > 38 1 MOVE +2 TO WS-SUB. > > 39PERFORM SUB-PARA-2. > > 40PERFORM SUB-PARA-1. > > > >==40==> IGYOP3094-W There may be a loop from the "PERFORM" statement at >"PERFORM (line >40.01)" to itself. "PERFORM" statement optimization > was not attempted. > > > 41MOVE WS-SUB TO RETURN-CODE. > > 42GO TO PARA-EXIT.
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
I agree it is ugly code. Not my invention, I'm just the maintainer, so I get to fix it. I have to restructure the whole program anyway to add some major new functionality, so this will just be part of the job. Peter -Original Message- From: IBM Mainframe Discussion List [mailto:IBM-MAIN@bama.ua.edu] On Behalf Of Gibney, Dave Sent: Monday, April 23, 2012 4:01 PM To: IBM-MAIN@bama.ua.edu Subject: Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop? Dropping through into PARA-2 from PARA-1 when the return from the PERFORM PARA-2 is still set would result in a loop. Ugly code IMO. -- This message and any attachments are intended only for the use of the addressee and may contain information that is privileged and confidential. If the reader of the message is not the intended recipient or an authorized representative of the intended recipient, you are hereby notified that any dissemination of this communication is strictly prohibited. If you have received this communication in error, please notify us immediately by e-mail and delete the message and any attachments from your system. -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
Thanks for the suggestion, but moving the two SUB-PARA's out of the PARA-1 to PARA-EXIT scope didn't remove the warning. I *think* what is happening is that COBOL does not like branches to PARA-EXIT from any paragraph that PARA-1 itself performs, regardless of where they are placed. The only option that seems to work is to hoist the GO TO PARA-EXIT statement out of PERFORMed SUB-PARA's back into the mainline PARA-1 code. I had hoped to avoid those kind of changes (since there are a lot of them in the real code), but I guess I don't have a choice. Thanks again for your help. Peter -Original Message- From: IBM Mainframe Discussion List [mailto:IBM-MAIN@bama.ua.edu] On Behalf Of Arthur T. Sent: Monday, April 23, 2012 4:45 PM To: IBM-MAIN@bama.ua.edu Subject: Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop? On 23 Apr 2012 12:36:08 -0700, in bit.listserv.ibm-main (Message-ID:<985915eee6984740ae93f8495c624c6c21e1d43...@jscpcwexmaa1.bsg.ad.adp.com>) peter.far...@broadridge.com (Farley, Peter x23353) wrote: It's been a *long* time since I coded Cobol, but I suspect the compiler is right. SUB-PARA-1 is part of the PERFORM in line 33. Thus, as far as the compiler can tell, you're performing yourself from within the perform, which could easily lead to an endless recursion. Try moving both SUB-PARAs out of PARA-1 and give each their own EXIT. If you want that extra execution of -2, code it as another PERFORM. -- This message and any attachments are intended only for the use of the addressee and may contain information that is privileged and confidential. If the reader of the message is not the intended recipient or an authorized representative of the intended recipient, you are hereby notified that any dissemination of this communication is strictly prohibited. If you have received this communication in error, please notify us immediately by e-mail and delete the message and any attachments from your system. -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
Performing a paragraph does not require an "exit" point, one is generated automatically. Same holds true if you perform a SECTION. However, your perform is branching to an EXIT statement which, in effect, is trying to "short-circuit" the PARA-1 when ws-sub is less than 6. I would suggest taking out the GO TO in PARA-1 and simply let the IF move 0 to ws-sub while ws-sub is less than 6. Because your perform if para-1 is a perform and not a perform ... thru , an exit point will be generated for para-1 just prior to para-2. Using a branch to an EXIT statement is a common way of perform para-a thru para-b and para-b is an EXIT statement. Then, anywhere in the code that falls between para-a and para-b, you can branch to para-b and "get out" of the current perform, return to the point of the perform and then, the generated logic will determine if it need to "go again" or not. Performing a paragraph which has the SECTION clause on it provides a similar construct (thought not the exact same) as a perform para-a thru para-b. When one codes in sections it is not uncommon to find the last paragraph in the section is a paragraph with nothing more than an EXIT statement. Hope this helps. Chuck Charles (Chuck) Hardee Senior Systems Engineer Database Administration Information Technology Services Thermo Fisher Scientific chuck.har...@thermofisher.com -Original Message- From: IBM Mainframe Discussion List [mailto:IBM-MAIN@bama.ua.edu] On Behalf Of Farley, Peter x23353 Sent: Monday, April 23, 2012 3:33 PM To: IBM-MAIN@bama.ua.edu Subject: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop? Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" message IGYOP3094-W in the do-nothing program listed below? TIA for curing my ignorance. Peter PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date 04/23/2012 Time 15 LineID PL SL +-*A-1-B--+2+3+4+5+6+7-|--+8 01 * PROPRIETARY COMMENT ON LINE 1 REMOVED FOR PRIVACY 02ID DIVISION. 03PROGRAM-ID. TESTGOTO. 04ENVIRONMENT DIVISION. 05DATA DIVISION. 06WORKING-STORAGE SECTION. 0701 WS-WORK-AREA. 0805 WS-SUBPIC S9(4) USAGE IS BINARY. 09 10LINKAGE SECTION. 1101 PARM-AREA. 1205 PARM-LEN PIC S9(4) BINARY. 1305 PARM-DATA. 1410 PARM-CC PIC 9(02). 1510 PARM-YY PIC 9(02). 1610 PARM-MM PIC 9(02). 1710 PARM-DD PIC 9(02). 18 PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date 04/23/2012 Time 15 LineID PL SL +-*A-1-B--+2+3+4+5+6+7-|--+8 20PROCEDURE DIVISION USING PARM-AREA. 21 *LINES 22-30 PROPRIETARY COPY CODE REMOVED FOR PRIVACY 31 32MOVE PARM-DD TO WS-SUB. 33PERFORM PARA-1 THRU PARA-EXIT. 34GO TO RETURN-TO-CALLER. 35 36PARA-1. 37IF PARM-MM > 06
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
On 23 Apr 2012 12:36:08 -0700, in bit.listserv.ibm-main (Message-ID:<985915eee6984740ae93f8495c624c6c21e1d43...@jscpcwexmaa1.bsg.ad.adp.com>) peter.far...@broadridge.com (Farley, Peter x23353) wrote: 33PERFORM PARA-1 THRU PARA-EXIT. 34GO TO RETURN-TO-CALLER. 35 36PARA-1. 37IF PARM-MM > 06 38 1 MOVE +2 TO WS-SUB. 39PERFORM SUB-PARA-2. 40PERFORM SUB-PARA-1. ==40==> IGYOP3094-W There may be a loop from the "PERFORM" statement at "PERFORM (line 40.01)" to itself. "PERFORM" statement optimization was not attempted. 41MOVE WS-SUB TO RETURN-CODE. 42GO TO PARA-EXIT. 43 44SUB-PARA-1. 45IF WS-SUB < 6 46 1MOVE 0 TO WS-SUB 47 1GO TO PARA-EXIT. 48 49SUB-PARA-2. 50DISPLAY WS-SUB. 51 52PARA-EXIT. 53EXIT. It's been a *long* time since I coded Cobol, but I suspect the compiler is right. SUB-PARA-1 is part of the PERFORM in line 33. Thus, as far as the compiler can tell, you're performing yourself from within the perform, which could easily lead to an endless recursion. Try moving both SUB-PARAs out of PARA-1 and give each their own EXIT. If you want that extra execution of -2, code it as another PERFORM. -- I cannot receive mail at the address this was sent from. To reply directly, send to ar23hur "at" pobox "dot" com -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
Thanks for that suggestion. I tried moving SUB-PARA-2 in front of SUB-PARA-1, but the result was the same. Tom Ross, if you're lurking and available, can you explain why I get this warning, or better what I can do to prevent it? I was able to eliminate the message with the following change (hoisting the GO TO in SUB-PARA-1 back into PARA-1): MOVE PARM-DD TO WS-SUB. PERFORM PARA-1 THRU PARA-EXIT. GO TO RETURN-TO-CALLER. PARA-1. IF PARM-MM > 06 MOVE +2 TO WS-SUB. PERFORM SUB-PARA-2. PERFORM SUB-PARA-1. IF WS-SUB = 0 GO TO PARA-EXIT END-IF. MOVE WS-SUB TO RETURN-CODE. GO TO PARA-EXIT. SUB-PARA-2. DISPLAY WS-SUB. SUB-PARA-1. IF WS-SUB < 6 MOVE 0 TO WS-SUB END-IF. PARA-EXIT. EXIT. RETURN-TO-CALLER. GOBACK. In the real code from which this code structure is extracted and simplified, there are over 60 occurrences of PERFORM SUB-PARA-1, so it's going to be quite tedious to change them all in this manner. Peter -Original Message- From: IBM Mainframe Discussion List [mailto:IBM-MAIN@bama.ua.edu] On Behalf Of Bob Shannon Sent: Monday, April 23, 2012 3:46 PM To: IBM-MAIN@bama.ua.edu Subject: Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop? > Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" > message IGYOP3094-W >in the do-nothing program listed below? I haven't written in COBOL in over 30 years, but I suspect it's because SUB-PARA-2 sits in between SUB-PARA-1 and PARA-EXIT. 44SUB-PARA-1. 45IF WS-SUB < 6 46 1MOVE 0 TO WS-SUB 47 1GO TO PARA-EXIT. 48 49SUB-PARA-2. 50DISPLAY WS-SUB. 51 52PARA-EXIT. 53EXIT. Bob Shannon Rocket -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN This message and any attachments are intended only for the use of the addressee and may contain information that is privileged and confidential. If the reader of the message is not the intended recipient or an authorized representative of the intended recipient, you are hereby notified that any dissemination of this communication is strictly prohibited. If you have received this communication in error, please notify us immediately by e-mail and delete the message and any attachments from your system. -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
Dropping through into PARA-2 from PARA-1 when the return from the PERFORM PARA-2 is still set would result in a loop. Ugly code IMO. Dave Gibney Information Technology Services Washington State University > -Original Message- > From: IBM Mainframe Discussion List [mailto:IBM-MAIN@bama.ua.edu] On > Behalf Of Bob Shannon > Sent: Monday, April 23, 2012 12:46 PM > To: IBM-MAIN@bama.ua.edu > Subject: Re: Why does Enterprise COBOL V4.1 optimization complain about a > PERFORM loop? > > > Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" > message IGYOP3094-W >in the do-nothing program listed below? > > I haven't written in COBOL in over 30 years, but I suspect it's because SUB- > PARA-2 sits in between SUB-PARA-1 and PARA-EXIT. > > 44SUB-PARA-1. > 45IF WS-SUB < 6 > 46 1MOVE 0 TO WS-SUB > 47 1GO TO PARA-EXIT. > 48 > 49SUB-PARA-2. > 50DISPLAY WS-SUB. > 51 > 52PARA-EXIT. > 53EXIT. > > Bob Shannon > Rocket > > -- > For IBM-MAIN subscribe / signoff / archive access instructions, > send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Re: Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
> Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" > message IGYOP3094-W >in the do-nothing program listed below? I haven't written in COBOL in over 30 years, but I suspect it's because SUB-PARA-2 sits in between SUB-PARA-1 and PARA-EXIT. 44SUB-PARA-1. 45IF WS-SUB < 6 46 1MOVE 0 TO WS-SUB 47 1GO TO PARA-EXIT. 48 49SUB-PARA-2. 50DISPLAY WS-SUB. 51 52PARA-EXIT. 53EXIT. Bob Shannon Rocket -- For IBM-MAIN subscribe / signoff / archive access instructions, send email to lists...@bama.ua.edu with the message: INFO IBM-MAIN
Why does Enterprise COBOL V4.1 optimization complain about a PERFORM loop?
Can anyone explain to me why I get Enterprise COBOL V4.1 "informational" message IGYOP3094-W in the do-nothing program listed below? TIA for curing my ignorance. Peter PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date 04/23/2012 Time 15 LineID PL SL +-*A-1-B--+2+3+4+5+6+7-|--+8 01 * PROPRIETARY COMMENT ON LINE 1 REMOVED FOR PRIVACY 02ID DIVISION. 03PROGRAM-ID. TESTGOTO. 04ENVIRONMENT DIVISION. 05DATA DIVISION. 06WORKING-STORAGE SECTION. 0701 WS-WORK-AREA. 0805 WS-SUBPIC S9(4) USAGE IS BINARY. 09 10LINKAGE SECTION. 1101 PARM-AREA. 1205 PARM-LEN PIC S9(4) BINARY. 1305 PARM-DATA. 1410 PARM-CC PIC 9(02). 1510 PARM-YY PIC 9(02). 1610 PARM-MM PIC 9(02). 1710 PARM-DD PIC 9(02). 18 PP 5655-S71 IBM Enterprise COBOL for z/OS 4.1.0 TESTGOTO Date 04/23/2012 Time 15 LineID PL SL +-*A-1-B--+2+3+4+5+6+7-|--+8 20PROCEDURE DIVISION USING PARM-AREA. 21 *LINES 22-30 PROPRIETARY COPY CODE REMOVED FOR PRIVACY 31 32MOVE PARM-DD TO WS-SUB. 33PERFORM PARA-1 THRU PARA-EXIT. 34GO TO RETURN-TO-CALLER. 35 36PARA-1. 37IF PARM-MM > 06 38 1 MOVE +2 TO WS-SUB. 39PERFORM SUB-PARA-2. 40PERFORM SUB-PARA-1. ==40==> IGYOP3094-W There may be a loop from the "PERFORM" statement at "PERFORM (line 40.01)" to itself. "PERFORM" statement optimization was not attempted. 41MOVE WS-SUB TO RETURN-CODE. 42GO TO PARA-EXIT. 43 44SUB-PARA-1. 45IF WS-SUB < 6 46 1MOVE 0 TO WS-SUB 47 1GO TO PARA-EXIT. 48 49SUB-PARA-2. 50DISPLAY WS-SUB. 51