Table of Contents Previous Next PDF


Sample IMS Client and Server Transactions

Sample IMS Client and Server Transactions
Oracle Tuxedo Mainframe Adapter for TCP (IMS) (hereafter referenced as TMA TCP for IMS) client and server transactions are ordinary IMS MPP transactions, and when running the Oracle TMA TCP for IMS gateway as an OTMA client, FastPath transactions as well. Transactions can be written in any application programming language supported by IMS. Source code for the sample transactions in this document can be found in the Oracle TMA TCP for IMS SOURCE distribution library. The following sample transactions are provided in this document:
IMS Server Transaction
An IMS server transaction offers a specified service and processes client requests for that service. A server request takes place according to the following sequence of events.
1.
A client transaction running on a remote system makes a request for a service offered by the IMS gateway. The remote gateway forwards the request to the IMS gateway, which formats and inserts a server request message indirectly through OTMA. The server request message is destined for the IMS server transaction that offers the service.
2.
3.
BEASVR01 - A Sample IMS Server Transaction
Listing E‑1 is a simple echo transaction; that is, it simply returns a response consisting of whatever request data it received.
Listing E‑1 Sample IMS Server Transaction
CBL APOST *****************************************************************
FILE: BEASVR01
PURPOSE: SAMPLE IMS SERVER TRANSACTION FOR USE WITH
BEA TMA TCP FOR IMS
COMMENTS: THIS IS A SIMPLE ECHO SERVER TRANSACTION THAT ISSUES A
RESPONSE CONSISTING OF THE SAME DATA AS RECEIVED.
LANGUAGE: COBOL
COPYRIGHT (C) 1997 BEA SYSTEMS, INC. ALL RIGHTS RESERVED
*****************************************************************

IDENTIFICATION DIVISION.
PROGRAM-ID. BEASVR01.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-370.
OBJECT-COMPUTER. IBM-370.
DATA DIVISION.
WORKING-STORAGE SECTION.

77 GU PIC X(04) VALUE 'GU '.
77 CHNG PIC X(04) VALUE 'CHNG'.
77 ISRT PIC X(04) VALUE 'ISRT'.
77 PURG PIC X(04) VALUE 'PURG'.

01 BEAGW PIC X(08) VALUE 'BEATCPI '.


*****************************************************************
* REQUEST MESSAGE *
*****************************************************************
01 REQUEST-MESSAGE.
(1) COPY SERVER.
05 USER-DATA PIC X(512).
*****************************************************************
* RESPONSE MESSAGE *
*****************************************************************
01 REQUEST-MESSAGE.
(1) COPY SERVER.
05 USER-DATA PIC X(512).
LINKAGE SECTION.
****************************************************************
* I/O PCB *
****************************************************************
01 01 IOPCB.
05 LTERM PIC X(08).
05 FILLER PIC X(02).
05 IOPCB-STATUS PIC X(02).
05 FILLER PIC X(28).
*****************************************************************

PROCEDURE DIVISION.
ENTRY 'DLITCBL' USING IOPCB, ALTPCB.
PERFORM IOPCB-GET THRU IOPCB-GET-EXIT.
PERFORM ECHO-MSG THRU ECHO-MSG-EXIT.
PERFORM ISRT-MSG THRU ISRT-MSG-EXIT.
GO TO 9999-RETURN.

*****************************************************************
* RETRIEVE THE REQUEST MESSAGE FROM THE IMS QUEUE *
*****************************************************************
IOPCB-GET.
(2) CALL 'CBLTDLI' USING GU, IOPCB, REQUEST-MESSAGE.
IF IOPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

IOPCB-GET-EXIT.
EXIT.
*****************************************************************
*
COMPOSE THE RESPONSE MESSAGE *
*****************************************************************
ECHO-MSG.
* THE RESPONSE MESSAGE HAS THE SAME BASIC FORMAT AS
* THE REQUEST MESSAGE. WE CHANGE THE TRAN CODE TO THAT
* OF THE DESTINATION. NOTE THAT THE FIELD
* BEA-RESERVED MUST BE COPIED INTACT FROM THE
* REQUEST MESSAGE TO THE RESPONSE MESSAGE. FOR RE-
* SPONSE DATA, WE SIMPLY RETURN THE REQUEST DATA.
* HENCE THIS IS AN ECHO TRANSACTION.

(3) MOVE REQUEST-MESSAGE TO RESPONSE-MESSAGE.
(4,6) MOVE BEAGW TO TRAN-CODE IN RESPONSE-MESSAGE.

