IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Linkage with "By Value": how can I get each parame


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
ossodue

New User


Joined: 29 Mar 2006
Posts: 4

PostPosted: Tue Feb 26, 2008 10:08 pm
Reply with quote

Hi.
I find on the web the code that a called routine can use to get the number and the address of passed parameter.
With some tricks, my version is
Code:

      *----------------------------------------------------------------*
       IDENTIFICATION DIVISION.
      *----------------------------------------------------------------*
       PROGRAM-ID.              PARMCOUN.
      *----------------------------------------------------------------*
       ENVIRONMENT DIVISION.
      *----------------------------------------------------------------*
       CONFIGURATION SECTION.
      *----------------------------------------------------------------*
       SPECIAL-NAMES.
      *----------------------------------------------------------------*
           DECIMAL-POINT               IS COMMA.
      *----------------------------------------------------------------*
       INPUT-OUTPUT SECTION.
      *----------------------------------------------------------------*
       FILE-CONTROL.
      *----------------------------------------------------------------*
       DATA DIVISION.
      *----------------------------------------------------------------*
       FILE SECTION.
      *----------------------------------------------------------------*
       WORKING-STORAGE SECTION.
      *----------------------------------------------------------------*
       01  SW-LAST-PARM                 PIC  X(01)      VALUE SPACE.
           88  NO-LAST-PARM                             VALUE 'N'.
           88  YES-LAST-PARM                            VALUE 'Y'.
       01  W-PARMS-COUNTER              PIC  9(08)      COMP
                                                        VALUE ZERO.
      *----------------------------------------------------------------*
       LINKAGE SECTION.
      *----------------------------------------------------------------*
       01  L-BASE-PARMS                POINTER.
       01  L-TAB-PARMS.
           05  L-ELE-PARM              OCCURS 1
                                       INDEXED BY IX-ELE-PARM.
               10  L-ADDR-PARM-X.
                   15  L-ADDR-PARM-P   POINTER.
                   15  L-ADDR-PARM-B REDEFINES L-ADDR-PARM-P
                                       PIC S9(09)       BINARY.
      *----------------------------------------------------------------*
       PROCEDURE DIVISION           USING BY VALUE L-BASE-PARMS.
      *----------------------------------------------------------------*
           IF  ADDRESS OF L-BASE-PARMS  NOT =  NULL
               SET ADDRESS OF L-TAB-PARMS
                                       TO ADDRESS OF L-BASE-PARMS
               MOVE ZERO               TO W-PARMS-COUNTER
               SET NO-LAST-PARM        TO TRUE

               PERFORM VARYING IX-ELE-PARM FROM 1 BY 1
                         UNTIL YES-LAST-PARM
                 ADD 1                 TO W-PARMS-COUNTER

                 IF  L-ADDR-PARM-P (IX-ELE-PARM)  =  NULL
                     DISPLAY 'ADDRESS OF PARAMETER NUMBER '
                             W-PARMS-COUNTER
                             ' IS NULL'
                 ELSE
                     DISPLAY 'ADDRESS OF PARAMETER NUMBER '
                             W-PARMS-COUNTER
                             ' IS >'
                             L-ADDR-PARM-X (IX-ELE-PARM)
                             '<'
                 END-IF

                 IF  L-ADDR-PARM-B (IX-ELE-PARM)  <  ZERO
                     SET YES-LAST-PARM TO TRUE
                 END-IF
               END-PERFORM
           ELSE
               DISPLAY 'NO PARAMETERS PASSED'
           END-IF.

           GOBACK.


I'd like to get the length of each parameter. Is it possible?

Thanks.
Back to top
View user's profile Send private message
UmeySan

Active Member


Joined: 22 Aug 2006
Posts: 771
Location: Germany

PostPosted: Wed Feb 27, 2008 10:03 pm
Reply with quote

Hi ossodue !

In your example, you receiving the adresses where data has been stored for futher use. So the parameter is a adress. A adress is a 4byte word.

But i think you do not mean this. If you want to know the whole length of
the data at that adress, the calling applikation has to store the length into a separate field. Could easily done by using String with count-option.

UNSTRING WRK-VERWENDTX DELIMITED BY '*' ...or size
INTO DATA-VERW-ZWECK-D IN UMSATZ-BEREICH
COUNT IN DATA-VERW-ZWECK-L IN UMSATZ-BEREICH
END-UNSTRING


CALL MDP01510 USING UMSATZ-BEREICH


01 UMSATZ-BEREICH
10 DATA-VERW-ZWECK.
49 DATA-VERW-ZWECK-L PIC S9(4) COMP.
49 DATA-VERW-ZWECK-D PIC X(378).


Regards, UmeySan
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts COBOL -Linkage Section-Case Sensitive COBOL Programming 1
No new posts PuTTY - "User is not a surrogate... IBM Tools 5
No new posts Newbie Stuck on "Duplicate Datas... TSO/ISPF 5
No new posts RABBIT HOLE NEEDED - "Live"... All Other Mainframe Topics 0
No new posts Using PARM=('JPn"&SYMBOL&quo... DFSORT/ICETOOL 2
Search our Forums:

Back to Top