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

COBOL 4.0 Help on Sub Routine 1

Status
Not open for further replies.

riveradd

IS-IT--Management
Jan 31, 2002
21
0
0
US
This may be as basic as it comes but I need help calling a subroutine. I am a student so please dis-regard my ignorance. First let me give you some background so that maybe you can help me. The program that I am supposed to develop is quite simple. It requires 2 subroutines that do seperate calculations. I will include these programs along with the main program. Anyway, I am able to compile, build and execute the program with no errors but when the program writes the output, I do not get any of the calulations. I get the dollar signs, decimal points and even zeros but no numbers. I ran it through the debugger in animate mode, then checked the values after it ran through the call statements but they only showed question marks on called values. Then I stepped through the program manually but this time I got an internal debugger error,after which it closed the program.

Here is the main program call
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. PROGRAM3.
000030 AUTHOR. DAVID RIVERA.
000040
000050 ENVIRONMENT DIVISION.
000060 INPUT-OUTPUT SECTION.
000070 FILE-CONTROL.
000080 SELECT COMMREPINPUT-FILE ASSIGN TO SYSIN
000090 ORGANIZATION IS LINE SEQUENTIAL.
000100 SELECT COMMREPOUTPUT-FILE ASSIGN TO SYSOUT
000110 ORGANIZATION IS LINE SEQUENTIAL.
000120
000130 DATA DIVISION.
000140 FILE SECTION.
000150 FD COMMREPINPUT-FILE
000160 RECORD CONTAINS 67 CHARACTERS
000170 DATA RECORD IS COMMREPINPUT-RECORD.
000171
000180 01 COMMREPINPUT-RECORD.
000190 05 FILLER PIC X(6).
000200 05 CRI-CONTNUMB PIC 9(6).
000210 05 CRI-CONTOWNER PIC X(20).
000220 05 FILLER PIC X(25).
000230 05 CRI-NUMBCONTR PIC 9(2).
000240 05 FILLER PIC X(2).
000250 05 CRI-CONTCOST PIC 99V99.
000260 05 FILLER PIC X(2).
000270
000280 FD COMMREPOUTPUT-FILE
000290 RECORD CONTAINS 132 CHARACTERS
000300 DATA RECORD IS COMMREPOUTPUT-RECORD.
000310 01 COMMREPOUTPUT-RECORD.
000320 05 FILLER PIC X(1).
000330 05 CRO-CONTNUMB PIC ZZZZZ9.
000340 05 FILLER PIC X(2).
000350 05 CRO-CONTOWNER PIC X(20).
000360 05 FILLER PIC X(5).
000370 05 CRO-NUMBCONTR PIC Z9.
000380 05 FILLER PIC X(6).
000390 05 CRO-CONTCOST PIC $$$.99.
000400 05 FILLER PIC X(4).
000410 05 CRO-CONTRTOT PIC $$,$$$.99.
000420 05 FILLER PIC X(5).
000430 05 CRO-COMMISS PIC $$$$.99.
000440 05 FILLER PIC X(5).
000450 05 CRO-TOTCOST PIC $$$,$$$.99.
000460
000470 WORKING-STORAGE SECTION.
000480 01 WS-EOF-FLAG PIC X.
000490 01 WS-ARGUMENTS.
000500 05 WS-COMM PIC 999V99.
000510 05 WS-CONTRTOT PIC 9999V99.
000520 05 WS-TOTCOST PIC 99999V99.
000530 01 WS-ACCUMULATORS.
000540 05 WS-FNL-NUMBCONTR PIC 9999.
000550 05 WS-FNL-CONTRTOT PIC 9(6)V99.
000560 05 WS-FNL-COMM PIC 9(5)V99.
000570 05 WS-FNL-TOTCOST PIC 9(7)V99.
000580 01 HEADING-LINE1.
000590 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000600 05 FILLER PIC X(7).
000610 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000620 05 FILLER PIC X(7).
000630 05 FILLER PIC X(9) VALUE 'NUMBER OF'.
000640 05 FILLER PIC X(2).
000650 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000660 05 FILLER PIC X(4).
000670 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000680 05 FILLER PIC X(20).
000690 05 FILLER PIC X(5) VALUE 'TOTAL'.
000700
000710 01 HEADING-LINE2.
000720 05 FILLER PIC X(1).
000730 05 FILLER PIC X(6) VALUE 'NUMBER'.
000740 05 FILLER PIC X(10).
000750 05 FILLER PIC X(5) VALUE 'OWNER'.
000760 05 FILLER PIC X(8).
000770 05 FILLER PIC X(9) VALUE 'CONTRACTS'.
000780 05 FILLER PIC X(4).
000790 05 FILLER PIC X(4) VALUE 'COST'.
000800 05 FILLER PIC X(8).
000810 05 FILLER PIC X(5) VALUE 'TOTAL'.
000820 05 FILLER PIC X(5).
000830 05 FILLER PIC X(10) VALUE 'COMMISSION'.
000840 05 FILLER PIC X(7).
000850 05 FILLER PIC X(4) VALUE 'COST'.
000851
000870 01 TOTAL-LINE.
000880 05 FILLER PIC X(15) VALUE 'TOTAL CONTRACTS'.
000890 05 FILLER PIC X(1) VALUE SPACES.
000900 05 TL-FNL-NUMBCONTR PIC ZZZ9.
000910 05 FILLER PIC X(16) VALUE SPACES.
000920 05 FILLER PIC X(12) VALUE 'FINAL TOTALS'.
000930 05 FILLER PIC X(2) VALUE SPACES.
000940 05 TL-FNL-CONTRTOT PIC $$$$,$$$.99.
000950 05 FILLER PIC X(2) VALUE SPACES.
000960 05 TL-FNL-COMM PIC $$$,$$$.99.
000970 05 FILLER PIC X(2) VALUE SPACES.
000980 05 TL-FNL-TOTCOST PIC $$,$$$,$$$.99.
000990
001000 PROCEDURE DIVISION.
001010 PREPARE-COMMODREP-REPORT.
001020 OPEN INPUT COMMREPINPUT-FILE
001030 OUTPUT COMMREPOUTPUT-FILE
001040 MOVE "N" TO WS-EOF-FLAG
001050 READ COMMREPINPUT-FILE
001060 AT END MOVE "Y" TO WS-EOF-FLAG
001070 END-READ.
001080
001090 PERFORM WRITE-HEADING-LINE1.
001100 PERFORM WRITE-HEADING-LINE2.
001110 PERFORM UNTIL WS-EOF-FLAG IS EQUAL TO "Y"
001130 MOVE SPACES TO COMMREPOUTPUT-RECORD
001140 MOVE CRI-CONTNUMB TO CRO-CONTNUMB
001150 MOVE CRI-CONTOWNER TO CRO-CONTOWNER
001160 MOVE CRI-NUMBCONTR TO CRO-NUMBCONTR
001170 MOVE CRI-CONTCOST TO CRO-CONTCOST
001171 CALL 'CALCCOMMSUB'
001172 USING CRI-NUMBCONTR, CRI-CONTCOST, WS-ARGUMENTS
001173 END-CALL
001174
001175 MOVE WS-CONTRTOT TO CRO-CONTRTOT
001176 MOVE WS-COMM TO CRO-COMMISS
001177 MOVE WS-TOTCOST TO CRO-TOTCOST
001178 MOVE WS-TOTCOST TO CRO-TOTCOST
001179 CALL 'ACCTOTLSUB'
001180 USING CRI-NUMBCONTR, WS-COMM, WS-CONTRTOT, WS-TOTCOST, WS-FNL-NUMBCONTR, WS-FNL-CONTRTOT, WS-FNL-COMM, WS-FNL-TOTCOST
001181 END-CALL
001182 MOVE WS-FNL-NUMBCONTR TO TL-FNL-NUMBCONTR
001183 MOVE WS-FNL-CONTRTOT TO TL-FNL-CONTRTOT
001184 MOVE WS-FNL-COMM TO TL-FNL-COMM
001185 MOVE WS-FNL-TOTCOST TO TL-FNL-TOTCOST
001189 WRITE COMMREPOUTPUT-RECORD
001320 READ COMMREPINPUT-FILE
001330 AT END MOVE "Y" TO WS-EOF-FLAG
001340 END-READ
001350 END-PERFORM.
001361
001384 PERFORM WRITE-TOTAL-LINE.
001430 CLOSE COMMREPINPUT-FILE.
001450 CLOSE COMMREPOUTPUT-FILE.
001460 STOP RUN.
001470 WRITE-HEADING-LINE1.
001490 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001500 WRITE COMMREPOUTPUT-RECORD.
001510 MOVE HEADING-LINE1 TO COMMREPOUTPUT-RECORD.
001520 WRITE COMMREPOUTPUT-RECORD.
001530
001540 WRITE-HEADING-LINE2.
001550 MOVE HEADING-LINE2 TO COMMREPOUTPUT-RECORD.
001560 WRITE COMMREPOUTPUT-RECORD.
001570 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001580 WRITE COMMREPOUTPUT-RECORD.
001590
001600 WRITE-TOTAL-LINE.
001610 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001620 WRITE COMMREPOUTPUT-RECORD.
001630 MOVE TOTAL-LINE TO COMMREPOUTPUT-RECORD.
001640 WRITE COMMREPOUTPUT-RECORD.
001650

