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
 
PS #2
I am using the Fujitsu compiler, in case it matters.

David
 
Assuming that COMMREPINPUT-RECORD is &quot;072786100103ALLENSON, SHEILA M. CONTEMPORARY DESK 202386800873403&quot;, then,
05 FILLER PIC X(6) = &quot;072786&quot;.
05 CRI-CONTNUMB PIC 9(6) = 100103[bold]ALL[/bold]!
etc...

Your data is not correctly mapped into COMMREPINPUT-RECORD; there is garbage in the numeric fields. This is probably why no digits are printed out.

Correct your record layout. If you need further help, please ask.

Dimandja


 
Lets try that post again [bigsmile]

Assuming that COMMREPINPUT-RECORD is &quot;072786100103ALLENSON, SHEILA M. CONTEMPORARY DESK 202386800873403&quot;, then,
05 FILLER PIC X(6) = &quot;072786&quot;.
05 CRI-CONTNUMB PIC 9(6) = 100103ALL!
etc...

Your data is not correctly mapped into COMMREPINPUT-RECORD; there is garbage in the numeric fields. This is probably why no digits are printed out.

Correct your record layout. If you need further help, please ask.

Dimandja


 
Hi riveradd,

Please ignore those posts. My analysis was wrong.

Dimandja
 
Here is the output I get for the first line input. Of course I have about 30 lines but I won't show that here.

NUMBER OWNER CONTRACTS COST TOTAL COMMISSION COST

ALBERT, PETER A. 21 $30.89 $ , . 0 $ . 0 $ , . 0
 
A few questions.

1. Do CRI-NUMBCONTR and CRI-CONTCOST contain valid data before the call to CALCCOMMSUB?

2. Does WS-ARGURMENTS contain valid data after the call to CALCCOMMSUB?

If your answer is no to the second question, then we need to take a closer look at CALCCOMMSUB:

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.

END-COMPUTE, in this context, is capable of confusing some compilers. Either remove it, or be consistent and use it everywhere compute appears.
 
Usually Dimandja gives great advice. However, the last post, on the part regarding END-COMPUTE &quot;capable of confusing some compilers&quot; is not correct. [sadeyes] The fact is that any compiler capable of parsing COBOL should reasonably terminate a COMPUTE statement when a reserved word is found where an operator or user word is expected. What may differ among compilers is the quality of the diagnostic. END-COMPUTE is not confusing in this context. Where Dimandja and I would find common ground, however, is that your use of END-COMPUTE in this context shows some confusion on your part, David. [smile]

I think if you follow other advice provided by Dimandja you will find your error.

This next bit is not your logic error but...

If your compiler is not complaining about your last PROCEDURE DIVISION USING, it should. Formal arguments listed on the PROCEDURE DIVISION USING list should be defined with a level 01 or 77 in the LINKAGE SECTION, not with 05. Tom Morrison
 
Thanks for the input. The answer for number 1 is yes, it does contain valid numbers when you step through the program. As far as question 2, the answer is no. After stepping through the program, it shows question marks whereas CRI-NUMBCONTR and CRI-CONTCOST contain correct numbers. As far as the end-compute, I just added it as another resort to try to answer my problem. I had it without the end-compute statement prior to this post and it still gave me the same output. I can try it once again later this evening but in the meanwhile if there are any more suggestions, I am certainly open to them. I should add that before I created the sub-routine, I used the CALCCOMM as a perform statement, in which case it worked just fine. I cut an pasted it to the new sub-routine and it has been a problem ever since. Thanks again for taking interest in this.

David
 
One thing we all agree on is that I am most definitely confused. As I look at the code, Tom, I do agree with what you are saying. But in this case, I am actually using a 01 level argument along with its subs (for lack of a better word). Isn't it ok to use it in this fashion?
01 WS-ACCUMULATORS.
05 LS-FNL-NUMBCONTR PIC 9999.
05 LS-FNL-CONTRTOT PIC 9(6)V99.
05 LS-FNL-COMM PIC 9(5)V99.
05 LS-FNL-TOTCOST PIC 9(7)V99.


