Re: Argument length not always correctly passed to subroutine or entry point for ANY LENGTH item

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

 



Thanks – It might be a bit confusing in the code at some of the entry points when using generic field names but a few comments should help.

 

 

Upon further review it looks like returning  a literal value  via the any length link field, link field is being treated as a 1 byte field in the move.

 

If an x(5) calling field initially contained “12345” and the literal “abcde” is moved to it in sub1, the resulting value is “a2345”.

 

If, however, the sub1 moves a ws item x(5) with value “abcde” to the link field, the resulting value is “abcde”.

 

 

 

 

From: Michael [mailto:michael@xxxxxxxxxxxxxxxx]
Sent: Friday, May 01, 2015 1:01 PM
To: open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
Subject: Re: Argument length not always correctly passed to subroutine or entry point for ANY LENGTH item

 

Yes, it seems as if there is a naming issue....
Change SUB1 to look like so, and it works correctly.

IDENTIFICATION DIVISION.
PROGRAM-ID.    SUB1.
DATA DIVISION.
FILE SECTION.
WORKING-STORAGE SECTION.
LINKAGE SECTION.
    1  link1   PIC X ANY LENGTH.
    1  link2   PIC X ANY LENGTH.
PROCEDURE DIVISION USING link1, link2.
0000-BEGIN.
    DISPLAY "SUB1-P1   - LENGTH=" FUNCTION LENGTH (link1) " DATA="" link1.
    DISPLAY "SUB1-P2   - LENGTH=" FUNCTION LENGTH (link2) " DATA="" link2.
    GOBACK.
0100-ENTRY.
ENTRY "ENTRY1" USING link1, link2.
    DISPLAY "ENTRY1-P1 - LENGTH=" FUNCTION LENGTH (link1) " DATA="" link1.
    DISPLAY "ENTRY1-P3 - LENGTH=" FUNCTION LENGTH (link2) " DATA="" link2.
    GOBACK.
0200-ENTRY.
ENTRY "ENTRY2" USING link1, link2.
    DISPLAY "ENTRY2-P1 - LENGTH=" FUNCTION LENGTH (link1) " DATA="" link1.
    DISPLAY "ENTRY2-P4 - LENGTH=" FUNCTION LENGTH (link2) " DATA="" link2.
    GOBACK.
END PROGRAM SUB1.

On 05/01/2015 11:48 AM, Jim Rinn wrote:

Below is an example of calls to a subprogram and entry statements within the subprogram.

 

It looks like the argument value is being passed correctly but he argument length is not always correct.

 

In main the lengths/values for p1, p2, p3 and p4 are respectively 1/1, 2/22, 3/333, 4/4444 as would be expected.

 

In sub1 p1 and p2 lengths are 1 and 2 as would be expected and the data is correct.

 

In entry1 p1 and p3 the correct data field is passed but the lengths of 1 and 1 are incorrect.  The lengths should 1 and 3.

 

In entry2 p1 and p4 the correct data field is passed but the lengths of 1 and 1 are incorrect.  The lengths should 1 and 4.

 

Looking at the generated C code, the issue seems to be the content of arg list created in main1 and the expected content of that same list in the sub1. 

 

The main1 builds the list as a list of the args listed in the call statement.

 

Looks like in sub1 the arg list is treated as the list of fields in the linkage section.  The if code picking up the lengths is indexing the arg list by the position of the items in the linkage section rather the the position on the original call. 

 

 

May be able to work around this by always using p1 to pn in the order as listed in linkage section.  But that seems restrictive.  In COBOL, positionally the args should carry though from a call to the subroutine main entry or any of the entry points should pass thru correctly.

 

 

Jim Rinn

 

 