Here is the first sub-routine
000010 IDENTIFICATION DIVISION.
000011 PROGRAM-ID. CALCCOMMSUB.
000012 AUTHOR. DAVID RIVERA
000013
000016 LINKAGE SECTION.
000018 01 LS-NUMBCONTR PIC 9(2).
000019 01 LS-CONTCOST PIC 99V99.
000021 01 LS-ARGUMENTS.
000022 05 LS-COMM PIC 999V99.
000023 05 LS-CONTRTOT PIC 9999V99.
000024 05 LS-TOTCOST PIC 99999V99.
000025
000026 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-CONTCOST, LS-ARGUMENTS.
000028 COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST
000030 IF LS-CONTRTOT <= 1000.00
000031 COMPUTE LS-COMM = LS-CONTRTOT * 0.7
000032 ELSE
000033 COMPUTE LS-COMM = (LS-CONTRTOT - 1000.00) * 0.5 + 70.00
000034 END-IF
000035 COMPUTE LS-TOTCOST = LS-CONTRTOT + LS-COMM
000036 END-COMPUTE.
000037 EXIT PROGRAM.

Here is the last sub-routine
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. ACCTOTLSUB
000030 AUTHOR. DAVID RIVERA
000040
000050 LINKAGE SECTION.
000051 01 LS-NUMBCONTR PIC 9(2).
000053 01 LS-COMM PIC 99V99.
000054 01 LS-CONTRTOT PIC 9999V99.
000055 01 LS-TOTCOST PIC 99999V99.
000056 01 WS-ACCUMULATORS.
000057 05 LS-FNL-NUMBCONTR PIC 9999.
000058 05 LS-FNL-CONTRTOT PIC 9(6)V99.
000059 05 LS-FNL-COMM PIC 9(5)V99.
000060 05 LS-FNL-TOTCOST PIC 9(7)V99.
000061
000120 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-COMM, LS-CONTRTOT, LS-TOTCOST,
000121 LS-FNL-NUMBCONTR, LS-FNL-CONTRTOT, LS-FNL-COMM, LS-FNL-TOTCOST.
000122 CALC-TOTALS.
000130 ADD LS-NUMBCONTR TO LS-FNLNUMCONT
000140 ADD LS-CONTRTOT TO LS-FNL-CONTRTOT
000141 ADD LS-COMM TO LS-FNL-COMM
000142 ADD LS-TOTCOST TO LS-FNL-TOTCOST
000150
000160 EXIT PROGRAM.

I know this is long but I wanted to make sure that you understood what I was looking at. Again, the program links and executes just fine. HELP.

PS Here is the first 2 lines of the input file just in case someone feels like going beyond just looking. Thanks in advance.

072786100103ALLENSON, SHEILA M. CONTEMPORARY DESK 202386800873403
072786100105ANDERSON, ARLENE T. EXECUTIVE DESK CHAIR301259301005005

David
 
Marc,
I did what Tom suggested and still the problem exists. All of the fields are now 01 levelized but I get the same problem of not displaying the calculations.

Tom,
I used winlink to link all three of my .obj files and had no problems. Unfortunately I am still not getting any output. Frustration does not begin to say how I feel much less how you guys must feel.

I really appreciate your inputs. If you have any more please let me know but please do not make this your headache. Unfortunately it is mine. Its back to the old drawing board. Tom, was the above change that you made the only change? In other words you just changed the levels and it worked fine? That is what stumps me the most, that it works on your compiler but not on mine. Guess thats why I am on here asking, NO, begging for help. :)

David David Rivera
 
David,
could you re-post your current version of the program and two sub programs.
Thanks
Marc
 
riveradd,

There is a significant difference between your program and Tom's. It could just be a typo on your part, but there is no paragraph name in your CALCOMMSUB:

000026 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-CONTCOST, LS-ARGUMENTS.
000028 COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST

Tom's:
000026 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-CONTCOST,
LS-ARGUMENTS.
a.
000028 COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST
 
Marc,
Here is the entire program again. I also included part of the input file that I am using, just in case you need it.

Dimanja,
What did you mean there was a significant difference between my program and Toms. I only ask because I was under the impression that Tom used my program initially to see if it worked and it did. What he posted was an example of using a nested sub-routine.

Tom is this right?

Marc here is the program.

INPUT FILE

072786100101ALBERT, PETER A. CRT WORKSTATION 101202100308901
072786100103ALLENSON, SHEILA M. CONTEMPORARY DESK 202386800873403
072786100105ANDERSON, ARLENE T. EXECUTIVE DESK CHAIR301259301005005

THE MAIN PROGRAM

000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. PROGRAM3.
000030 AUTHOR. DAVID RIVERA.
000040
000050 ENVIRONMENT DIVISION.
000060 INPUT-OUTPUT SECTION.
000070 FILE-CONTROL.
000080 SELECT COMMREPINPUT-FILE ASSIGN TO SYSIN
000090 ORGANIZATION IS LINE SEQUENTIAL.
000100 SELECT COMMREPOUTPUT-FILE ASSIGN TO SYSOUT
000110 ORGANIZATION IS LINE SEQUENTIAL.
000120
000130 DATA DIVISION.
000140 FILE SECTION.
000150 FD COMMREPINPUT-FILE
000160 RECORD CONTAINS 67 CHARACTERS
000170 DATA RECORD IS COMMREPINPUT-RECORD.
000171
000180 01 COMMREPINPUT-RECORD.
000190 05 FILLER PIC X(6).
000200 05 CRI-CONTNUMB PIC 9(6).
000210 05 CRI-CONTOWNER PIC X(20).
000220 05 FILLER PIC X(25).
000230 05 CRI-NUMBCONTR PIC 9(2).
000240 05 FILLER PIC X(2).
000250 05 CRI-CONTCOST PIC 99V99.
000260 05 FILLER PIC X(2).
000270
000280 FD COMMREPOUTPUT-FILE
000290 RECORD CONTAINS 132 CHARACTERS
000300 DATA RECORD IS COMMREPOUTPUT-RECORD.
000310 01 COMMREPOUTPUT-RECORD.
000320 05 FILLER PIC X(1).
000330 05 CRO-CONTNUMB PIC ZZZZZ9.
000340 05 FILLER PIC X(2).
000350 05 CRO-CONTOWNER PIC X(20).
000360 05 FILLER PIC X(5).
000370 05 CRO-NUMBCONTR PIC Z9.
000380 05 FILLER PIC X(6).
000390 05 CRO-CONTCOST PIC $$$.99.
000400 05 FILLER PIC X(4).
000410 05 CRO-CONTRTOT PIC $$,$$$.99.
000420 05 FILLER PIC X(5).
000430 05 CRO-COMMISS PIC $$$$.99.
000440 05 FILLER PIC X(5).
000450 05 CRO-TOTCOST PIC $$$,$$$.99.
000460
000470 WORKING-STORAGE SECTION.
000480 01 WS-EOF-FLAG PIC X.
000490 01 WS-ARGUMENTS.
000500 05 WS-COMM PIC 999V99.
000510 05 WS-CONTRTOT PIC 9999V99.
000520 05 WS-TOTCOST PIC 99999V99.
000530 01 WS-ACCUMULATORS.
000540 05 WS-FNL-NUMBCONTR PIC 9999.
000550 05 WS-FNL-CONTRTOT PIC 9(6)V99.
000560 05 WS-FNL-COMM PIC 9(5)V99.
000570 05 WS-FNL-TOTCOST PIC 9(7)V99.
000580 01 HEADING-LINE1.
000590 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000600 05 FILLER PIC X(7).
000610 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000620 05 FILLER PIC X(7).
000630 05 FILLER PIC X(9) VALUE 'NUMBER OF'.
000640 05 FILLER PIC X(2).
000650 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000660 05 FILLER PIC X(4).
000670 05 FILLER PIC X(8) VALUE 'CONTRACT'.
000680 05 FILLER PIC X(20).
000690 05 FILLER PIC X(5) VALUE 'TOTAL'.
000700
000710 01 HEADING-LINE2.
000720 05 FILLER PIC X(1).
000730 05 FILLER PIC X(6) VALUE 'NUMBER'.
000740 05 FILLER PIC X(10).
000750 05 FILLER PIC X(5) VALUE 'OWNER'.
000760 05 FILLER PIC X(8).
000770 05 FILLER PIC X(9) VALUE 'CONTRACTS'.
000780 05 FILLER PIC X(4).
000790 05 FILLER PIC X(4) VALUE 'COST'.
000800 05 FILLER PIC X(8).
000810 05 FILLER PIC X(5) VALUE 'TOTAL'.
000820 05 FILLER PIC X(5).
000830 05 FILLER PIC X(10) VALUE 'COMMISSION'.
000840 05 FILLER PIC X(7).
000850 05 FILLER PIC X(4) VALUE 'COST'.
000851
000870 01 TOTAL-LINE.
000880 05 FILLER PIC X(15) VALUE 'TOTAL CONTRACTS'.
000890 05 FILLER PIC X(1) VALUE SPACES.
000900 05 TL-FNL-NUMBCONTR PIC ZZZ9.
000910 05 FILLER PIC X(16) VALUE SPACES.
000920 05 FILLER PIC X(12) VALUE 'FINAL TOTALS'.
000930 05 FILLER PIC X(2) VALUE SPACES.
000940 05 TL-FNL-CONTRTOT PIC $$$$,$$$.99.
000950 05 FILLER PIC X(2) VALUE SPACES.
000960 05 TL-FNL-COMM PIC $$$,$$$.99.
000970 05 FILLER PIC X(2) VALUE SPACES.
000980 05 TL-FNL-TOTCOST PIC $$,$$$,$$$.99.
000990
001000 PROCEDURE DIVISION.
001010 PREPARE-COMMODREP-REPORT.
001020 OPEN INPUT COMMREPINPUT-FILE
001030 OUTPUT COMMREPOUTPUT-FILE
001040 MOVE &quot;N&quot; TO WS-EOF-FLAG
001050 READ COMMREPINPUT-FILE
001060 AT END MOVE &quot;Y&quot; TO WS-EOF-FLAG
001070 END-READ.
001080
001090 PERFORM WRITE-HEADING-LINE1.
001100 PERFORM WRITE-HEADING-LINE2.
001110 PERFORM UNTIL WS-EOF-FLAG IS EQUAL TO &quot;Y&quot;
001130 MOVE SPACES TO COMMREPOUTPUT-RECORD
001140 MOVE CRI-CONTNUMB TO CRO-CONTNUMB
001150 MOVE CRI-CONTOWNER TO CRO-CONTOWNER
001160 MOVE CRI-NUMBCONTR TO CRO-NUMBCONTR
001170 MOVE CRI-CONTCOST TO CRO-CONTCOST
001171 CALL 'CALCCOMMSUB'
001172 USING CRI-NUMBCONTR, CRI-CONTCOST, WS-COMM, WS-CONTRTOT, WS-TOTCOST
001173 END-CALL
001174
001175 MOVE WS-CONTRTOT TO CRO-CONTRTOT
001176 MOVE WS-COMM TO CRO-COMMISS
001177 MOVE WS-TOTCOST TO CRO-TOTCOST
001179 CALL 'ACCTOTLSUBA'
001180 USING CRI-NUMBCONTR, WS-COMM, WS-CONTRTOT, WS-TOTCOST, WS-FNL-NUMBCONTR, WS-FNL-CONTRTOT, WS-FNL-COMM, WS-FNL-TOTCOST
001181 END-CALL
001182 MOVE WS-FNL-NUMBCONTR TO TL-FNL-NUMBCONTR
001183 MOVE WS-FNL-CONTRTOT TO TL-FNL-CONTRTOT
001184 MOVE WS-FNL-COMM TO TL-FNL-COMM
001185 MOVE WS-FNL-TOTCOST TO TL-FNL-TOTCOST
001189 WRITE COMMREPOUTPUT-RECORD
001320 READ COMMREPINPUT-FILE
001330 AT END MOVE &quot;Y&quot; TO WS-EOF-FLAG
001340 END-READ
001350 END-PERFORM.
001361
001384 PERFORM WRITE-TOTAL-LINE.
001430 CLOSE COMMREPINPUT-FILE.
001450 CLOSE COMMREPOUTPUT-FILE.
001460 STOP RUN.
001470 WRITE-HEADING-LINE1.
001490 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001500 WRITE COMMREPOUTPUT-RECORD.
001510 MOVE HEADING-LINE1 TO COMMREPOUTPUT-RECORD.
001520 WRITE COMMREPOUTPUT-RECORD.
001530
001540 WRITE-HEADING-LINE2.
001550 MOVE HEADING-LINE2 TO COMMREPOUTPUT-RECORD.
001560 WRITE COMMREPOUTPUT-RECORD.
001570 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001580 WRITE COMMREPOUTPUT-RECORD.
001590
001600 WRITE-TOTAL-LINE.
001610 MOVE SPACES TO COMMREPOUTPUT-RECORD.
001620 WRITE COMMREPOUTPUT-RECORD.
001630 MOVE TOTAL-LINE TO COMMREPOUTPUT-RECORD.
001640 WRITE COMMREPOUTPUT-RECORD.

