BAL, COBOL, ISPF 2.x, MVS38J, Subroutine, TSO

PARMs in MVS38J

Overview

Passing parameters to a program is a common practice when using and/or developing subroutines. The parameter communications protocol (API) can take different forms depending on established APIs or newly defined APIs.

This post will focus on two types of parameter layouts encountered in a TSO / ISPF environment when invoking a program or command:

  1. Parameter layout used by TSO CALL requests (same as using PARM= keyword in the MVS JCL EXEC statement)
  2. Parameter layout used by TSO COMMAND requests (i.e. TSO LISTDSI DIR)

Both type of requests pass (share) the starting address (Register 1 in Assembler, resembling a pointer) of the actual communications content) comprised of more than the actual parameter data.

Let’s review each of the parameter layout APIs…

TSO CALL Requests

For this request, the content layout includes a parameter length and data as shown below:

  Upon program entry,

                        +----------+-----------------------+
  R1 will point here--> | Length   |  Parm Data....        |
                        +----------+-----------------------+
                          2-bytes     
                          Binary

Assembler and COBOL declarations that support the above construct are as follows:

   ASSEMBLER

   0        1         2
   1...5....0....5....0....5

   PARMLEN   DS   H
   PARMDAT   DS   CLnn

----------------------------------------------------------------------------

   COBOL LINKAGE

   0        1         2         3         4         5
   1...5....0....5....0....5....0....5....0....5....0....5
          01  PARM-DATA.
              05  PARM-LEN            PIC S9(04)  COMP.
              05  PARM-DATA           PIC X(nn).


   Note: Developer finalizes nn based on program (subroutine) parameter
         communication design.


Refer to the two use cases below to examine how data is represented in actual memory:

   Using TSO:       TSO CALL 'MY.PDS(PGMNAME)' '1234AB'
    - or -
   Using TSO/ISPF:  TSO ISPEXEC SELECT PGM(PGMNAME) PARM(1234AB)


   Program PGMNAME receives control with an address (i.e. x'00001046')
   in R1 whose EBCDIC content is represented by the below memory map:


   Address-  -------- -----Hex Data --- --------    ---- Char Data ----   
   00001040  0000FF00 F0C50006 F1F2F3F4 C1C2FF0D    .... 0E.. 1234 AB..
   00001050  10800809 00005FB8 00008890 00000000    .... ..^. .... ....


   o The parm length (actual length of parm data) is 6
   o The parm data is '1234AB'
   o Both are represented by the highlighted area

TSO COMMAND Requests

For this request, the content layout includes a parameter length, offset and data as shown below:

  Upon program entry,

                        +----------+----------+-----------------------+
  R1 will point here--> | Length   | Offset   |  Parm Data....        |
                        +----------+----------+-----------------------+
                          2-bytes    2-bytes     Command Buffer
                          Binary     Binary

Assembler and COBOL declarations that support the above figure follows:

   ASSEMBLER

   0        1         2
   1...5....0....5....0....5

   CMDLLEN   DS   H
   CMDLOFF   DS   H
   CMDLDAT   DS   CLnn

----------------------------------------------------------------------------

   COBOL LINKAGE

   0        1         2         3         4         5
   1...5....0....5....0....5....0....5....0....5....0....5
          01  CMDL-DATA.
              05  CMDL-LEN            PIC S9(04)  COMP.
              05  CMDL-OFF            PIC S9(04)  COMP.
              05  CMDL-DATA           PIC X(nn).


   Note: Developer finalizes nn based on program (subroutine) parameter
         communications design.


Refer to the two use cases below to examine how data is represented in actual memory:

   Using TSO:       TSO PGMNAME 1234AB
    - or -
   Using TSO/ISPF:  TSO ISPEXEC SELECT CMD(PGMNAME 1234AB)


   Program PGMNAME receives control with an address (i.e. x'00001046')
   in R1 whose EBCDIC content is represented by the below memory map:


   Address-  -------- -----Hex Data --- --------    ---- Char Data ----   
   00001040  0000FF00 F0C50012 0008D7C7 D4D5C1D4    .... 0E.. ..PG  MNAM
   00001050  C540F1F2 F3F4C1C2 00005FB8 00008890    E 12 34AB ..^. ....


   Referring to the highlighted area in the memory map, the parm length is 18,
   parm offset is 8 and parm data is 'PGMNAME 1234AB'.


   Note: Parm Data is the command line buffer!  The developer uses the offset
         to position to start of actual passed parameter data.  Ultimately,
         the passed parameter is "1234AB".


                                                     Passed Parameter Content         
                                                     ....PGMNAME 1234AB
                                                     ^   ^       {----}
                                                     |   |       ^  |
   Parm data starts at R1 (address);                 |   |       |  |
   let's call it A            o----------------------+   |       |  |
                                                         |       |  |
   Command Buffer starts at A + 4 (parm header)          |       |  |
   let's call it B            o--------------------------+       |  |
                                                                 |  |
   Parameters starts at A + 4 + 8                                |  |
   let's call it C            o----------------------------------+  |
                                                                    |
   Parm length - Parm header - Offset        = Length of parameters |
   18          - 4           - 8             = 6      o-------------+

   Note: Parm header is 4, 2-bytes for length and 2-bytes for offset fields.

The code…

A developer can distinguish the difference in PARM layouts by inspecting the high-order bit in the passed address (Register 1).

If the high-order bit is ON, it designates a TSO CALL PARM type. Otherwise, it is assumed to be a TSO COMMAND PARM type. Of course, this can easily be determined using Assembler as shown in the following code snippet:

*     * /********************************************************/ 
*     * /* Get PARAMTER information passed to program           */             
*     * /* - R1 myPARMS address on entry                        */             
*     * /* - R4 Starting parms address                          */             
*     * /* - R6 Starting parms length                           */             
*     * /* - R3, R5                   Working Register          */             
*     * /********************************************************/
         LTR   R1,R1               Do I have a PARM?
         BZ    ...                 NO, EXIT
         LR    R3,R1               PARM/CMDL addr                           
         TM    0(R3),X'80'         Is it PARM or CMDL addr?
         BZ    CMDL$IN             YES, CMDL addr          
PARM$IN  EQU   *                   NO,  PARM addr
         L     R4,0(,R3)           Addr of PARM                           
         LH    R6,0(,R4)           Length of PARM                           
         LTR   R6,R6               PARM > 0 length?                      
         BZ    ...                 NO, EXIT                       
         LA    R4,2(,R4)           YES, point to start of PARM data            
         B     DOPARMS              and continue...                            
CMDL$IN  EQU   *
         L     R4,0(,R3)           Command Buffer addr                         
         LH    R5,2(,R4)           Offset to Command Variables                 
         LTR   R5,R5               Any Variables?                              
         BZ    ...                 NO, EXIT                      
         LH    R6,0(,R4)           Length of Command Buffer                    
         SR    R6,R5               Subtract variable offset                    
         SH    R6,=H'4'            Subtract prefix                             
         BM    ...                 EXIT, NO VARIABLES            
         LA    R4,4(R4,R5)         Point to variables start addr               
DOPARMS  EQU   *
*     * /********************************************************/
*     * /* Uppercase translation of PARMIN                      */
*     * /* - R4 Starting parms address                          */
*     * /* - R6 Parm Length                                     */
*     * /* - R2, R7                   Working Register          */
*     * /********************************************************/
UP#EM    EQU   *
         LR    R2,R4               Start addr - PARMS   
         LR    R7,R6               Length of  - PARMS    
         BCTR  R7,0                Adjust for EXecute
         EX    R7,UPPERCS          Execute Uppercase translate   FUNCT
*UPPERCS  OC    0(0,R2),BLANKS      EBCDIC Lower-Upper Case Translate
*      
.
.
.
.


However, in COBOL, specifically with the version of COBOL compiler supplied with the MVS 3.8J public domain version, the language is limited in comparison to today’s Z/OS COBOL compiler.

What follows is a ‘GUESS’ determination approach, written in COBOL some time ago, to differentiate PARAMETER types for a program executing under TSO or TSO/ISPF.

This program includes COBOL compile and link-edit JCL:

//COBPARM0 JOB (SYS),'Install COBPARM',      <-- Review and Modify
//         CLASS=A,MSGCLASS=X,               <-- Review and Modify
//         MSGLEVEL=(1,1),NOTIFY=&SYSUID     <-- Review and Modify
//*
//* -------------------------------------------------------*
//* *                                                      *
//* *  Compile  Link-edit COBPARM                          *
//* *                                                      *
//* -------------------------------------------------------*
//COBPARM  EXEC COBUCL,CPARM1='LIST,LOAD,NODECK,PMAP,DMAP' 
//COB.SYSPUNCH DD DUMMY
//COB.SYSIN DD *
       IDENTIFICATION DIVISION.
       PROGRAM-ID.             COBPARM.
       AUTHOR.                 Larry Belmontes.
       DATE-WRITTEN.           JULY  2018.                                      
       REMARKS. 
      ******************************************************************        
      *
      *  =============================================================
      *
      *  CCCCC    OOOOO   BBBBBB   PPPPPP    AAAAA   RRRRRR  MM   MM         
      * CC   CC  OO   OO  BB   BB  PP   PP  AA   AA  RR   RR MMM MMM         
      * CC       OO   OO  BB   BB  PP   PP  AA   AA  RR  RR  MMM MMM         
      * CC       OO   OO  BBBBBB   PPPPPP   AAAAAAA  RRRRR   MM M MM         
      * CC       OO   OO  BB   BB  PP       AA   AA  RR RR   MM   MM  
      * CC   CC  OO   OO  BB   BB  PP       AA   AA  RR  RR  MM   MM  
      *  CCCCC    OOOOO   BBBBBB   PP       AA   AA  RR   RR MM   MM  
      *
      *  =============================================================
      * 1234567--1234567--1234567--1234567--1234567--1234567-1234567--
      *
      *  Program: COBPARM 
      *
      *  Author:  Larry Belmontes Jr.
      *           https://ShareABitofIT.net/PARMs-in-MVS38J
      *           Copyright (C) 2018  Larry Belmontes, Jr.
      *
      *  Disclaimer:                                                   
      *  ==============================================================
      *                                                                
      *     No guarantee; No warranty; Install / Use at your own risk. 
      *                                                                
      *     This software is provided "AS IS" and without any expressed
      *  or implied warranties, including, without limitation, the     
      *  implied warranties of merchantability and fitness for a       
      *  particular purpose.                                           
      *                                                                
      *     The author requests keeping authors name intact in any     
      *  modified versions.                                            
      *                                                                
      *     In addition, the author requests readers to submit any     
      *  code modifications / enhancements and associated comments     
      *  for consideration into a subsequent release (giving credit    
      *  to contributor(s)) thus, improving overall functionality      
      *  and further benefiting the MVS 3.8J hobbyist public domain    
      *  community.                                                    
      *                                                                
      *                                                                
       EJECT
      *
      *  Overview:
      *  =============================================================
      *
      *     This program will differentiate between a PARM area or  
      *  COMMAND LINE area.               
      *
      *     This program is written in COBOL using the compiler   
      *  supplied with MVS 3.8J public domain OS.
      *
      *     The software components are:  
      *       - COBPARM   COBOL Program for MVS38J
      *  
      *     See program documentation for more logic detail.
      *  
      *  
      * ---------------------------------------------------------------
      *     Use the following command to start COBPARM from TSO/ISPF 
      *  command line which uses a COMMAND LINE area:          
      *  
      *     TSO COBPARM A PARM 
      *  
      *     Use the following command to start COBPARM from TSO/ISPF 
      *  command line which uses a COMMAND LINE area:          
      *  
      *     TSO ISPEXEC SELECT CMD(COBPARM A PARM)
      *  
      *  
      *     Use the following command to start COBPARM from TSO/ISPF 
      *  command line which uses a PARM area:          
      *  
      *     TSO CALL 'MY.LOAD.PDS(COBPARM)' 'SOME PARM DATA' 
      *  
      *
      *     Use the following command to start COBPARM from TSO/ISPF 
      *  command line which uses a PARM area:          
      *  
      *     TSO ISPEXEC SELECT PGM(COBPARM) PARM(SOME PARM DATA) 
      *  
      *
      *
      *
      *  Enjoy!
      *
      *  Larry Belmontes Jr.
      *
      *
       EJECT
      *
      *  Prerequisite: User Modifications             
      *  ==============================================================
      *
      *     No user-mods are REQUIRED to use this software under       
      *  MVS38J / TSO.                                       
      *
      *     However, if ISPF 2.x (Wally Mclaughlin's ISPF-like product)
      *  is being used on your system, check for any required user     
      *  modifications.
      *
      *     More information on the above user-mods can be obtained
      *  from the ISPF 2.x distribution tape (HET).
      *
      *
      *
      *  COBPARM  Programs / Services:
      *  ==================================================================
      *
      *    1) None                      None               
      *
      *
      *
      *  References:
      *  ==============================================================
      *
      *  - None                                                       
      *
      *
      *  Messages:                       
      *  ==============================================================
      *
      *  +--------+---------------------------------------------------+
      *  |Msg ID  |Description                                        |
      *  +--------+---------------------------------------------------+
      *  |        |None                                               |     
      *  +--------+---------------------------------------------------+
      *
      *
      *
      *  Change History:              
      *  ==============================================================
      *
      *  MM/DD/CCYY Version  Name / Description
      *  ---------- -------  ------------------------------------------
      *
      *  02/11/2019 0.9.00   Larry Belmontes Jr.
      *                      - Initial version released to MVS 3.8J
      *                        hobbyist public domain
      *
      *
      *
      *
       EJECT
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      *                                                                         
      * /********************************************************/
      * /* Program Timestamp                                    */
      * /********************************************************/
       01  WS-PGM-TIMESTAMP.                                          
           05  WS-PROGRAM-ID       PIC X(08)   VALUE 'COBPARM '.
           05  FILLER              PIC X(08)   VALUE 'MVS3.8J '.
           05  WS-PROGRAM-VRM      PIC X(08)   VALUE 'V0.9.00 '.
           05  FILLER              PIC X(08)   VALUE '08072018'.
           05  FILLER              PIC X(02)   VALUE ' '.
           05  WS-COBOL-CTS        PIC X(21)   VALUE SPACES.
           05  FILLER              REDEFINES   WS-COBOL-CTS.
               10  WS-TIMESTAMP    PIC X(08).
      *       'HH.MM.SS'
               10  WS-DATESTAMP    PIC X(12).
      *       'mmm dd, ccyy'
           05  FILLER              PIC X(25)                 
           VALUE  'Copyright (C) 2018'.                                    
           05  FILLER              PIC X(25)                 
           VALUE  'Larry Belmontes, Jr. '.                                      
           05  FILLER              PIC X(50)                 
           VALUE  'https://ShareABitofIT.net/PARMs-in-MVS38J'.
                                                                                
       01  TEXT-L                  PIC S9(04)  COMP.                  
       01  CLPRML                  PIC S9(04)  COMP.                  
       EJECT
        
       LINKAGE SECTION.                                                         
      ************************************************************
      *     
      *    This program can be started from a TSO command line
      *    or SELECT PGM() ISPF service request.              
      *     
      *    The TSO COBPARM PARMDATA uses the form (command line):
      *        2-byte binary length, 2-byte offset, text
      *     
      *    The SELECT PGM(COBPARM) PARM(PARMDATA) uses the form (PARM):
      *        2-byte binary length, text
      *     
      *    Typically, in ASSEMBLER, you test the high-order bit
      *    of Register 1 for X'80'.  If bit is on, it is a PARM
      *    DATA layout.                                        
      *                              
      *    The following COBOL logic is a GUESS approach to determine
      *    the invoking method.
      *     
      ************************************************************
       01  PARM-DATA.
           05  PARM-LEN            PIC S9(04)  COMP.
           05  PARM-DAT            PIC X(35).
            
       01  CMDL-DATA   REDEFINES   PARM-DATA.
           05  CMDL-LEN            PIC S9(04)  COMP.
           05  CMDL-OFF            PIC S9(04)  COMP.
           05  CMDL-DAT            PIC X(33).
           05  FILLER   REDEFINES  CMDL-DAT.
               10  CMDL-DAT-1      PIC X             
                                   OCCURS  33 TIMES.
       EJECT
       PROCEDURE DIVISION USING PARM-DATA.                                
      *
      **   Not available in MVS 3.8J COBOL Compiler.
      **   MOVE WHEN-COMPILED TO WS-COBOL-CTS.
      *                                                                         
      * /********************************************************/
      * /* PARM passed to program?                              */
      * /********************************************************/
           IF PARM-LEN > 0           
      *        /*************************************************/
      *        /* Yes, offset present within range of length?   */
      *        /*************************************************/
               IF (CMDL-OFF > 0)     AND
                  ((CMDL-OFF < PARM-LEN) OR    
                   (CMDL-OFF = PARM-LEN))      
      *            /*********************************************/
      *            /* Yes, assume 'Command Buffer' layout...    */
      *            /* Parms in Command Line?                    */
      *            /*********************************************/
                   IF (CMDL-LEN - 4) > CMDL-OFF
      *                /*********************************************/
      *                /* Yes.                                      */
      *                /*********************************************/
                       DISPLAY 'CMDL Detected' 
                       DISPLAY 'CMDL-LEN="' CMDL-LEN '"' 
                       DISPLAY 'CMDL-OFF="' CMDL-OFF '"' 
                       COMPUTE TEXT-L = CMDL-LEN - 4
                       DISPLAY 'TEXT-L="' TEXT-L '"' 
                       COMPUTE CLPRML = CMDL-LEN - 4 - CMDL-OFF
                       DISPLAY 'CLPRML="' CLPRML '"' 
                       DISPLAY 'CMDL-DAT="' CMDL-DAT '"' 
                   ELSE
      *                /*********************************************/
      *                /* No.                                       */
      *                /*********************************************/
                       DISPLAY 'No CMDL parms detected!'
               ELSE                   
      *            /*********************************************/
      *            /* No, assume 'PARM' layout...               */
      *            /*********************************************/
                   DISPLAY 'PARM Detected' 
                   DISPLAY 'PARM-LEN="' PARM-LEN '"' 
                   DISPLAY 'PARM-DAT="' PARM-DAT '"' 
           ELSE
      *        /*************************************************/
      *        /* NO, no parm passed to program                 */
      *        /*************************************************/
              DISPLAY 'No parm detected!'.
           
       EJECT
      *                                                                       
      * /********************************************************/
      * /* Return to caller                                     */
      * /********************************************************/
           GOBACK.
       EJECT
/*
//LKED.SYSLMOD DD DSN=my.tso.ispf.load(COBPARM),       <-- TARGET
//         DISP=SHR    
//                                                  
            

Below are some use cases to demonstrate COBPARMs ‘GUESS’ approach for parameter layout. Each command is entered into the TSO/ISPF command line.



OPTION  ===> TSO COBPARM
 CMDL Detected            
 CMDL-LEN="0011"          
 CMDL-OFF="0007"          
 TEXT-L="0007"            
 CLPRML="0000"            
 CMDL-DAT="COBPARM                          "
                          
 ***                      

OPTION  ===> TSO COBPARM SOME DATA
 CMDL Detected                               
 CMDL-LEN="0021"                             
 CMDL-OFF="0008"                             
 TEXT-L="0017"                               
 CLPRML="0009"                               
 CMDL-DAT="COBPARM SOME DATA                "
                                             
 ***                                         

OPTION  ===> tso ispexec select pgm(cobparm) parm(some data here)          
 PARM Detected                                 
 PARM-LEN="0014"                               
 PARM-DAT="SOME DATA HERE                     "
                                               
 ***                                           
                                                      
OPTION  ===> tso ispexec select cmd(cobparm some more data) 
 CMDL Detected                               
 CMDL-LEN="0027"                             
 CMDL-OFF="0009"                             
 TEXT-L="0023"                               
 CLPRML="0014"                               
 CMDL-DAT="COBPARM  SOME MORE DATA          "
                                             
 ***                                         
                                             
OPTION  ===> tso call 'my.tso.ispf.loadlib(cobparm)' 'my data passed here'   
 PARM Detected                                  
 PARM-LEN="0019"                                
 PARM-DAT="MY DATA PASSED HERE                " 
                                                
 ***                                            



   Note: TEXT-L is the actual length of CMDL-DAT.
         PARM-L is the actual length of PARM-DAT.



Software Disclaimer

No guarantee; No warranty; Install / Use at your own risk.

This software is provided “AS IS” and without any expressed or implied warranties, including, without limitation, the implied warranties of merchantability and fitness for a particular purpose.

The author requests keeping authors name intact to any modified versions.

In addition, the author requests readers to submit any code modifications / enhancements and associated comments for consideration into a subsequent release (giving credit to contributors) thus, improving overall functionality benefiting the MVS 3.8J hobbyist public domain community.

Closing

I hope you find this post helpful in your overall learnings and use of software in the MVS 3.8J OS environment.

Please use the comment box below or the contact us link on the menu bar to communicate any suggestions, improvements, corrections or issues.

Enjoy,

Larry Belmontes

Leave a Reply

Your email address will not be published. Required fields are marked *


CAPTCHA Image
Reload Image

This site uses Akismet to reduce spam. Learn how your comment data is processed.