I had tried just using the 05 statements and if I am not mistaken (I have tried so many things I can't remember anything) it did work. But after looking my book over I felt this was a better way, I will try it to see if it makes a difference. Thanks Tom.

David
 
David,

1. Are the subroutines nested or separately compiled?

2. If separately compiled, are you sure you are using the same compiler opetions for all compilations? (You probably are.)

3. An aside... Are you sure your constants in CALCCOMMSUB should be 0.5 and 0.7. 0.05 and 0.07 seem more likely. (This is not the source of your error.)

4. By the way, I compiled your program on RM/COBOL and it works fine. [medal] This would lead me to believe that your compiler environment is not set up correctly. What compiler are you using? Tom Morrison
 
David, our posts are crossing!

What you should code in the subroutine is:
Code:
01  LS-FNL-NUMBCONTR      PIC 9999.
01  LS-FNL-CONTRTOT       PIC 9(6)V99.
01  LS-FNL-COMM           PIC 9(5)V99.
01  LS-FNL-TOTCOST        PIC 9(7)V99.

Your linkage section must correctly describe each item's data layout, not its placement in the data heirarchy of the calling program. Thus, if a LINKAGE SECTION item is named in the PROCEDURE DIVISION USING list (i.e. it is a formal parameter for the called program), its level number should be 01 (or 77 -- but that is a bit antiquated these days). Tom Morrison
 
David, I just went back through the thread and discovered that you are using Fujitsu, so ignore my Q in item 4 of a previous post. Tom Morrison
 
Tom,
You said you compiled the program and it worked. Did it produce the output? I only ask because when I compile and execute, everything works fine. The output is where I see there is a problem. I will take your advice on using the 01 levels. Is that what you used? Also, I compiled this using the Fujitsu compiler. I compiled the under the same .exe name and then build them together. Am I answering your question? Also, I will re-visit the number issue as I think you may be correct.
 
David,

Here is the output from RM/COBOL:
Code:
CONTRACT       CONTRACT       NUMBER OF  CONTRACT    CONTRACT                    TOTAL
 NUMBER          OWNER        CONTRACTS    COST        TOTAL     COMMISSION       COST

 100103  ALLENSON, SHEILA M.      68      $87.34    $5,939.12     $539.56      $6,478.68
 100105  ANDERSON, ARLENE T.      93        $.50       $46.50      $32.55         $79.05

TOTAL CONTRACTS  161                FINAL TOTALS    $5,985.62      $57.20      $6,557.73
I used 01 levels to define items in the second subroutine (not the first, which seems correct). Remember that the error seems to be happening on the call to the first subprogram.

I am no expert on the Fujitsu development environment, so I cannot be very helpful chasing this problem any further.

Good luck! Tom Morrison
 
So, Tom, are you saying that the problem is in my compilers environment? I am going to change all the statements to 01 level arguments to see if maybe that will work. If it does not then I must conclude that the settings in my compiler is having problems. Thank you very much for your help. At least now I have a new direction to follow. I will let you know what happens. Thanks again.

David
 
David,

One final thing. I slightly restructured your program to use nested subprograms. You might try that. I have removed many unchanged lines from the following to emphasize the structure:
Code:
000010   IDENTIFICATION DIVISION. 
000020   PROGRAM-ID.  PROGRAM3.
000030   AUTHOR.      DAVID RIVERA.
000040
000050   ENVIRONMENT DIVISION.
000060   INPUT-OUTPUT SECTION.
    [snip]
000130    DATA DIVISION.
000140    FILE SECTION.
    [snip]
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.
    [snip]
001000  PROCEDURE DIVISION.
001010  PREPARE-COMMODREP-REPORT.
    [snip]
001171          CALL 'CALCCOMMSUB'
001172                USING CRI-NUMBCONTR, CRI-CONTCOST, WS-ARGUMENTS
001173            END-CALL
    [snip]
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                       
000010    IDENTIFICATION DIVISION.
000011    PROGRAM-ID.    CALCCOMMSUB.
000012    AUTHOR.        DAVID RIVERA.
000013    Data Division.
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.
       a.    
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.
000011    END PROGRAM    CALCCOMMSUB.
000010    IDENTIFICATION DIVISION.
000020    PROGRAM-ID.    ACCTOTLSUB.
000030    AUTHOR.        DAVID RIVERA.
000040    data division.
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.
000057    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-FNL-NUMBCONTR
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.
000020    END PROGRAM     ACCTOTLSUB.
000020    END PROGRAM   PROGRAM3.

The benefit of using the nested subprogram structure is that it will eliminate any inadvertant disagreements in compiler options between the program and its subprograms.

Again, good luck. Tom Morrison
 
That sounds like a great suggestion. I can't implement it this program as the instructor specifically wanted 2 separate sub-routines, I guess to show us how to compile different programs into one. I will definitely keep this in file. So Tom, do you think that my problem lies mainly with the compiler options? I had thought that all along but could not find any real way of proving it. Based on the fact that you produced the output on your compiler seems to suggest that it may be a compiler problem. Just wondering.

David David Rivera
 
David,

Well...they are still subroutines, but such semantic minutiae might not be appreciated. [smarty]

I've had another look back in this thread. Other than a problem with compiler settings, you might not be linking the programs together correctly. You are doing (presumably) three separate compiles; each compile should produce its own, separate object (.obj) file. After compiling all three programs, into their separate .obj files, you would use the linker (WINLINK?) and specify the list of .obj files to include. The following is from Fujitsu v6 documentation set:[ul][li]Enter the name of the object file of the main program to be linked in the Link Object-List list box.[/li][li]Enter the files (object file, library file) required for linking in the Link Object-List list box. See “Entering Files.”[/li][/ul]So you should have three (3) .obj files in the List list box, the first of which should be for PROGRAM3.

Of course if version 4 doesn't have the same linking procedures, you need to dig into the help file to determine the correct way to link multiple object files.

Again, happy compiling! Tom Morrison
 
Hi David,
Your problem is, as Tom suggests, in the way in which you are calling the sub program, and the way in which that sub program is set up.

If you

CALL SUBPROGR USING FIELDA, FIELDB, FIELDC

the subprogram MUST have 3 01 (or 77) levels. (In actuality I believe all that is passed between one program and the next, is an address of the data).

In your original examples you show the program calling the ACCTOTLSUB subroutine with 8 fields, but this subroutine has only got 5 01 levels. I believe that the remaining 3 fields will be zeroised.

Tom's version works because he has called all subroutines with the correct number of parameters as defined by the 01 levels in the linkage section.

If this all sounds like jibberish, then please get back to me, as I am convinced that your problem lies in the call to ACCTOTLSUB

hth
Marc
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top