FIRST SUBROUTINE - CALCCOMMSUB
000010 IDENTIFICATION DIVISION.
000011 PROGRAM-ID. CALCCOMMSUB.
000012 AUTHOR. DAVID RIVERA
000013
000016 LINKAGE SECTION.
000018 01 LS-NUMBCONTR PIC 9(2).
000019 01 LS-CONTCOST PIC 99V99.
000021 01 LS-COMM PIC 999V99.
000023 01 LS-CONTRTOT PIC 9999V99.
000024 01 LS-TOTCOST PIC 99999V99.
000025
000026 PROCEDURE DIVISION USING LS-COMM, LS-CONTRTOT, LS-TOTCOST.
000028 COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST
000030 IF LS-CONTRTOT <= 1000.00
000031 COMPUTE LS-COMM = LS-CONTRTOT * 0.07
000032 ELSE
000033 COMPUTE LS-COMM = (LS-CONTRTOT - 1000.00) * 0.05 + 70.00
000034 END-IF
000035 COMPUTE LS-TOTCOST = LS-CONTRTOT + LS-COMM
000036
000037 EXIT PROGRAM.

SECOND SUBROUTINE ACCTOTLSUB David Rivera
 
David,

Well Dimandja is correct; I did add paragraph name(s) where you had none. I presumed that Fujitsu is forgiving in this area, though I could be mistaken and that might be the cause of this behavior (but I doubt it). In particular, your first subroutine does not have a paragraph name after the PROCEDURE DIVISION header where one is required by standard COBOL.

