Showing posts with label CICS. Show all posts
Showing posts with label CICS. Show all posts

Saturday, August 10, 2013

Samle Remote stored procedure in CICS/Cobol (RSP)

A Typical RSP Structure
  (check the CICS link for more informtion on RSP)
LINKAGE SECTION.
01 DFHCOMMAREA.
COPY SPAREAC.
01 LK-INPUT-PIPE                    PIC X(100).

01 LK-RETURN-PIPE.
   05 LK-RPLY-SEND-AREA             PIC X(200).

PROCEDURE DIVISION.

PERFORM OPEN-INPUT-PIPE   THRU OPEN-EXIT
PERFORM GET-INPUT-PARM    THRU GET-INPUT-EXIT
PERFORM OPEN-OUTPUT-PIPE  THRU OPEN-OUTPUT-EXIT
PERFORM PROCESS-DATA      THRU PROCESS-EXIT
PERFORM CLOSE-PIPE        THRU CLOSE-EXIT
PERFORM FREE-STORAGE      THRU FREE-EXIT
PERFORM RETURN-TO-FRONT-END.

OPEN-INPUT-PIPE.
MOVE 'OUTPUT'    TO SPMODE.
MOVE 'STD'       TO SPFORMAT.
MOVE  200        TO SPMAXLEN.

CALL 'OPENPIPE' USING SPAREA.
IF SPRC NOT = '000'
MOVE 'OPEN PIPE ERROR IN DRIVER' TO SPMSG
PERFORM PIPE-ERR-RTN  THRU PIPE-EXIT
END-IF.


GET-INPUT-PARM
IF SPVARLEN > 0
   SET ADDRESS OF LK-INPUT-PIPE TO SPVARTXT
   MOVE LK-INPUT-PIPE           TO WS-INPUT-AREA

ELSE
PEROFRM-ERROR-PARA
END-IF.

OPEN-OUTPUT-PIPE.

EXEC CICS GETMAIN
SET (ADDRESS OF LK-RETURN-PIPE)
LENGTH(200)
INITIMG(WS-INITIMG)
RESP (WS-RESP)
END-EXEC


IF WS-RESP = DFHRESP (LENGERR)
MOVE 'CICS LENGTH ERROR IN RETURN AREA'
                                      TO LK-ERR-DESC
END-IF.


PROCESS-DATA
...... PROCESS THE DATA LIKE UPDATE/FETCH WHCH WE GOT FROM FRONT-END
 THRU LINKAGE SECTION INTO OUR WS-VARIABLES.
 PERFORM RESULT-LINKAGE-OUTPUT

RESULT-LINKAGE-OUTPUT
  MOVE WS-OUTPUT-AREA   TO LK-RPLY-SEND-AREA
  SET SPFROM TO ADDRESS OF LK-RETURN-PIPE
  PERFORM PUT-PIPE      THRU EXIT.


PUT-PIPE.
CALL 'PUTPIPE' USING SPAREA.
IF SPRC NOT = '000'
   MOVE 'PUT-PIPE ERROR ' TO SPMSG
   PERFORM PIPE-ERR-RTN
END-IF.


CLOSE-PIPE
CALL 'CLOSPIPE' USING  SPAREA.
IF  SPRC  NOT = '000'
    MOVE  'CLOSE-PIPE ERROR' TO  SPMSG
END-IF.
MOVE  'OK'   TO SPSTATUS
CALL  'STATUS'  USING SPAREA.


FREE-STORAGE.
EXEC CICS FREEMAIN
     DATA (LK-RETURN-PIPE)
END-EXEC


RETURN-TO-FRONT-END.
EXEC CICS 

     RETURN
END-EXEC.


Explanation:
First we need to include SPAREAC in LINKAGE SECTION. SPAREAC includes all pointers,codes that the RSP needs to exchange the data with the front end via the Direct connect.It sets the pointer to the communication channel.
CICS put pipe error might come if the pipe is opened properly .Also if the middleware( like Direct connect or somthing) server is down, CICS program can give put pipe error. So we need to initialize the storage pipes properly and  remove the put pipe,get pipe error.
(For further clarifications leave ur questions in comments section..)
Structure of SPAREAC::::
STORED PROCEDURE COMMUNICATION AREA
03    SPAREA.
05    SPHEADER    PIC X(8).
05    SPRESRVD    PIC X(33).
05    SPTRCOPT    PIC X(1).
05    SPSTATUS    PIC X(2).
05    SPCODE    PIC X(8).
05    SPFORMAT    PIC X(3).
05    SPMODE    PIC X(6).
05    SPRC    PIC X(3).
05    SPFROM    USAGE IS POINTER.
05    SPINTO    REDEFINES SPFROM USAGE IS POINTER.
05    SPSQLDA    REDEFINES SPINTO USAGE IS POINTER.
05    SPVARTXT    USAGE IS POINTER.
05    SPVARTAB    USAGE IS POINTER.
05    SPROWS    PIC S9(8) COMP.
05    SPMAXLEN    PIC S9(4) COMP.
05    SPRECLEN    REDEFINES SPMAXLEN PIC S9(4) COMP.
05    SPVARLEN    PIC S9(4) COMP.
05    SPPREFIX    PIC X.
05    SPMSG    PIC X(100).
05    FILLER    PIC X(3).
05    SPSQL    USAGE IS POINTER.
05    SPATTACH    PIC X(8).
05    SPUSERID    PIC X(8).
05    SPPWD    PIC X(8).
05    SPCMPOPT    PIC X(1).
05    SPIND    PIC X(1).
05    SPDATE    PIC X(8).
05    SPTIME    PIC X(8).
05    SPCONFIG    PIC X(4).
05    SPSERVER    PIC X(30).
05    FILLER    PIC X(32).


The input pipe is opened for communication.In the GETINPUT para, the pointer is set, so that linkage-varibales get the variables passed from front-end via the SPVARTEXT.Then we bring the variables from  likage to our WS-VARIABLES for processing. Once processing is over, we move the Result from WS-OUTPUT to linkage-output and then on to FRONT-END.

Friday, July 5, 2013

UNABLE TO DETERMINE ADDRESS while calling a CICS program

Mostly we get this type of error when we call a NON-CICS pogram from a CICS program. This occurs more obviously if we use a CICS COBOL complier and compile the NON-CICS COBOL program. Generally we use DFHCOMMAREA along with other LINKAGE SECTION  variables while calling sub-pgm. But internally the CICS compiler inserts the variable DFHEIBLK along with the LINKAGE SECTION parameters

DFHEIBLK:  (Data facility Heirarchy Exec Interface BlocK) is a cobol copy book which will be automatically included by the cics translator in all the cics programs.This will contain PIC clauses of all the fields that are mandatory in any cics program. 

Thus there is a address mismatch and it says 'UNABLE TO DETERMINE ADDRESS'. There is a mismatch between what the linkage section is sending and what the linkage section in the called program is receiving.
 To Overcome this situation, we need to include DFHEIBLK along with other parameters passed in the linkage section  in both  the called and calling program respectively.

Thursday, June 27, 2013

CICS with DB2/IMS - Remote Stored Procedure(RSP) in CICS


When and where do we use Remote Stored procedure:
Remote Stored procedures are very handy specially if an front-end application does an dynamic handshaking with mainframe,ie,fetch data from db2 or ims or any other databases and passes the data back to front end .
Overview:
These are compiled programs stored in CICS that basically execute a bunch of SQL statements coded around some logical and manipulative processing in a programming language (We can use either Assembly or COBOL).  RSP’s are generally written in COBOL. A Client front end application program uses the “CALL”  statement to invoke the RSP .A Client program can be written in VB, C#, Powerbuilder and other languages.

The most visible difference between DB2 stored procedure and RSP is that there is no catalog entry for RSPs and they can be written in COBOL. Advantage of using an RSP is that it executes many precompiled SQL statements in a single call reducing the need for multiple calls to the DB2.

Also every time a dynamic SQL is executed from the Client application, Connection has to be made through Middleware like Direct Connect in common cases.

The Direct Connect Gateway Product can communicate with CICS in five modes
1)       STANDARD
2)       BIN
3)       DB2
4)       SDS 
5)       MIX
Modes 1 & 2 transfer data between front end and the CICS without Data structure.Mode 3,4,5 transfer with data structure.
In Standard mode, the entire data is passed to the front end in form of a long string.
If we are using the Standard mode we have one main driver program that will talk to front end application and other CICS programs or its subprograms,ie the entire information flow should be through one program ;the driver progam.
In DB2 mode, the data is returned in result set to front end. For this to happen, CICS program also passes the Data Structure for all the columns that form the result set by using the SQL Descriptor Area or SQLDA. SQLDA tells the front end data type, length,etc of the column .

There are some terms unique to Direct Connect gateway
1.       Open Pipe
2.       Put Pipe
3.       Close Pipe

Just imagine a pipe with taps at both the ends. One end is connected to Client program and the other end is connected to CICS. 
1.       When the Client issues a call, tap at the client end opens automatically and sends in the call to CICS and the tap at the CICS end receives it through linkage section
2.       The pipe is opened at the CICS end through the command OPEN PIPE to Output data
3.       Input data is processed and output is put into the pipe through PUTPIPE at one row at a time.
4.       If process is complete, then the tap at the CICS end is closed
5.       The data now in the pipe is retrieved by the front end by opening the tap at its end.

























Check the Sample program in CICS section.

Before You  Test or invoke RSP:
Each RSP must have a CICS PPT entry. (Generally, the systems administrator or system programmer makes CICS entries.)In addition, if the RSP runs through TRS and accesses DB2,transaction definition in CICS is required for each RSP and an RCT entry is required for that transaction.

Prerequisites to build an RSP:
     RSPs must communicate with the front-end Client application using the SPAREA and the DATA PIPE.The SPAREA contains all the pointers,codes and commands that the RSP needs to  to exchange information. RSP commands(OPENPIPE,PUTPIPE,GETPIPE and others) are small ASSEMBLER programs that calls the Server Connect.We need DATA PIPES to pass rows of data between the application and mainframe.Choosing client application functions
Choosing the Client application function:
You need to understand what functions the client application that calls the RSP is going to perform. Coordinate with the client application programmer to determine the data (that is, keyword variables, variable text, or data) being sent to the RSP and the kind of formatting the client application is capable of performing on the results.
For example, if your RSP provides data structure information with the data it is sending, the client application does less decoding of results. If the RSP sends unformatted data, the client must include more logic to decode the results.

Accessing Databases:
RSP can access the databases like DB2,IMS,ADABAS,VSAM,BDAM

Exchanging Information between front end and CICS:
The SPAREA contains all the pointers, codes, and command details that the RSP needs to exchange with the RSP API. Every RSP receives or sends information using the SPAREA.

BASIC TERMS AND USAGE:
The OPENPIPE command uses values from these SPAREA fields:

SPMODE specifies whether the data pipe is opened for input or output.
INPUT indicates the RSP reads data records sent from the client application.
OUTPUT indicates the RSP writes data records to be sent to the client application.
SPFORMAT specifies the data pipe format.
STD indicates standard format, in which each data record is transmitted to or from the client application as a single-text column record.
BIN indicates a single-binary column format, like STD, except that the data is binary. No ASCII-EBCDIC or EBCDIC-ASCII conversion occurs on binary data
SPMAXLEN specifies the maximum size, in bytes, of the data records written to or read from the data pipe. 
STD and BIN format pipes must use SPMAXLEN to identify the maximum record length.

Sampel Code to Open a STD output pipe:
MOVE 'OUTPUT' TO SPMODE.
MOVE 'STD' TO SPFORMAT.
MOVE 450 TO SPMAXLEN.
CALL 'OPENPIPE' USING SPAREA.

Check the Sample program in CICS section.

DB2 indicates data is transmitted from the RSP as a multiple-column record, where the column definitions are contained in an associated SQLDA. The SQLDA is a collection of variables and pointers that provide column information about data being transmitted to the client application.
SPSQLDA specifies the address of a SQLDA that describes the content of the data records. Use only for output pipes.
For DB2 format pipes, the RSP must supply the SPSQLDA address. DB2 format pipes must use SPSQLDA.
Both an input pipe and an output pipe can be open at the same time

Continued in Sample program in CICS section. ...