|
Passing Parameters |
|
|
* -------------------------------------------------------------
*
IDENTIFICATION DIVISION.
* ------------------------------------------------------------- *
PROGRAM-ID. COBPASS.
* ------------------------------------------------------------- *
ENVIRONMENT DIVISION.
* ------------------------------------------------------------- *
DATA DIVISION.
* ------------------------------------------------------------- *
WORKING-STORAGE SECTION.
* ------------------------------------------------------------- *
*
* W00 - General work fields
*
01 W00-RC PIC S9(04) BINARY VALUE ZERO.
*
* W02 - Data fields derived from the PARM field
*
01 W02-QMGR PIC X(48) VALUE SPACES.
01 W02-QUEUE PIC X(48) VALUE SPACES.
* ------------------------------------------------------------- *
LINKAGE SECTION.
* ------------------------------------------------------------- *
01 PARMDATA.
05 PARM-LEN PIC S9(03) BINARY.
05 PARM-STRING PIC X(100).
*
* ------------------------------------------------------------- *
PROCEDURE DIVISION USING PARMDATA.
* ------------------------------------------------------------- *
A-MAIN SECTION.
* ------------------------------------------------------------- *
*
* If no data was passed, display a message and exit rc=16
*
IF PARM-LEN = 0 THEN
DISPLAY 'No parms passed to program'
MOVE '16' TO W00-RC
GO TO A-MAIN-END
END-IF.
*
* Separate into the relevant fields any data passed in the
* PARM statement
*
UNSTRING PARM-STRING DELIMITED BY ALL ','
INTO W02-QMGR
W02-QUEUE.
DISPLAY 'Queue manager name passed = ' W02-QMGR.
IF W02-QUEUE = SPACES THEN
DISPLAY 'No queue name passed to program'
MOVE '16' TO W00-RC
GO TO A-MAIN-END
END-IF.
DISPLAY 'Queue name passed = ' W02-QUEUE.
A-MAIN-END.
*
* Set the return code
*
MOVE W00-RC to RETURN-CODE.
STOP RUN.
|
To avoid the need to change code as it gets rolled out from development
through to production it is recommended that the name of the target Queue
manager and target queue(s) be passed to the program via the EXEC DD card
rather than be hardcoded into the program.
The code supplied here demonstrates how to do this via a COBOL program.
A copy of this 'program' is available here.
|
|
|
| |
|
Obtaining Job Information |
|
|
* -------------------------------------------------------------
*
IDENTIFICATION DIVISION.
* ------------------------------------------------------------- *
PROGRAM-ID. JOBINFO.
* ------------------------------------------------------------- *
ENVIRONMENT DIVISION.
* ------------------------------------------------------------- *
DATA DIVISION.
* ------------------------------------------------------------- *
WORKING-STORAGE SECTION.
01 JOB-NAME PIC X(8).
01 PROGRAM-NAME PIC X(8).
01 STEP-NAME PIC X(8).
01 LPAR-NAME PIC X(8).
01 JOB-NUMBER PIC X(8).
01 USER-ID PIC X(8).
* ------------------------------------------------------------- *
LINKAGE SECTION.
* ------------------------------------------------------------- *
01 CVT-ADRS USAGE IS POINTER.
01 PSA.
05 FILLER PIC X(16).
05 CVTADDR POINTER.
05 FILLER PIC X(520).
05 PSATOLD POINTER.
05 FILLER PIC X(4).
05 PSAAOLD POINTER.
01 TCB.
05 FILLER PIC X(12).
05 TCBTIO POINTER.
05 FILLER PIC X(164).
05 TCBJSCBB POINTER.
01 TIOT.
05 TIOCNJOB PIC X(8).
05 TIOCSTPN PIC X(8).
01 JSCB.
05 FILLER PIC X(316).
05 SSIBPNTR POINTER.
05 FILLER PIC X(40).
05 JSCBPGMN PIC X(8).
01 SSIB.
05 FILLER PIC X(12).
05 SSJOBNUM PIC X(8).
01 CVT.
05 FILLER PIC X(140).
05 ECVTPNTR POINTER.
01 ECVT.
05 FILLER PIC X(344).
05 ECVTLPAR PIC X(8).
01 ASCB.
05 FILLER PIC X(108).
05 ASCBASXB POINTER.
01 ASXB.
05 FILLER PIC X(200).
05 ASXBSENV POINTER.
01 ACEE.
05 FILLER PIC X(21).
05 USERID PIC X(8).
* ------------------------------------------------------------- *
PROCEDURE DIVISION.
* ------------------------------------------------------------- *
A-MAIN SECTION.
* ------------------------------------------------------------- *
* Address PSA
SET ADDRESS OF PSA TO NULL
* Address CVT
SET ADDRESS OF CVT TO CVTADDR.
* Address ECVT
SET ADDRESS OF ECVT TO ECVTPNTR.
MOVE ECVTLPAR TO LPAR-NAME
* Address TCB
SET ADDRESS OF TCB TO PSATOLD
* Address TIOT
SET ADDRESS OF TIOT TO TCBTIO
MOVE TIOCNJOB TO JOB-NAME
MOVE TIOCSTPN TO STEP-NAME
* Address JSCB
SET ADDRESS OF JSCB TO TCBJSCBB
SET ADDRESS OF SSIB TO SSIBPNTR
MOVE JSCBPGMN TO PROGRAM-NAME
* Address ASCB
SET ADDRESS OF ASCB TO PSAAOLD IN PSA.
SET ADDRESS OF ASXB TO ASCBASXB IN ASCB.
SET ADDRESS OF ACEE TO ASXBSENV IN ASXB.
MOVE USERID TO USER-ID.
SET ADDRESS OF SSIB TO SSIBPNTR
MOVE SSJOBNUM TO JOB-NUMBER
MOVE ECVTLPAR TO LPAR-NAME
DISPLAY 'JOB NAME = ' JOB-NAME
DISPLAY 'STEP NAME = ' STEP-NAME
DISPLAY 'PROGRAM NAME = ' PROGRAM-NAME
DISPLAY 'JOB NUMBER = ' JOB-NUMBER
DISPLAY 'Running on = ' LPAR-NAME
DISPLAY 'Userid = ' USER-ID
STOP RUN.
|
This code demonstrates how to gather system information from within a Cobol program.
The code really doesn't do anything useful but it serves as an example of how to navigate down
system control blocks and extract information from within them.
To see what information is
maintained with system control blocks you will need to see the IBM documentation.
Getting the LPAR name of the system that the program is running on will allow the program to take decisions based upon it.
For example if the
program is running on a development LPAR then you may want to write trace messages or take a
different logic flow based on the LPAR.
A copy of this 'program' is available here.
The code has now been altered to include displaying the USERID of the user that is running the program.
The changed line are displayed in red.
The link to the program above has the new changes coded.
|
|
|
| |
|
Listing All DDNAMEs |
|
|
Link to DDLISTR text file
|
This code takes the JOBINFO program as is basis and adds the ability to report the DDNAMEs used by
the program along with the associated dataset name.
The program is fairly worthless as it stands but it does demonstrate how to access z/OS control blocks.
A copy of this program is available here.
|
|
|
| |
|
Display Userid of User Running a Program |
|
|
* -------------------------------------------------------------
*
IDENTIFICATION DIVISION.
* ------------------------------------------------------------- *
PROGRAM-ID. USERID.
* ------------------------------------------------------------- *
ENVIRONMENT DIVISION.
* ------------------------------------------------------------- *
DATA DIVISION.
* ------------------------------------------------------------- *
WORKING-STORAGE SECTION.
* ------------------------------------------------------------- *
01 USER-IDENT PIC X(8).
* ------------------------------------------------------------- *
LINKAGE SECTION.
* ------------------------------------------------------------- *
01 CVT-ADRS USAGE IS POINTER.
01 PSA.
05 FILLER PIC X(16).
05 CVTADDR POINTER.
05 FILLER PIC X(520).
05 PSATOLD POINTER.
05 FILLER PIC X(4).
05 PSAAOLD POINTER.
01 ASCB.
05 FILLER PIC X(108).
05 ASCBASXB POINTER.
01 ASXB.
05 FILLER PIC X(200).
05 ASXBSENV POINTER.
01 ACEE.
05 FILLER PIC X(21).
05 USERID PIC X(8).
* ------------------------------------------------------------- *
PROCEDURE DIVISION
* ------------------------------------------------------------- *
A-MAIN SECTION.
* ------------------------------------------------------------- *
* Address PSA
SET ADDRESS OF PSA TO NULL.
* Address ASCB
SET ADDRESS OF ASCB TO PSAAOLD IN PSA.
SET ADDRESS OF ASXB TO ASCBASXB IN ASCB.
SET ADDRESS OF ACEE TO ASXBSENV IN ASXB.
DISPLAY 'Userid = ' USER-ID
STOP RUN.
|
TThis little program demonstrates how to obtain the USERID of the person that submitted the job that is running the program
This code can be useful if, for example, you want to build a dataset under the users logon id from within the program.
A copy of this program is available here.
|
|