However, there is now a very significant error in your program:
Code:
    CALL 'CALCCOMMSUB'
           USING CRI-NUMBCONTR, CRI-CONTCOST, WS-COMM, WS-CONTRTOT, WS-TOTCOST
    END-CALL
versus:
Code:
PROCEDURE DIVISION USING LS-COMM, LS-CONTRTOT, LS-TOTCOST.
Note that you have three formal parameters (on the PROCEDURE DIVISION header) but you have five actual parameters (on the CALL statement). This is not as originally posted, so I presume that something got changed somehow along the way.

[David, w.r.t. your remark several posts back: Of course it works on my COBOL -- because it really is my COBOL! [wink]]

Tom Morrison
 
Your COBOL? WOW. Anyway you are right about the change. I thought I had re-added that code. I deleted as an experiment but as you can tell forgot to re-add. When you compiled my program originally, did you change anything other than the levels in ACCTOTLCOMM? I assume that you used it as written except for that. As for the paragraph name, can you specify a little more because, as I asked Dimandja, I am not sure what you mean. An example might help. Thanks again.

David David Rivera
 
In the first subroutine I added a paragraph name where there was none, viz.
Code:
000026    PROCEDURE DIVISION USING LS-NUMBCONTR, LS-CONTCOST, 
                   LS-ARGUMENTS.
       a.    
000028      COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST
That a. is a paragraph name, albeit a nondescriptive one. Tom Morrison
 
I went ahead and made my changes but to no avail. Tom, if you would can you please tell me if you used my original code with just the changes on the levels or did you use the above nested code? Just wondering. Thanks, Tom and to all who have tried to help. I'm afraid this one may get the best of me. Anyway for those who care, here is my adjusted code for the subs.

CALCCOMMSUB

000010 IDENTIFICATION DIVISION.
000011 PROGRAM-ID. CALCCOMMSUB.
000012 AUTHOR. DAVID RIVERA
000013
000016 LINKAGE SECTION.
000018 01 LS-NUMBCONTR PIC 9(2).
000019 01 LS-CONTCOST PIC 99V99.
000021 01 LS-COMM PIC 999V99.
000023 01 LS-CONTRTOT PIC 9999V99.
000024 01 LS-TOTCOST PIC 99999V99.
000025
000026 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-CONTCOST, LS-COMM, LS-CONTRTOT, LS-TOTCOST.
000028 COMPUTE-TOT.
000029 COMPUTE LS-CONTRTOT = LS-NUMBCONTR * LS-CONTCOST
000030 IF LS-CONTRTOT <= 1000.00
000031 COMPUTE LS-COMM = LS-CONTRTOT * 0.07
000032 ELSE
000033 COMPUTE LS-COMM = (LS-CONTRTOT - 1000.00) * 0.05 + 70.00
000034 END-IF
000035 COMPUTE LS-TOTCOST = LS-CONTRTOT + LS-COMM
000036
000037 EXIT PROGRAM.

ACCTOTLSUB
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. ACCTOTLSUB
000030 AUTHOR. DAVID RIVERA
000040
000050 LINKAGE SECTION.
000051 01 LS-NUMBCONTR PIC 9(2).
000053 01 LS-COMM PIC 99V99.
000054 01 LS-CONTRTOT PIC 9999V99.
000055 01 LS-TOTCOST PIC 99999V99.
000056 01 LS-FNL-NUMBCONTR PIC 9999.
000058 01 LS-FNL-CONTRTOT PIC 9(6)V99.
000059 01 LS-FNL-COMM PIC 9(5)V99.
000060 01 LS-FNL-TOTCOST PIC 9(7)V99.
000061
000120 PROCEDURE DIVISION USING LS-NUMBCONTR, LS-COMM, LS-CONTRTOT, LS-TOTCOST,
000121 LS-FNL-NUMBCONTR, LS-FNL-CONTRTOT, LS-FNL-COMM, LS-FNL-TOTCOST.
000122 CALC-TOTALS.
000130 ADD LS-NUMBCONTR TO LS-FNLNUMCONT
000140 ADD LS-CONTRTOT TO LS-FNL-CONTRTOT
000141 ADD LS-COMM TO LS-FNL-COMM
000142 ADD LS-TOTCOST TO LS-FNL-TOTCOST
000150
000160 EXIT PROGRAM.
David Rivera
 
David, I used nested subprograms but -- I can assure you -- the behavior of RM/COBOL would be no different were they separately compiled subprograms (remember it is my COBOL).

Now, I find it almost impossible to imagine that the Fujitsu compiler won't somehow allow you to debug a program which contains subroutines, for the very simple reason that virtually every one of Fujitsu's customers writes COBOL programs that contain subroutines! So, what to do....?

I would, at this point, put in DISPLAY statements between every statement that has anything to do with calling CALCCOMMSUB, including those statements that use the results of the CALL. At minimum this will inform you that you have/have not successfully linked everything together correctly and what values CALCCOMMSUB thinks it has to work on.

Another question: Having noticed that Fujitsu v6 has a MAIN/NOMAIN compiler option, I wonder if you are using the NOMAIN option on the subprograms? Tom Morrison
 
Not sure of the last question but I know I have proj3 as the main program set on the compiler. As to whether is an option or not, I don't believe there is. I will try the display statements. I should have done that already but my mind set got lost somewhere in the confusion. To me there is not doubt that it is in the calling statement. Now whether it is because I made an error or whether the compiler is just not linking everything together, of course I don't know. I tend to believe it has something to do with the compiler but without having someone with the same compiler trying to do the same thing, I am at a lost.
When I get the display statements and check it out, I will let you know. Thanks for everything.

David Rivera
 
A thought, David.

So far, we don't have any proof that CALCCOMMSUB is executing. Let's find out.

Get this subprogram to do something. A display, as Tom suggests, in CALCCOMMSUB, would help.

You did mention that the debugger crashed at some point; when was this? On the call to CALCCOMMSUB?

One more thing. If you have to modify your program for testing, make and test each modification separately - it makes it easy to see what each change does. Making several changes in one compilation will not show what bugs got corrected or which ones were introduced.

Dimandja

 
David,

Well, curiosity got the better of me. I got my copy of Fujitsu v6 off the shelf and installed it.

You have several problems that I encountered, some of which are probably due to the difficulty (until you learn to use TGML) posting code on the forum. But here we go...

0. It wasn't anything too esoteric like compile or link options.

1. accumulators need to be initialized! Usually to zero. (This was not an issue on RM/COBOL because RM/COBOL initializes working-storage memory to spaces, unless a VALUE is specified. The RM/COBOL, as part of its legacy, will treat spaces as zeros in arithmetic calculations.)

2. Look very carefully at the names of the destination of the ADD statements:
Code:
PROCEDURE DIVISION USING LS-NUMBCONTR, LS-COMM, LS-CONTRTOT, LS-TOTCOST, 
   LS-FNL-NUMBCONTR, LS-FNL-CONTRTOT, LS-FNL-COMM, LS-FNL-TOTCOST.
CALC-TOTALS.
  ADD LS-NUMBCONTR TO LS-FNLNUMCONT
  ADD LS-CONTRTOT TO LS-FNL-CONTRTOT
  ADD LS-COMM TO LS-FNL-COMM
  ADD LS-TOTCOST TO LS-FNL-TOTCOST
Note the misspelling on the first destination. I finally got the code massaged to the place where the Fujitsu compiler actually diagnosed this error, but I had to do a lot of cleanup (which, again, may be due to the problems with posting code in the forum). Interestingly enough, the program would execute with this error present, but since it was the first statement in the sentence, none of the statements in the sentence were executed!, Therefore, the effect was as if ACCTOTLSUB was not being executed at all. (I surmise that I unknowingly corrected this problem when moving the program to RM/COBOL. As you can see when I posted the fragment, the correction had been made.)

3. Therefore, be careful with punctuation and correct use of area A. The problem with free-form COBOL source is that the compiler has to make assumptions that sometimes hide the real syntax problems with a program. Just as in the olden days, neatness counts.

4. Now I am going to uninstall Fujitsu v6.

Good luck! Tom Morrison
 
Dimandja,
I will try the display statements. You are right in that the debugger did give me an internal debugger error. It said it may not have enough virtual memory. Well I tried it on 2 different machines and it still gave me the same error. Basically, whenever I used the animate feature in the debugger it went through the entire program detecting no problems. But when I manually stepped into both call statements I got the error. Thanks for the input.

Tom,
Good find on the misspelling. I looked that over dozens of times without finding it. Anyway, were you able, then, to produce an output? I assume that you did. I really am surprised that the compiler did not catch that. Before I do anything else I will re-verify my code for correctness. That is rather embarrasing. Thanks. One thing though. I do not remember reading anything about initializing the accumular to zero? I thought it odd that it wasn't initialized, seeing as how other programming languages do. Anyway I will look it up. I am still concerned with the CALCCOMMSUB. I should displaying something from that but then maybe it too has a typo. Thanks again.

David Rivera
 
David asked: Anyway, were you able, then, to produce an output?

Yes.

The: One thing though. I do not remember reading anything about initializing the accumular to zero?

Well, if working-storage is initialized to spaces, I could reasonably extrapolate the results you were seeing, If the digit positions of the accumulators each contain a space, the MOVE numeric TO numeric-edited result might be exactly as you observed if the editing routine does not consider space=zero. Tom Morrison
 
I looked over the code once again and I found 2 more mis-spelled arguments in the ACCTOTLSUB. Nothing on the first. Will try later on to do the display statements. Thanks David Rivera
 
Well it finally worked. Had to do some more tweaking and renaming but it displays as advertised. Thanks to all who suffered with me through all this. I really appreciate it.
David Rivera
 
riveraddd,

Could you give us an idea of the type of tweaking you did to make this program work?

I am still wondering how your compiler would not flag practically any violations described in this thread -mispelled variables, missing language elements...

Dimandja
 
I did a line by line code evalutation, making sure that words were spelled correctly. Then I took all of the inputs in this thread and applied them. To be real honest the program still did not work the way I had thought it should. I had created 3 seperate programs, compiled them separately with prog3 being the main. Like I said earlier they all compiled correctly but it did not work. I got an idea from Tom, I believe, to make it all under one program name. I talked to the instructor and she did not have a problem with it so everything I had as a sub program, I included them into the main program and it worked.
I still wonder why it did not work. I guess I was thinking in C++ terms, in that we were supposed to link 3 separate programs and get them to work together. Is this something that COBOL won't do? Just an inquistive question as I am still stumped over this. Thanks for your help and thanks to all. David Rivera
 
David,

I did have each subprogram as a separate compile/separate object and then link the three together. I used the Fujitsu project manager, not PowerCOBOL. While I have uninstalled the Fujitsu compiler, I still have all the programs so I can send them to you. Drop me a request at t.morrison *at* liant.com.

Dimandja,

I was a bit amazed too at the difficulty I had getting the compiler to diagnose the syntax error, but there are lots of ways to construct a compiler, so I won't shoot at Fujitsu. [cannon] Tom Morrison
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top