ECHO-MSG-EXIT.
EXIT.
*****************************************************************
* INSERT RESPONSE MESSAGE TO IMS QUEUE *
*****************************************************************
ISRT-MSG.
* (5) CALL 'CBLTDLI' USING ISRT, IOPCB, RESPONSE-MESSAGE.
IF IOPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.
ISRT-MSG-EXIT.
EXIT.
*****************************************************************
* INSERT RESPONSE MESSAGE TO ALTERNATE PCB *
*****************************************************************
PCB-ISRT.
9999-RETURN.
GOBACK.
 
Notes
1.
The format of the Oracle TMA TCP for IMS server request/response message header is supplied by a COBOL copybook, SERVER. The equivalent C language header is provided by the BEATCPI.H header file. Both are available in the Oracle TMA TCP for IMS INCLUDE distribution library.
2.
A GU (Get Unique) call is issued to retrieve the request message from the IMS message queue. A server request message is always formatted as a single message segment, so a GN (Get Next) call is not strictly required.
3.
The USER-DATA (user-defined request data) is simply copied from the request message to the response message.
4.
The TRAN-CODE in the response message is set to that of the Oracle TMA TCP for IMS (in this example, BEAGW="BEATCPI”; the name may be different in your installation).
5.
An ISRT (Insert) call is issued to insert the message into the IMS message queue, returning the response to Oracle TMA TCP for IMS.
6.
IMS Client Transactions
An IMS client transaction is one that issues a request for a specified remote service made available through Oracle TMA TCP for IMS. IMS client requests (unlike server requests) are processed in two distinct “phases”: a request phase, followed by a response phase. The request and response must be processed by two separate transaction executions (for example, T1 and T2).
Request Phase
A client request takes place according to the following scenario.
1.
The request transaction, T1, issues a request for a service provided by a remote gateway by inserting a client request message into the IMS message queue. The client request message is destined for TMA TCP for IMS, and must specify the name (transaction code) of a response transaction (T2).
2.
Response Phase
A client response takes place according to the following scenario.
1.
When the response (if required) is received, a client response message is formatted and inserted directly into the IMS message queue. If running the OTMA client, the response is placed into the IMS message queue indirectly through the OTMA interface. The client response message is destined for the specified response transaction (T2).
2.
BEACRQ01 - A Sample IMS Client Request Transaction
The following sample IMS client request transaction makes a request for a service called TOUPPER, provided by a remote system. The TOUPPER service returns a response consisting of the request data translated to uppercase.
Listing E‑2 Sample IMS Client Request Transaction
CBL APOST
IDENTIFICATION DIVISION.
PROGRAM-ID. BEACRQ01.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-370.
OBJECT-COMPUTER. IBM-370.
DATA DIVISION.
WORKING-STORAGE SECTION.

77 GU PIC X(04) VALUE 'GU '.
77 CHNG PIC X(04) VALUE 'CHNG'.
77 ISRT PIC X(04) VALUE 'ISRT'.
77 PURG PIC X(04) VALUE 'PURG'.

01 MSG-IN.
05 MI-LL PIC S9(04) COMP VALUE +0.
05 MI-ZZ PIC S9(04) COMP VALUE +0.
05 MI-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 MI-AREA. PIC X(91) VALUE SPACES.
10 MI-DATA

(1) 01 CLIENT-REQUEST.
05 CRR-LL PIC 9(04) COMP VALUE 0.
05 CRR-ZZ PIC 9(04) COMP VALUE 0.
05 CRR-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 BEA-RESERVED-1 PIC X(03) VALUE LOW-VALUES.
05 CRR-HEADER-LEN PIC 9(08) COMP.
05 CRR-CONTEXT-DATA-LEN PIC 9(08) COMP.
05 CRR-REQUEST-DATA-LEN PIC 9(08) COMP.
05 CRR-MAX-RESPONSE-LEN PIC 9(08) COMP.
05 CRR-REQUEST-TYPE PIC 9(08) COMP.
05 CRR-RESPONSE-FORMAT PIC 9(08) COMP.
05 CRR-ERROR-CODE PIC 9(08) COMP.
05 CRR-REASON-CODE PIC 9(08) COMP.
05 CRR-SERVICE-NAME PIC X(16) VALUE LOW-VALUES.
05 CRR-RESPONSE-TRAN PIC X(08) VALUE LOW-VALUES.
05 CRR-ORIGIN-TERMINAL PIC X(08) VALUE LOW-VALUES.
05 BEA-RESERVED-2 PIC X(16) VALUE LOW-VALUES.
05 CRR-CONTEXT-AREA.
10 CRR-CONTEXT-DATA PIC X(31) VALUE SPACES.
05 CRR-REQUEST-AREA.
10 CRR-REQUEST-DATA PIC X(100) VALUE SPACES.

LINKAGE SECTION.
01 IOPCB.
05 LTERM PIC X(08).
05 FILLER PIC X(02).
05 IOPCB-STATUS PIC X(02).
05 FILLER PIC X(28).
01 ALTPCB.
05 ALTPCB-DEST PIC X(08).
05 FILLER PIC X(02).
05 ALTPCB-STATUS PIC X(02).
05 FILLER PIC X(10).

PROCEDURE DIVISION.
ENTRY 'DLITCBL' USING IOPCB, ALTPCB.

(2) CALL 'CBLTDLI' USING GU, IOPCB, MSG-IN.
IF IOPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(3) MOVE 'BEATCPI' TO CRR-TRANCODE.
MOVE 96 TO CRR-HEADER-LEN.
MOVE 1 TO CRR-REQUEST-TYPE.
MOVE 0 TO CRR-RESPONSE-FORMAT.
MOVE LTERM TO CRR-ORIGIN-TERMINAL.
MOVE 'TOUPPER' TO CRR-SERVICE-NAME.
MOVE 'BEACRP01' TO CRR-RESPONSE-TRAN.
MOVE ALL 'A' TO CRR-REQUEST-DATA.
MOVE LENGTH OF CRR-REQUEST-AREA TO
CRR-REQUEST-DATA-LEN.
MOVE CRR-REQUEST-DATA-LEN TO CRR-MAX-RESPONSE-LEN.

(4) MOVE ALL 'B' TO CRR-CONTEXT-DATA.
MOVE LENGTH OF CRR-CONTEXT-AREA TO CRR-CONTEXT-DATA-LEN.

(5) COMPUTE CRR-LL = CRR-REQUEST-DATA-LEN +
CRR-CONTEXT-DATA-LEN +
CRR-HEADER-LEN.

(6) CALL 'CBLTDLI' USING CHNG, ALTPCB, CRR-TRANCODE.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(7) CALL 'CBLTDLI' USING ISRT, ALTPCB, CLIENT-REQUEST.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(8) CALL 'CBLTDLI' USING PURG, ALTPCB.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(9) 9999-RETURN.

GOBACK.
 
Notes
1.
Although not used in the previous example, the format of the TMA TCP for IMS client request/response message header is supplied by a COBOL copybook, CLIENT. The equivalent C language header is provided by the BEATCPI.H header file. Both are available in the TMA TCP for IMS INCLUDE distribution library.
2.
A GU (Get Unique) call is issued to retrieve the terminal input message from the IMS message queue.
3.
CRR-TRANCODE is set to the transaction code of the TMA TCP for IMS gateway (in this example, “BEATCPI”; the name may be different in your installation).
BEA-RESERVED-1 must be initialized to binary zero.
CRR-HEADER-LEN is set to the length of the client request header (96 bytes).
CRR-REQUEST-TYPE is set to 1, specifying that a response is required.
CRR-RESPONSE-FORMAT is set to 0, specifying that the response is to be returned as a single message segment.
CRR-ORIGIN-TERMINAL is set to the name of the requesting terminal (LTERM), obtained from the IOPCB.
CRR-SERVICE-NAME is set to the name of the service being requested (“TOUPPER”). This name must be the name of the service as locally defined to TMA TCP for IMS. This name may (or may not) be the same as the name of the service as defined on the remote system which offers the service.
CRR-RESPONSE-TRAN is set to the name of the designated response transaction (“BEACRP01”).
CRR-REQUEST-DATA-LEN is set to the length of user-defined request data being sent.
CRR-MAX-RESPONSE-LEN is set to the maximum amount of response data that can be accommodated.
BEA-RESERVED-2 must be initialized to binary zero.
4.
CRR-CONTEXT-DATA-LEN is set to the length of any user-defined context data included.
5.
The length of the message segment (LL) is set to the overall length of the client request message (header + context data + request data).
6.
A CHNG (Change) call is issued to set the destination to the transaction code of the TMA TCP for IMS gateway (in this example, “BEATCPI”; the name may be different in your installation).
7.
An ISRT (Insert) call is issued to insert the client request message into the IMS message queue. Although the client request message is formatted as a single message segment in this example, the client request message may be formatted as multiple message segments, if desired.
8.
A PURG call is issued to signal that the message is complete; for example, there are no additional message segments.
9.
BEACRP01 - A Sample IMS Client Response Transaction
The following sample IMS client response transaction processes the response from a request for a service called TOUPPER, provided by a remote system. The TOUPPER service returns a response consisting of the request data translated to uppercase.
Listing E‑3 Sample IMS Response Transaction
CBL APOST
IDENTIFICATION DIVISION.
PROGRAM-ID. BEACRP01.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-370.
OBJECT-COMPUTER. IBM-370.
DATA DIVISION.

WORKING-STORAGE SECTION.
77 GU PIC X(04) VALUE 'GU'.
77 CHNG PIC X(04) VALUE 'CHNG'.
77 ISRT PIC X(04) VALUE 'ISRT'.
77 PURG PIC X(04) VALUE 'PURG'.

1 MSG-OUT.
05 MO-LL PIC S9(04) COMP VALUE +0.
05 MO-ZZ PIC S9(04) COMP VALUE +0.
05 MO-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 MO-AREA
10 MO-DATA PIC X(91) VALUE SPACES.
(1) 01 CLIENT-RESPONSE.
05 CRR-LL PIC 9(04) COMP VALUE 0.
05 CRR-ZZ PIC 9(04) COMP VALUE 0.
05 CRR-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 BEA-RESERVED-1 PIC X(03) VALUE LOW-VALUES.
05 CRR-HEADER-LEN PIC 9(08) COMP.
05 CRR-CONTEXT-DATA-LEN PIC 9(08) COMP.

(7) 05 CRR-RESPONSE-DATA-LEN PIC 9(08) COMP.
(7) 05 CRR-MAX-RESPONSE-LEN PIC 9(08) COMP.
05 CRR-REQUEST-TYPE PIC 9(08) COMP.
(3) 05 CRR-RESPONSE-FORMAT PIC 9(08) COMP.
05 CRR-ERROR-CODE PIC S9(08) COMP.
05 CRR-REASON-CODE PIC S9(08) COMP.
05 CRR-SERVICE-NAME PIC X(16) VALUE LOW-VALUES.
05 CRR-RESPONSE-TRAN PIC X(08) VALUE LOW-VALUES.
05 CRR-ORIGIN-TERMINAL PIC X(08) VALUE LOW-VALUES.
05 BEA-RESERVED-2 PIC X(16) VALUE LOW-VALUES.
(6) 05 CRR-CONTEXT-AREA.
10 CRR-CONTEXT-DATA PIC X(31) VALUE SPACES.
05 CRR-RESPONSE-AREA.
10 CRR-RESPONSE-DATA PIC X(100) VALUE SPACES.

LINKAGE SECTION.

01 IOPCB.
05 LTERM PIC X(08).
05 FILLER PIC X(02).
05 IOPCB-STATUS PIC X(02).
05 FILLER PIC X(28).
01 ALTPCB
05 ALTPCB-DEST PIC X(08).
05 FILLER PIC X(02).
05 ALTPCB-STATUS PIC X(02).
05 FILLER PIC X(10).
01 IOPCB.

PROCEDURE DIVISION.
ENTRY 'DLITCBL' USING IOPCB, ALTPCB.

(2) CALL 'CBLTDLI' USING GU, IOPCB, CLIENT-RESPONSE.
IF IOPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(4) IF CRR-ERROR-CODE EQUAL 0 AND

(5) CRR-REASON-CODE EQUAL 0
THEN MOVE 'PASSED' TO MO-DATA
ELSE MOVE 'FAILED' TO MO-DATA.
MOVE CRR-TRANCODE TO MO-TRANCODE.
MOVE 84 TO MO-LL.

CALL 'CBLTDLI' USING CHNG, ALTPCB, CRR-ORIGIN-TERMINAL.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

(8) CALL 'CBLTDLI' USING ISRT, ALTPCB, MSG-OUT.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

CALL 'CBLTDLI' USING PURG, ALTPCB.
IF ALTPCB-STATUS NOT = SPACES
GO TO 9999-RETURN.

9999-RETURN.

GOBACK.
 
Notes
1.
Although not used in the previous example, the format of the TMA TCP for IMS client request/response message header is supplied by a COBOL copybook, CLIENT. The equivalent C language header is provided by the BEATCPI.H header file. Both are available in the TMA TCP for IMS INCLUDE distribution library.
2.
A GU (Get Unique) call is issued to retrieve the client response message from the IMS message queue.
3.
CRR-RESPONSE-FORMAT indicates the response format: single segment or multiple-segment, as specified in the original request. If multi-segment response format is specified, the response message consists of three segments: response header, context data, and response data.
4.
CRR-ERROR-CODE indicates whether or not an error occurred. If this field is zero, it indicates that the request was successfully processed. Otherwise, an error occurred and the error code identifies the type of error. The error code should always be checked before processing a response.
5.
CRR-REASON-CODE may provide additional information when an error is indicated. A value of zero indicates that no additional information is available.
6.
7.
CRR-RESPONSE-DATA-LEN contains the length of any response data returned. However, if a truncation error occurred, this field contains the actual (pretruncated) length of the response data. The amount of response data returned is truncated to the length specified by CRR-MAX-RESPONSE-LEN.
8.
A response indicating success or failure (based on the error and reason codes) is written to the original (requesting) terminal, using the LTERM preserved in CRR-ORIGIN-TERMINAL. Note that a modifiable, alternate PCB must be used for this purpose.
BEACRR01 - A Sample IMS Client Request/Response Transaction
If desired, the functionality of the IMS client request and response transactions can be combined into a single application transaction. However, logic must be added to perform the appropriate (request or response) processing based upon the dynamic execution context.
Listing E‑4 Sample IMS Request/Response Transaction
CBL APOST
IDENTIFICATION DIVISION.
PROGRAM-ID. BEACRR01.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-370.
OBJECT-COMPUTER. IBM-370.
DATA DIVISION.
WORKING-STORAGE SECTION.

77 GU PIC X(04) VALUE 'GU '.
77 CHNG PIC X(04) VALUE 'CHNG'.
77 ISRT PIC X(04) VALUE 'ISRT'.
77 PURG PIC X(04) VALUE 'PURG'.

01 MSG-IN.
05 MI-LL PIC S9(04) COMP VALUE +0.
05 MI-ZZ PIC S9(04) COMP VALUE +0.
05 MI-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 MI-AREA.
10 MI-DATA PIC X(91) VALUE SPACES.
01 MSG-OUT.
05 MO-LL PIC S9(04) COMP VALUE +0.
05 MO-ZZ PIC S9(04) COMP VALUE +0.
05 MO-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 MO-AREA.
10 MO-DATA PIC X(91) VALUE SPACES.

(1) 01 CLIENT-REQUEST-RESPONSE.
05 CRR-LL PIC 9(04) COMP VALUE 0.
05 CRR-ZZ PIC 9(04) COMP VALUE 0.
05 CRR-TRANCODE PIC X(08) VALUE SPACES.
05 FILLER PIC X(01) VALUE SPACES.
05 BEA-RESERVED-1 PIC X(03) VALUE LOW-VALUES.
05 CRR-HEADER-LEN PIC 9(08) COMP.
05 CRR-CONTEXT-DATA-LEN PIC 9(08) COMP.
05 CRR-REQUEST-DATA-LEN PIC 9(08) COMP.
05 CRR-MAX-RESPONSE-LEN PIC 9(08) COMP.
05 CRR-REQUEST-TYPE PIC 9(08) COMP.
05 CRR-RESPONSE-FORMAT PIC 9(08) COMP.
05 CRR-ERROR-CODE PIC 9(08) COMP.
05 CRR-REASON-CODE PIC 9(08) COMP.
05 CRR-SERVICE-NAME PIC X(16) VALUE LOW-VALUES.
05 CRR-RESPONSE-TRAN PIC X(08) VALUE LOW-VALUES.
05 CRR-ORIGIN-TERMINAL PIC X(08) VALUE LOW-VALUES.
05 BEA-RESERVED-2 PIC X(16) VALUE LOW-VALUES.
05 CRR-CONTEXT-AREA.
10 CRR-CONTEXT-DATA PIC X(31) VALUE SPACES.
05 CRR-REQUEST-AREA.
10 CRR-REQUEST-DATA PIC X(100) VALUE SPACES.

LINKAGE SECTION.
01 IOPCB.
05 LTERM PIC X(08).
05 FILLER PIC X(02).
05 IOPCB-STATUS PIC X(02).
05 FILLER PIC X(28).
01 01 ALTPCB.
05 ALTPCB-DEST PIC X(08).
05 FILLER PIC X(02).
05 ALTPCB-STATUS PIC X(02).
05 FILLER PIC X(10).

PROCEDURE DIVISION.
ENTRY 'DLITCBL' USING IOPCB, ALTPCB.
(3) IF LTERM = SPACES OR LOW-VALUES
THEN PERFORM RESPONSE-MESSAGE THRU RESPONSE-MESSAGE-EXIT
ELSE PERFORM REQUEST-MESSAGE THRU REQUEST-MESSAGE-EXIT.

9999-RETURN.
GOBACK.

REQUEST-MESSAGE.
CALL 'CBLTDLI' USING GU, IOPCB, MSG-IN.
IF IOPCB-STATUS NOT = SPACES
GO TO REQUEST-MESSAGE-EXIT.

MOVE 'BEATCPI' TO CRR-TRANCODE.
MOVE 96 TO CRR-HEADER-LEN.
MOVE 1 TO CRR-REQUEST-TYPE.
MOVE 0 TO CRR-RESPONSE-FORMAT.
MOVE LTERM TO CRR-ORIGIN-TERMINAL.
MOVE 'TOUPPER' TO CRR-SERVICE-NAME.
MOVE MI-TRANCODE TO CRR-RESPONSE-TRAN.
MOVE ALL 'A' TO CRR-REQUEST-DATA.
MOVE LENGTH OF CRR-REQUEST-AREA TO CRR-REQUEST-DATA-LEN.
MOVE CRR-REQUEST-DATA-LEN TO CRR-MAX-RESPONSE-LEN.
MOVE ALL 'B' TO CRR-CONTEXT-DATA.
MOVE LENGTH OF CRR-CONTEXT-AREA TO CRR-CONTEXT-DATA-LEN.
COMPUTE CRR-LL = CRR-REQUEST-DATA-LEN +
CRR-CONTEXT-DATA-LEN +
CRR-HEADER-LEN.

CALL 'CBLTDLI' USING CHNG, ALTPCB, CRR-TRANCODE.
IF ALTPCB-STATUS NOT = SPACES
GO TO REQUEST-MESSAGE-EXIT.

CALL 'CBLTDLI' USING ISRT, ALTPCB,CLIENT-REQUEST-RESPONSE.
IF ALTPCB-STATUS NOT = SPACES
GO TO REQUEST-MESSAGE-EXIT.

CALL 'CBLTDLI' USING PURG, ALTPCB.
IF ALTPCB-STATUS NOT = SPACES
GO TO REQUEST-MESSAGE-EXIT.

REQUEST-MESSAGE-EXIT.
EXIT.

RESPONSE-MESSAGE.

CALL 'CBLTDLI' USING GU, IOPCB, CLIENT-REQUEST-RESPONSE.
IF IOPCB-STATUS NOT = SPACES
GO TO RESPONSE-MESSAGE-EXIT.
IF CRR-ERROR-CODE EQUAL 0 AND
CRR-REASON-CODE EQUAL 0
THEN MOVE 'PASSED' TO MO-DATA
ELSE MOVE 'FAILED' TO MO-DATA.
MOVE CRR-TRANCODE TO MO-TRANCODE.
MOVE 84 TO MO-LL.

CALL 'CBLTDLI' USING CHNG, ALTPCB, CRR-ORIGIN-TERMINAL.
IF ALTPCB-STATUS NOT = SPACES
GO TO RESPONSE-MESSAGE-EXIT.

CALL 'CBLTDLI' USING ISRT, ALTPCB, MSG-OUT.
IF ALTPCB-STATUS NOT = SPACES
GO TO RESPONSE-MESSAGE-EXIT.

CALL 'CBLTDLI' USING PURG, ALTPCB.
IF ALTPCB-STATUS NOT = SPACES
GO TO RESPONSE-MESSAGE-EXIT.

RESPONSE-MESSAGE-EXIT.
EXIT.
 
Notes
1.
Although not used in the previous example, the format of the TMA TCP for IMS client request/response message header is supplied by a COBOL copybook, CLIENT. The equivalent C language header is provided by the BEATCPI.H header file. Both are available in the TMA TCP for IMS INCLUDE distribution library.
2.
3.

Copyright © 1994, 2017, Oracle and/or its affiliates. All rights reserved.