# cat cobtst1.cbl

       IDENTIFICATION DIVISION.

       PROGRAM-ID.    MAIN1.

 

       DATA DIVISION.

       FILE SECTION.

 

       WORKING-STORAGE SECTION.

       01  WS-P1   PIC X(1) VALUE "1".

       01  WS-P2   PIC X(2) VALUE "22".

       01  WS-P3   PIC X(3) VALUE "333".

       01  WS-P4   PIC X(4) VALUE "4444".

 

       PROCEDURE DIVISION.

       0000-BEGIN.

           DISPLAY "MAIN1-P1  - LENGTH="FUNCTION LENGTH (WS-P1)

                    " DATA="" WS-P1.

           DISPLAY "MAIN1-P2  - LENGTH="FUNCTION LENGTH (WS-P2)

                    " DATA="" WS-P2.

           DISPLAY "MAIN1-P3  - LENGTH="FUNCTION LENGTH (WS-P3)

                    " DATA="" WS-P3.

           DISPLAY "MAIN1-P4  - LENGTH="FUNCTION LENGTH (WS-P4)

                    " DATA="" WS-P4.

           CALL "SUB1"   USING WS-P1, WS-P2.

           CALL "ENTRY1" USING WS-P1, WS-P3.

           CALL "ENTRY2" USING WS-P1, WS-P4.

           GOBACK.

       END PROGRAM MAIN1.

 

       IDENTIFICATION DIVISION.

       PROGRAM-ID.    SUB1.

 

       DATA DIVISION.

       FILE SECTION.

 

       WORKING-STORAGE SECTION.

       LINKAGE SECTION.

       01  WS-P1   PIC X ANY LENGTH.

       01  WS-P2   PIC X ANY LENGTH.

       01  WS-P3   PIC X ANY LENGTH.

       01  WS-P4   PIC X ANY LENGTH.

       01  WS-P5   PIC X ANY LENGTH.

 

       PROCEDURE DIVISION USING WS-P1, WS-P2.

       0000-BEGIN.

           DISPLAY "SUB1-P1   - LENGTH=" FUNCTION LENGTH (WS-P1)

                   " DATA="" WS-P1.

           DISPLAY "SUB1-P2   - LENGTH=" FUNCTION LENGTH (WS-P2)

                   " DATA="" WS-P2.

           GOBACK.

 

       0100-ENTRY.

           ENTRY "ENTRY1" USING WS-P1, WS-P3.

           DISPLAY "ENTRY1-P1 - LENGTH=" FUNCTION LENGTH (WS-P1)

                   " DATA="" WS-P1.

           DISPLAY "ENTRY1-P3 - LENGTH=" FUNCTION LENGTH (WS-P3)

                   " DATA="" WS-P3.

 

           GOBACK.

 

       0200-ENTRY.

           ENTRY "ENTRY2" USING WS-P1, WS-P4.

           DISPLAY "ENTRY2-P1 - LENGTH=" FUNCTION LENGTH (WS-P1)

                   " DATA="" WS-P1.

           DISPLAY "ENTRY2-P4 - LENGTH=" FUNCTION LENGTH (WS-P4)

                   " DATA="" WS-P4.

           GOBACK.

 

       END PROGRAM SUB1.

 

# cobc -x cobtst1.cbl

# cobtst1

MAIN1-P1  - LENGTH=000000001 DATA="">

MAIN1-P2  - LENGTH=000000002 DATA="">

MAIN1-P3  - LENGTH=000000003 DATA="">

MAIN1-P4  - LENGTH=000000004 DATA="">

SUB1-P1   - LENGTH=000000001 DATA="">

SUB1-P2   - LENGTH=000000002 DATA="">

ENTRY1-P1 - LENGTH=000000001 DATA="">

ENTRY1-P3 - LENGTH=000000001 DATA="">

ENTRY2-P1 - LENGTH=000000001 DATA="">

ENTRY2-P4 - LENGTH=000000001 DATA="">

#




------------------------------------------------------------------------------
One dashboard for servers and applications across Physical-Virtual-Cloud 
Widest out-of-the-box monitoring support with 50+ applications
Performance metrics, stats and reports that give you Actionable Insights
Deep dive visibility with transaction tracing using APM Insight.
http://ad.doubleclick.net/ddm/clk/290420510;117567292;y




_______________________________________________
open-cobol-list mailing list
open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
https://lists.sourceforge.net/lists/listinfo/open-cobol-list

 

------------------------------------------------------------------------------
_______________________________________________
open-cobol-list mailing list
open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
https://lists.sourceforge.net/lists/listinfo/open-cobol-list

[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux