![]() ![]() ![]() ![]() ![]() ![]() ![]() |
The following subsections identify issues that CICS programmers should be aware of when they develop or modify application programs that operate with BEA Tuxedo Mainframe Adapter for TCP (CICS) (hereafter referenced as TMA TCP for CICS):
The following sections identify issues that CICS programers should be aware of when they develop or modify application programs that interoperate with TMA TCP for CICS as clients.
To make requests to remote BEA Tuxedo domains from CICS application programs, use the EXEC CICS LINK
command. The exact layout of the request/response data area is discussed in a later section.
The layout of the data buffer sent between CICS and BEA Tuxedo should be agreed upon by the CICS applications programmer, the BEA Tuxedo applications developer, and the BEA Tuxedo administrator to ensure consistency and proper configuration. There are no limitations on the CICS programmer concerning native COBOL or C data types.
To make a service call from a CICS program to a remote BEA Tuxedo domain, make an EXEC CICS LINK
call to the Pre-requester. The service you want to access must be configured by the BEA TMA Administrator, but from a programming point of view the LINK
call is all you need. The following COBOL record is in the COBOL copybook client.cbl
.
01 REQUEST-RECORD.
05 REQUEST-HEADER.
10 DATALEN PIC S9(08) COMP.
10 SVCNAME[16] PIC X(16).
10 REQUESTCD PIC S9(08) COMP.
10 RETURNCD PIC S9(08) COMP.
10 REQRETURNCD PIC S9(08) COMP.
05 REQUEST-DATA.
10 DATA-AREA PIC X(DATALEN).
The layout of the structure in C that must be passed in the LINK
call is shown in
Listing 5-2. The following C structures are in the clienth.h
INCLUDE
file.
typedef struct CLIENTHDR
{
long DataLen; /* THE LEN OF THE DATA FROM AND TO APPL */
char SvcName[16]; /* THE SERVICE NAME */
long RequestCd; /* THE REQUEST COMMAND FROM THE APPL */
long ReturnCd; /* THE RETURN CODE TO THE APPL */
long ReqReturnCd; /* THE RETURN CODE FROM THE PREQ AND REQ */
} CLIENTHDR;
typedef struct CMAREA
{
CLIENTHDR CltHdr; /*HEADER */
char Request_data[MAX_DATA_LENGTH]; /* REQUEST DATA */
} CMAREA;
The variables in the previous COBOL and C examples are defined as follows.
DataLen
SvcName
RequestCd
BEA_REQUEST_NORESPONSE
- Value is 7. A No Reply Service Request. In this case the request is sent over to BEA Tuxedo for the service to be performed, but no response data is sent back.
BEA_REQUEST_RESPONSE
- Value is 5. A Request/Response Request. A request is sent to BEA Tuxedo and a response is expected back.
ReturnCd
Note: | For a complete description of these codes, refer to the Codes Returned to a CICS Client Program section in Appendix A. |
ReqReturnCd
Request_data
The following sample is an example of a COBOL CICS client program.
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTCLN.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-3090.
OBJECT-COMPUTER. IBM-3090.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER PIC X(32) VALUE 'SAMPLE COBOL CICS CLIENT PROGRAM'.
01 MSG-AREA.
05 M-DATA PIC X(42) VALUE SPACES.
05 M-RCDE PIC Z(05) VALUE ZEROS.
01 WS-COMMAREA.
05 WC-DATALEN PIC S9(9) COMP-4.
05 WC-SVCNAME PIC X(16).
05 WC-REQUESTCD PIC S9(9) COMP-4.
05 WC-RETURNCD PIC S9(9) COMP-4.
05 WC-REQRETURNCD PIC S9(9) COMP-4.
05 WC-REQDATA PIC X(14).
LINKAGE SECTION.
01 DFHCOMMAREA PIC X(14).
PROCEDURE DIVISION.
A100-ENTRY.
MOVE +14 TO WC-DATALEN.
MOVE 'TOLOWER' TO WC-SVCNAME.
MOVE +5 TO WC-REQUESTCD.
MOVE 'THIS IS A TEST' TO WC-REQDATA.
EXEC CICS LINK PROGRAM('BEAPRERQ')
COMMAREA(WS-COMMAREA)
LENGTH(LENGTH OF WS-COMMAREA)
END-EXEC.
IF RETURNCD = 0
MOVE 'SUCCESSFUL CALL, RETURN DATA IS IN WC-DATA'
TO MSG-DATA
ELSE
MOVE 'PROCESS ERROR OCCURRED, RETURN CODE EQUAL '
TO MSG-DATA
MOVE RETURNCD TO M-RCDE
END-IF.
EXEC CICS SEND TEXT FROM(MSG-AREA) LENGTH(47)
ERASE TERMINAL FREEKB CURSOR(0)
END-EXEC.
A200-EXIT.
EXEC CICS RETURN END-EXEC.
The following is an example of a C CICS client program.
long resp, resp2;
unsigned short int lmsg;
struct CMAREA carea;
carea.CltHdr.DataLen = strlen(sendbuf);
memcpy(carea.CltHdr.SvcName, "ECHO", 4);
carea.CltHdr.RequestCd = BEA_REQUEST_RESPONSE;
memcpy(carea.Request_data, "This is a test", 14);
lmsg=sizeof(carea);
/* Use the name defined during installation */
EXEC CICS LINK PROGRAM("PREREQ")
COMMAREA(&carea)
LENGTH(lmsg) RESP(resp) RESP2(resp2);
if(carea.CltHdr.ReturnCd || carea.CltHdr.ReqReturnCd)
process error;
else
successful call, returned data is in Request_data;
Note: | C Programmers, do not include the NULL terminator on any strings. In the previous example, the memxxx calls were used instead of the strxxx calls. This example is typical when using C and CICS together. For more information see your C for CICS documentation. |
You may encounter the following three types of errors while using TMA TCP for CICS:
The following subsections explain how TMA TCP handles these different kinds of errors.
When local or remote gateway errors occur they are logged in the BEA Tuxedo ULOG
file on the remote BEA Tuxedo node and in the BEALOG
file (a TD Queue defined during installation) within the CICS region. All associated service requests fail and if the TMA gateways are able to communicate with each other, error messages are communicated between them.
For requests originating in the BEA Tuxedo domain, if the remote target system does not make it possible for TMA TCP for CICS to detect particular types of failure, the TMA TCP gateway (the BEA Tuxedo domain) blocking time-out parameter can be tuned to provide timely detection of problems. This configuration parameter is set in the remote TMA TCP gateway system; discuss any changes you want to make with the administrator of that system.
Problems with requests that originate in the CICS region are also logged to the BEALOG
file. Additionally, time-out periods for these requests can be tuned using the TMA TCP for CICS administration tool.
For more information about the blocking time-out parameter, refer to the BEA TMA TCP gateway User Guide.
If an error occurs that makes the Handler unable to execute a certain program (such as, the program does not exist or is disabled) the Handler sends a message back to the TMA TCP gateway gateway. If any other type of error occurs within an application program and the Handler is not notified of the problem, a time-out message is sent from the Handler back to the remote gateway.
For requests originating with CICS, BEA Tuxedo returns information about specific problems, if possible. If there are network problems that prohibit the transmission of data, the request receives a timeout error.
The following subsections identify issues that CICS programmers should be aware of when they develop or modify application programs that interoperate with TMA TCP for CICS as servers.
A CICS application program that processes requests originating from a remote BEA Tuxedo domain is written like a CICS application program that is invoked with the CICS LINK
command.
The CICS programs that work best for satisfying BEA Tuxedo requests are the ones that perform a certain operation and return information to the caller. The CICS services requested by a BEA Tuxedo client program must entail a single request/response scenario.
CICS service programs that are called from BEA Tuxedo clients must be careful if they give up control, as when performing an EXEC CICS XCTL
operation. To ensure that the response data is returned to the client, chaining programs must pass the original COMMAREA
during the XCTL so that it may be RETURN
ed to the TMA TCP for CICS Handler by the final program in the chain.
Service programs expected to send a response to the client use the EXEC CICS LINK
command to execute. The COMMAREA
option contains a pointer to the raw data; therefore, no header is sent. As a result, the request data is available to the service programs in the COMMAREA
.
Service programs that do not send replies back to the requester execute using transactions started by the EXEC CICS START
command. The FROM
option of this command contains a pointer to the raw data; therefore, no header is sent. As a result, such service programs must use an EXEC CICS RETRIEVE
command with the SET
option containing a pointer to the raw data.
Note: | Define a unique transaction for each service that does not send a reply and enter the name of that transaction in the TRANSACTION NAME field of the Inbound Service Information screen for the corresponding service. |
An example of a service sending no reply is one requested by a client using a tpacall with the TPNOREPLY
flag set.
You can manage the actual size of the return message the system sends over the gateway on a per request basis. This is different than simply limiting the message size for a particular service using the MAX MESSAGE
field of the Inbound Service Information screen. To limit the size of the return message per request, the service program must ADDRESS
the TWA using the copybook or the include file delivered in the "YOURHLQ".BEATCPC.INCLUDE file.
To modify the return message length on a per request basis, specify the message length in the rtnMsgSize
field in a TWA_CONNECT
structure defined in the TWAINCL
file.
To modify the return message length on a per request basis, specify the message length in the RTN-MSG-SIZE
field in a TWA_CONNECT
record layout in the copybook TWACOPY
.
![]() ![]() ![]() |