Você está na página 1de 29

When should I consider using a TSQ rather than the Commarea?

A commarea will only exist to pass data between tasks and can be set so when ending a
transaction to display a map to it is avaiable when the transaction starts after the map.
Commareas should not normally exceed 32K.

When a TSQ is created it remains in existance until it is deleted or the cics system is shut.
The data is avaiable to any trnsaction that knows its name. S it could be used to hold
global parameters what are loaded at cics start up to reduce file access etc. if you are
using a TSQ to hold information relatin to a particular task or termaial you must have a
naming convenetion to support that. You only have a finite abount of TSQ space to so
you delete unwanted TSQ's.

***********************************************************************
*

Sample program using TSQ

IDENTIFICATION DIVISION.
PROGRAM-ID. OSCICS3C.
DATE-WRITTEN. 12/02/96.
DATE-COMPILED.
******************************************************************
**
** (c) 1995 by Sybase, Inc. All Rights Reserved
**
******************************************************************
******************************************************************
** PROGRAM: OSCICS3C
**
** THIS PROGRAM IS A THE OPEN SERVER VERSION OF RSP3C.
** This program receives parms up to 55 bytes in length
** will echo it back in 55 byte rows.
** NOTE: OS app cannot recieve input pipes as an RSP can,
** this is the only method using OS to do it...
** The input data is treated a a char type as RSP3c did...
** exec SY3C 1234567890, 1234567890, ..........
******************************************************************

ENVIRONMENT DIVISION.

DATA DIVISION.

WORKING-STORAGE SECTION.

******************************************************************
* COPY IN THE OS SERVER LIBRARYS
******************************************************************
COPY SYGWCOB.
******************************************************************
*OPEN SERVER WORK VARIBLES FOR OS CALL TO USE ...
******************************************************************
01 WS-GWL-WORK-VARIBLES.
05 GWL-PROC POINTER.
05 GWL-INIT-HANDLE POINTER.
05 GWL-RC PIC S9(9) COMP.
05 GWL-INFPRM-ID PIC S9(9) COMP.
05 GWL-INFPRM-TYPE PIC S9(9) COMP.
05 GWL-INFPRM-DATA-L PIC S9(9) COMP.
05 GWL-INFPRM-MAX-DATA-L PIC S9(9) COMP.
05 GWL-INFPRM-STATUS PIC S9(9) COMP.
05 GWL-INFPRM-NAME PIC X(30).
05 GWL-INFPRM-NAME-L PIC S9(9) COMP.
05 GWL-INFPRM-USER-DATA PIC S9(9) COMP.
05 GWL-INFUDT-USER-TYPE PIC S9(9) COMP.
05 GWL-STATUS-NR PIC S9(9) COMP.
05 GWL-STATUS-DONE PIC S9(9) COMP.
05 GWL-STATUS-COUNT PIC S9(9) COMP.
05 GWL-STATUS-COMM PIC S9(9) COMP.
05 GWL-COMM-STATE PIC S9(9) COMP.
05 GWL-STATUS-RETURN-CODE PIC S9(9) COMP.
05 GWL-STATUS-SUBCODE PIC S9(9) COMP.
05 GWL-NUMPRM-PARMS PIC S9(9) COMP.
05 GWL-RCVPRM-DATA-L PIC S9(9) COMP.
05 GWL-SETPRM-ID PIC S9(9) COMP.
05 GWL-SETPRM-TYPE PIC S9(9) COMP.
05 GWL-SETPRM-DATA-L PIC S9(9) COMP.
05 GWL-SETPRM-USER-DATA PIC S9(9) COMP.
05 GWL-CONVRT-SCALE PIC S9(9) COMP VALUE 2.
05 GWL-SETBCD-SCALE PIC S9(9) COMP VALUE 0.
05 GWL-INFBCD-LENGTH PIC S9(9) COMP.
05 GWL-INFBCD-SCALE PIC S9(9) COMP.
05 GWL-RETURN-ROWS PIC S9(9) COMP VALUE +0.
05 SNA-CONN-NAME PIC X(8) VALUE SPACES.
05 SNA-SUBC PIC S9(9) COMP.
05 WRK-DONE-STATUS PIC S9(9) COMP.
05 GWL-ACTUAL-LEN PIC S9(9) COMP.
05 GWL-TRAN-LEN PIC S9(9) COMP.
05 GWL-MSG-LEN PIC S9(9) COMP.
05 WS-NUMPRM-PARMS PIC S9(9) COMP.
05 GWL-REQUEST-TYP PIC S9(9) COMP.
05 GWL-RPC-NAME PIC X(30) VALUE SPACES.
05 GWL-COMM-STATE PIC S9(9) COMP.
05 I PIC S9(9) COMP.

01 DESCRIPTION-FIELDS.
05 COLUMN-NUMBER PIC S9(09) COMP VALUE +0.
05 HOST-TYPE PIC S9(09) COMP VALUE +0.
05 HOST-LEN PIC S9(09) COMP VALUE +0.
05 COLUMN-LEN PIC S9(09) COMP VALUE +0.
05 COLUMN-NAME-LEN PIC S9(09) COMP VALUE +0.
05 WS-ZERO PIC S9(09) COMP VALUE +0.

01 WS-MSG-WORK-VARS.
05 MSG-NR PIC S9(9) COMP VALUE +9999.

01 WS-INPUT-LEN PIC S9(9) COMP VALUE +55.


01 WS-INPUT-DATA PIC X(55) VALUE SPACES.

01 WS-OUTPUT-DATA PIC X(55) VALUE SPACES.

01 WS-OUTPUT-COL-NAME PIC X(13)


VALUE 'OUTPUT_COLUMN'.
01 WS-QUEUE-NAME.
05 WS-TRANID PIC X(4) VALUE 'SY3C'.
05 WS-TRMID PIC X(4) VALUE SPACES.
01 CICSRC PIC S9(8) COMP.
01 CICSRC-DIS PIC S9(8).

******************************************************************
* MESSAGES *
******************************************************************

01 WS-MSG.
05 FILLER PIC X(17)
VALUE 'ERROR IN OS CALL '.
05 WS-MSG-FUNC PIC X(10).
05 FILLER PIC X(04)
VALUE 'RC='.
05 WS-MSG-RC PIC S9(9).
05 FILLER PIC X(18)
VALUE ' SUBCODE ERROR = '.
05 MSG-SUBC PIC 9(9) VALUE 0.
05 WS-MSG-TEXT PIC X(50) VALUE SPACES.

01 WORK-SRVIN-INFO.
05 WK-INFO-TBL-ID PIC S9(8) COMP.
05 WK-INFO-TBL-NAME PIC X(30).
05 WK-INFO-TBL-VALUE PIC X(10).

LINKAGE SECTION.
**************************************************************
* THE LINKAGE SECTION DEFINES MASKS FOR DATA AREAS THAT ARE
* PASSED BETWEEN THIS PROGRAM.
**************************************************************

01 DFHCOMMAREA PIC X(1).

PROCEDURE DIVISION.

000-MAIN-PROCESSING.

PERFORM 100-INITIALIZE THRU 100-EXIT.

PERFORM 200-PROCESS-INPUT THRU 200-EXIT.

PERFORM 300-PROCESS-OUTPUT THRU 300-EXIT.

PERFORM 900-ALL-DONE THRU 900-EXIT.

GOBACK.

000-EXIT.
EXIT.

100-INITIALIZE.

******************************************************
* INTIALIZED THE TDS CONNECTION AND CONFIRM THAT IS
* WAS AN RPC CALL, ........
******************************************************
*==> INITIAL QUEUE NAME <===*
MOVE EIBTRMID TO WS-TRMID.

*==> ESTABLISH GATEWAY ENVIRONMENT <===*

CALL 'TDINIT' USING DFHEIBLK, GWL-RC, GWL-INIT-HANDLE.


IF GWL-RC NOT = TDS-OK THEN
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.
*==> ACCEPT CLIENT REQUEST <===*

CALL 'TDACCEPT' USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,


SNA-CONN-NAME, SNA-SUBC.
IF GWL-RC NOT = TDS-OK THEN
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

*==> TO MAKE SURE WE WERE STARTED BY RPC REQUEST... <===*

CALL 'TDINFRPC' USING GWL-PROC, GWL-RC,


GWL-REQUEST-TYP, GWL-RPC-NAME,
GWL-COMM-STATE.
IF GWL-RC NOT = TDS-OK OR
GWL-REQUEST-TYP NOT = TDS-RPC-EVENT
THEN
MOVE GWL-RC TO WS-MSG-RC
MOVE 'TDINFRPC' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

100-EXIT.
EXIT.

200-PROCESS-INPUT.
****************************************************************
* RECEIVE THE INPUT PARAMETER INTO HOST VARIBLE, SEND ROW
DATA *
* BACK DOWN TO CLIENT *
****************************************************************

*---> Find out how many parms are being passed <---*

CALL 'TDNUMPRM' USING GWL-PROC, GWL-NUMPRM-PARMS.

*---> No Parms ---> pump back a message <---*

IF GWL-NUMPRM-PARMS < +1 THEN


MOVE 'At least one parm is needed'
TO WS-MSG-TEXT
MOVE GWL-RC TO WS-MSG-RC
MOVE 'TDNUMPRM' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF

*---> SAVE THE NUMBER OF PARMS FOR THE LOOP <---*


MOVE GWL-NUMPRM-PARMS TO WS-NUMPRM-PARMS.

*---> LOOP THRU THE PARMS AND WRITE TO TEMP STORAGE <----*
PERFORM VARYING GWL-NUMPRM-PARMS FROM 1 BY 1
UNTIL GWL-NUMPRM-PARMS > WS-NUMPRM-PARMS
PERFORM 210-GET-PARM THRU 210-EXIT
PERFORM 220-WRITE-TS THRU 220-EXIT

END-PERFORM.
200-EXIT.
EXIT.
210-GET-PARM.
****************************************************************
* *---> GET THE PARM INTO THE HOST VARIBLE <---* *
****************************************************************

CALL 'TDRCVPRM' USING GWL-PROC, GWL-RC,


GWL-NUMPRM-PARMS,
WS-INPUT-DATA,
TDSCHAR,
WS-INPUT-LEN,
GWL-ACTUAL-LEN
IF GWL-RC NOT = TDS-OK THEN
MOVE GWL-RC TO WS-MSG-RC
MOVE 'TDRCVPRM' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

210-EXIT.
EXIT.
220-WRITE-TS.
****************************************************************
* *---> USING TEMP STORAGE, STORE PARMS FOR OUTPUT LATER <---**
****************************************************************

EXEC CICS
WRITEQ TS QUEUE(WS-QUEUE-NAME)
FROM (WS-INPUT-DATA)
LENGTH(LENGTH OF WS-INPUT-DATA)
RESP (CICSRC)
END-EXEC.
IF CICSRC NOT = DFHRESP(NORMAL)
MOVE CICSRC TO CICSRC-DIS
MOVE CICSRC-DIS TO WS-MSG-RC
MOVE 'WRITEQ' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

220-EXIT.
EXIT.
300-PROCESS-OUTPUT.
****************************************************************
* READ TEMP STORAGE QUEUE AND SEND ROWS TO CLIENT *
****************************************************************

PERFORM 310-DEFINE-OUTPUT THRU 310-EXIT.

PERFORM VARYING I FROM 1 BY 1 UNTIL I > WS-NUMPRM-PARMS


PERFORM 320-READQ-TS THRU 320-EXIT
PERFORM 330-SEND-ROW THRU 330-EXIT

END-PERFORM.

300-EXIT.
EXIT.

310-DEFINE-OUTPUT.
****************************************************************
* DEFINE THE OUTPUT COLUMN AS CHAR OF 55 BYTES *
****************************************************************

MOVE +1 TO COLUMN-NUMBER.
MOVE LENGTH OF WS-OUTPUT-DATA TO HOST-LEN
COLUMN-LEN.
MOVE LENGTH OF WS-OUTPUT-COL-NAME TO COLUMN-NAME-LEN.
CALL 'TDESCRIB' USING GWL-PROC,
GWL-RC,
COLUMN-NUMBER,
TDSCHAR,
HOST-LEN,
WS-OUTPUT-DATA,
TDS-ZERO,
TDS-FALSE,
TDSCHAR,
COLUMN-LEN,
WS-OUTPUT-COL-NAME,
COLUMN-NAME-LEN.

IF GWL-RC NOT = TDS-OK THEN


MOVE GWL-RC TO WS-MSG-RC
MOVE 'TDESCRIB' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

310-EXIT.
EXIT.
320-READQ-TS.
****************************************************************
* READ THE INPUT TEMP STORAGE QUEUE
****************************************************************
EXEC CICS
READQ TS QUEUE(WS-QUEUE-NAME)
INTO (WS-OUTPUT-DATA)
LENGTH(LENGTH OF WS-OUTPUT-DATA)
NEXT
RESP (CICSRC)
END-EXEC.
IF CICSRC NOT = DFHRESP(NORMAL)
MOVE CICSRC TO CICSRC-DIS
MOVE CICSRC-DIS TO WS-MSG-RC
MOVE 'READQ' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

320-EXIT.
EXIT.

330-SEND-ROW.
****************************************************************
* SEND ROW OF DATA TO CLIENT....
*****************************************************************

CALL 'TDSNDROW' USING GWL-PROC, GWL-RC


IF GWL-RC NOT = TDS-OK
THEN
MOVE GWL-RC TO WS-MSG-RC
MOVE 'TDSNDROW' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

330-EXIT.
EXIT.
EJECT
900-ALL-DONE.
******************************************************************
* CLOSE CONNECTION TO CLIENT AND RETURN TO CICS... *
******************************************************************

CALL 'TDSNDDON' USING GWL-PROC, GWL-RC, WRK-DONE-STATUS,


GWL-RETURN-ROWS, TDS-ZERO, TDS-ENDRPC.
IF GWL-RC NOT = TDS-OK THEN
PERFORM 980-CICS-DUMP THRU 980-EXIT
PERFORM 990-CICS-RETURN THRU 990-EXIT
END-IF.

CALL 'TDFREE' USING GWL-PROC, GWL-RC.

EXEC CICS
DELETEQ TS QUEUE(WS-QUEUE-NAME)
RESP (CICSRC)
END-EXEC.
IF CICSRC NOT = DFHRESP(NORMAL)
MOVE CICSRC TO CICSRC-DIS
MOVE CICSRC-DIS TO WS-MSG-RC
MOVE 'DELETEQ' TO WS-MSG-FUNC
PERFORM 920-SEND-MESSAGE THRU 920-EXIT
PERFORM 910-ERR-PROCESS THRU 910-EXIT
END-IF.

PERFORM 990-CICS-RETURN THRU 990-EXIT.

900-EXIT.
EXIT.

910-ERR-PROCESS.
******************************************************************
* PERFORM ALL-DONE IN A ERROR STATE *
******************************************************************

MOVE ZERO TO GWL-RETURN-ROWS.


MOVE TDS-DONE-ERROR TO WRK-DONE-STATUS.
PERFORM 900-ALL-DONE THRU 900-EXIT.

910-EXIT.
EXIT.

920-SEND-MESSAGE.
******************************************************************
* SEND ERROR MESSAGE DOWN TO CLIENT *
******************************************************************
CALL 'TDSTATUS' USING GWL-PROC, GWL-RC, GWL-STATUS-NR,
GWL-STATUS-DONE, GWL-STATUS-COUNT,
GWL-STATUS-COMM,
GWL-STATUS-RETURN-CODE,
GWL-STATUS-SUBCODE.

*==> ENSURE THAT WE ARE IN THE CORRECT STATE TO SEND A


MESSAGE <=*
IF GWL-RC NOT = TDS-OK THEN
PERFORM 980-CICS-DUMP THRU 980-EXIT
PERFORM 990-CICS-RETURN THRU 990-EXIT
END-IF.

IF GWL-STATUS-COMM = TDS-RECEIVE THEN


CALL 'TDCANCEL' USING GWL-PROC, GWL-RC.

MOVE LENGTH OF EIBTRNID TO GWL-TRAN-LEN.


MOVE LENGTH OF WS-MSG TO GWL-MSG-LEN.
CALL 'TDSNDMSG' USING GWL-PROC, GWL-RC, TDS-ERROR-MSG,
MSG-NR, TDS-ERROR-SEV, TDS-ZERO,
TDS-ZERO, EIBTRNID, GWL-TRAN-LEN,
WS-MSG, GWL-MSG-LEN.

920-EXIT.
EXIT.

980-CICS-DUMP.
******************************************************************
* CAUSE A CICS TRANSACTION DUMP USUALLY BECAUSE SOMETHING IS
BAD *
******************************************************************
EXEC CICS
DUMP DUMPCODE('SY3C') NOHANDLE
END-EXEC.
980-EXIT.
EXIT.

990-CICS-RETURN.
******************************************************************
* RETURN TO CICS... *
******************************************************************

EXEC CICS
RETURN
END-EXEC.

990-EXIT.
EXIT.

5.5 Transient data control

The CICS transient data control facility provides a generalized queuing


facility. Data can be queued (stored) for subsequent internal or external
processing. Selected data, specified in the application program, can be
routed to or from predefined symbolic transient data queues: either
intrapartition or extrapartition.

Transient data queues are intrapartition if they are associated with a


facility allocated to the CICS region, and extrapartition if the data is
directed to a destination that is external to the CICS region. Transient
data queues must be defined and installed before first reference by an
application program.

You can:

° Write data to a transient data queue (WRITEQ TD command)


° Read data from a transient data queue (READQ TD command)
° Delete an intrapartition transient data queue (DELETEQ TD command)

If the TD keyword is omitted, the command is assumed to be for temporary


storage.

5.5.1 Intrapartition queues

"Intrapartition" refers to data on direct-access storage devices for use


with one or more programs running as separate tasks. Data directed to or
from these internal queues is referred to as intrapartition data; it must
consist of variable-length records. Intrapartition queues can be
associated with either a terminal or an output data set. Intrapartition
data may ultimately be transmitted upon request to the terminal or
retrieved sequentially from the output data set.

Typical uses of intrapartition data include:

° Message switching
° Broadcasting
° Database access
° Routing of output to several terminals (for example, for order
distribution)
° Queuing of data (for example, for assignment of order numbers or
priority by arrival)
° Data collection (for example, for batched input from 2780 Data
Transmission Terminals)

There are three types of intrapartition transient data queue:

° Non-recoverable
Non-recoverable intrapartition transient data queues are recovered
only on a warm start of CICS. If a unit of work (UOW) updates a
non-recoverable intrapartition queue and subsequently backs out the
updates, the updates made to the queue are not backed out.

° Physically recoverable
Physically recoverable intrapartition transient data queues are
recovered on warm and emergency restarts. If a UOW updates a
physically recoverable intrapartition queue and subsequently backs out
the updates, the updates made to the queue are not backed out.

° Logically recoverable
Logically recoverable intrapartition transient data queues are
recovered on warm and emergency restarts. If a UOW updates a
logically recoverable intrapartition queue and subsequently backs out
the changes it has made, the changes made to the queue are also backed
out. On a warm or an emergency restart, the committed state of a
logically recoverable intrapartition queue is recovered. In-flight
UOWs are ignored.

If an application is trying to issue a read, write, or delete request


and suffers an indoubt failure, it may receive a LOCKED response if
WAIT(YES) and WAITACTION(REJECT) are specified in the queue
definition.

5.5.2 Extrapartition queues


Extrapartition queues (data sets) reside on any sequential device (DASD,
tape, printer, and so on) that are accessible by programs outside (or
within) the CICS region. In general, sequential extrapartition queues are
used for storing and retrieving data outside the CICS region. For
example, one task may read data from a remote terminal, edit the data, and
write the results to a data set for subsequent processing in another
region. Logging data, statistics, and transaction error messages are
examples of data that can be written to extrapartition queues. In
general, extrapartition data created by CICS is intended for subsequent
batched input to non-CICS programs. Data can also be routed to an output
device such as a printer.

Data directed to or from an external destination is referred to as


extrapartition data and consists of sequential records that are
fixed-length or variable-length, blocked or unblocked. The record format
for an extrapartition destination must be defined in the DCT by the system
programmer and the queue must be defined in the queue definition.

5.5.3 Indirect queues

Intrapartition and extrapartition queues can be used as indirect queues.


Indirect queues provide some flexibility in program maintenance in that
data can be routed to one of several queues with only the transient data
definition, and not the program itself, having to be changed.

When a transient data definition has been changed, application programs


continue to route data to the queue using the original symbolic name;
however, this name is now an indirect queue that refers to the new
symbolic name. Because indirect queues are established by using transient
data resource definitions, the application programmer does not usually
have to be concerned with how this is done. Further information about
transient data resource definition is in the CICS Resource Definition
Guide.

5.5.4 Automatic transaction initiation (ATI)

For intrapartition queues, CICS provides the option of automatic


transaction initiation (ATI).

A basis for ATI is established by the system programmer by specifying a


nonzero trigger level for a particular intrapartition destination. When the number of
entries (created by WRITEQ TD commands issued
by one or more programs) in the queue reaches the specified trigger level,
a transaction specified in the definition of the queue is automatically
initiated. Control is passed to a program that processes the data in the
queue; the program must issue repetitive READQ TD commands to deplete the
queue.

When the queue has been emptied, a new ATI cycle begins. That is, a new
task is scheduled for initiation when the specified trigger level is again
reached, whether or not execution of the earlier task has ended.

If an automatically initiated task does not empty the queue, access to the
queue is not inhibited. The task may be normally or abnormally ended
before the queue is emptied (that is, before a QZERO condition occurs in
response to a READQ TD command). If the contents of the queue are to be
sent to a terminal, and the previous task completed normally, the fact
that QZERO has not been reached means that trigger processing has not been
reset and the same task is reinitiated. A subsequent WRITEQ TD command
does not trigger a new task if trigger processing has not been reset.

If the contents of the queue are to be sent to a file, the termination of


the task has the same effect as QZERO (that is, trigger processing is
reset). The next WRITEQ TD command initiates the trigger transaction (if
the trigger level has been reached).

If the trigger level of a queue is zero, no task is automatically


initiated.

If a queue is logically recoverable, initiation of the trigger transaction


is deferred until the next syncpoint.

If the trigger level has already been exceeded because the last triggered
transaction abended before clearing the queue, or because the transaction
was never started because the MXT limit was reached, another task is not
scheduled. This is because QZERO has not been raised to reset trigger
processing. The task that has already been scheduled is reinitiated as
soon as possible. If the contents of a queue are destined for a file, the
termination of the task resets trigger processing and means that the next
WRITEQ TD command triggers a new task.

To ensure that an automatically initiated task completes when the queue is


empty, the application program should test for a QZERO condition in
preference to some other application-dependent factor (such as an
anticipated number of records). Only the QZERO condition indicates an
emptied queue.

If the contents of a queue are to be sent to another system, the session


name is held in EIBTERMID. If a transaction (started with a destination
of system) abends, a new transaction is started in the same way as a
terminal.

If you use ATI with a transient data trigger mechanism, it could create
inter-transaction affinities that adversely affect your ability to perform
dynamic transaction routing.

A trigger transaction is shunted if it suffers from an indoubt failure.


Another trigger transaction is not attached until the shunted UOW commits
or backs out the changes it has made following resynchronization.

Temporary storage control

The CICS temporary storage control facility provides the application


programmer with the ability to store data in temporary storage queues,
either in main storage, in auxiliary storage on a direct-access storage
device, or in a temporary storage data sharing pool. Data stored in a
temporary storage queue is known as temporary data.

You can:

° Write data to a temporary storage queue (WRITEQ TS command).

° Update data in a temporary storage queue (WRITEQ TS REWRITE command).

° Read data from a temporary storage queue (READQ TS command).

° Read the next data from a temporary storage queue (READQ TS NEXT
command).

° Delete a temporary storage queue (DELETEQ TS command).

The TS keyword may be omitted; temporary storage is assumed if it is not


specified.

5.6.1 Temporary storage queues

Temporary storage queues are identified by symbolic names that may be up


to eight characters, assigned by the originating task. Temporary data can
be retrieved by the originating task or by any other task using the
symbolic name assigned to it. To avoid conflicts caused by duplicate
names, a naming convention should be established; for example, the
operator identifier or terminal identifier could be used as a suffix to
each programmer-supplied symbolic name. Specific items (logical records)
within a queue are referred to by relative position numbers.

Temporary storage queues remain intact until they are deleted by the
originating task, by any other task, or by an initial or cold start;
before deletion, they can be accessed any number of times. Even after the
originating task is terminated, temporary data can be accessed by other
tasks through references to the symbolic name under which it is stored.

Temporary data can be stored either in main storage or in auxiliary


storage. Generally, main storage should be used if the data is needed for
short periods of time; auxiliary storage should be used if the data is to
be kept for long periods of time. Data stored in auxiliary storage is
retained after CICS termination and can be recovered in a subsequent
restart, but data in main storage cannot be recovered. Main storage might
be used to pass data from task to task, or for unique storage that allows
programs to meet the requirement of CICS that they be quasi-reentrant
(that is, serially reusable between entry and exit points of the program).

Temporary storage data sharing provides another type of temporary storage


queue that can be supported concurrently. The temporary storage queues
can be defined as local, remote, or shared, and they can be stored in
temporary storage pools in the coupling facility.

5.6.2 Typical uses of temporary storage control

A temporary storage queue that has only one record can be treated as a
single unit of data that can be accessed using its symbolic name. Using
temporary storage control in this way provides a typical scratch-pad
capability. This type of storage should be accessed using the READQ TS
command with the ITEM option; not doing so may cause the ITEMERR condition
to be raised.

In general, temporary storage queues of more than one record should be


used only when direct access or repeated access to records is necessary;
transient data control provides facilities for efficient handling of
sequential data sets.

Some uses of temporary storage queues are:

Terminal paging
A task could retrieve a large master record from a direct-access data
set, format it into several screen images (using BMS), store the
screen images temporarily in auxiliary storage, and then ask the
terminal operator which "page" (screen image) is desired. The
application programmer can provide a program (as a generalized
routine or unique to a single application) to advance page by page,
advance or back up a relative number of pages, and so on.

A suspend data set


Suppose a data collection task is in progress at a terminal. The
task reads one or more units of input and then allows the terminal
operator to interrupt the process by some kind of coded input. If
not interrupted, the task repeats the data collection process. If
interrupted, the task writes its incomplete data to temporary storage
and terminates. The terminal is now free to process a different
transaction (perhaps a high-priority inquiry). When the terminal is
available to continue data collection, the operator initiates the
task in a "resume" mode, causing the task to recall its suspended
data from temporary storage and continue as though it had not been
interrupted.

Preprinted forms
An application program can accept data to be written as output on a
preprinted form. This data can be stored in temporary storage as it
arrives. When all the data has been stored, it can first be
validated and then transmitted in the order required by the format of
the preprinted form.
Temporary Storage and Transient Data

WRITEQ TS QUEUE (queue name)


FROM (data area)
[LENGTH (data value)]
[ITEM (data area)]
[MAIN / AUXILLIARY]
[SYSID (name)]

READQ TS QUEUE (queue name)


INTO (data area)
[LENGTH (data area)]
[ITEM (data value) / NEXT]
[NUMITEMS (data area)]
[SYSID (name)]

WRITEQ TS QUEUE (queue name)


FROM (data area)
[LENGTH (data value)]
[ITEM (data area) [REWRITE]]
[MAIN / AUXILLIARY]
[SYSID (name)]

DELETEQ TS QUEUE (queue name)


[SYSID (name)]

Temporary Storage Queues


Temporary storage provides a means for storing data records in queues. Like files, these
records are identified by a unique symbolic name. Temporary storage queues do not have
to be predefined to Cics. They can be created in main storage or on auxilliary storage
devices. Once created, these records can be read either sequentially or randomly by any
other Cics program.
Temporary storage queues are not directly attached to a task. This means that temporary
storage queues are task independant. Once a temporary storage queue is written, it
remains intact after the task that created it has terminated.
Temporary Storage Queue Commands
There are three commands that process data in temporary storage queues.
* The WRITEQ TS command allows you to write records to a temporary storage queue.
If no queue exists when this command is issued, one will be created and the records will
be written to it.
* The READQ TS command allows you to read records, either sequentially or randomly,
from a temporary storage queue.
* Records in a temporary storage queue can be updated and rewritten by using the
REWRITE option of the WRITEQ TS command
* The DELETEQ TS command allows you to delete an entire temporary storage queue.
Individual records cannot be deleted
* The queue name specified in a temporary storage command must not exceed eight
characters in length

Transient Data Queues


Like temporary storage queues, transient data queues are task dependent. However
transient data queues can only be read sequentially.
Unlike temporary storage queues, transient data queues must be defined before they are
used. This definition takes place in a special Cics table called the Destination Control
Table (DCT). The DCT is usually maintained by a sys prog. One of the fields in each
DCT entry tells whether the queue is an intrapartition or extrapartition queue.
Intrapartition Data Queues
Intrapartition transient data queus may only reside on auxilliary storage and can only be
read sequentially by other CICS programs. Reading an intrapartition data queue is
destructive.
Intrapartition queues may also be associated with Automatic Task Initiation. When the
number of records in an intrapartition queue reaches a predefined count a special task is
automatically initiated.
Extrapartition Data Queues
Unlike intrapartition queus, extrapartition queues can be accessed by other Cics programs
as well as batch programs executing outside of the CICS partition or region. They can
reside on any sequential device, such as disk or tape, or be sent directly to an off line
printer. Reading records in an extrapartition queue is non-destructive.

WRITEQ TD QUEUE (queue name)


FROM (data area)
[LENGTH (data value)]
[SYSID (name)]

READQ TD QUEUE (queue name)


INTO (data area)
[LENGTH (data area)]
[SYSID (name)]

DELETEQ TD QUEUE (queue name)


[SYSID (name)]

* The WRITEQ TD command allows you to write records sequentially to a transient data
queue
* The READQ TD command allows you to read sequentially from a transient data queue
* The DELETEQ TD command allows you to delete the contents of an intrapartition TD
queue.
* Transient Data Queues are referenced by these commands using a symbolic name
which must be predefined in the DCT
* The queue name specified in transient data commands must not exceed four characters
in length

Exceptional Conditions

IOERR - An undetermined error has occured during input or output


ISCINVREQ - an undetermined error has occured on a remote system
ITEMERR - The requested item number is invalid
LENGERR - The length of a record is invalid or missing
NOSPACE - A write has failed due to lack of space
QIDERR - The requested queue cannot be found
QZERO - A read has been attempted on an empty queue
SYSIDERR - The specified remote system is unavailable or not defined

Do we need to define the TDQ? If yes , is it similar to TSQ? and if NO why?


Yes of course you need to define a TDQ.

You have to add a DCT entry for the with the queue name(4 characters) and also a
DSName corresponding to a file in the region.
TDQs can be intra/extra partitioned.

you must be extremely careful with the record length

You need to first define a tdq, then install the tdq. Only then u can access the tdq for read
or write. For defining and installing the tdq u can use CEDA command. For read and
write operations on the tdq u can use CECI command. TDQ's can be intra, extra or
indirect partitioned. You can delete the TDQ using DELETEQ command under CECI
after it is no longer useful.

Here are some of differences between a TDQ and a TSQ,

1) In Temporary Storage Queues Data is read randomly, While in Transient Data Queues
data must be read sequentially.
(2) In a TSQ data can be read any number of times as it remains in the queue until the
entire Queue is deleted. In TDQ data item can be read once only. To reuse the TDQ it
must be closed and reopened.
(3) Data can be changed in TSQ, but not in TDQ.
(4) TSQ can be written to Auxiliary or Main Storage, while TDQ is written to Disk.
Temporary storage is a holding place, while Transient data is always associated with
destination.
(5) TSQ name is defined dynamically, while a TDQ name need to be defined in the DCT.
Note: An application uses TSQ 's to pass info' from task to task, while a TDQ to
accumulate records before processing or send data for external use, such as a print
operation or other.

Queue services
Queues are sequential storage facilities with special properties. Like files and databases,
they are global resources within CICS or a complex of interconnected CICS systems.
That is, they are not associated with a particular task. Any task may read, write or delete
them, and the pointers associated with a queue are shared across all tasks.

CICS queues are also permanent storage. Except for temporary storage queues kept in
main storage, CICS queues persist across executions of CICS, unless explicitly discarded
in a cold start.
Some of the main differences between the two types of queue are:

Transient data queue names must be defined in the Transient Data Definitions (TDD)
before they are used by an application. You cannot define them arbitrarily at the time the
data is created. Thus, transient data does not have the same dynamic characteristics as
temporary storage.

Transient data queues must be read sequentially, and each item can be read only once.
That is, after a transaction reads an item, that item is removed from the queue and is not
available to any other transaction. In contrast, items in temporary storage queues may be
read either sequentially or directly (by item number). They can be read any number of
times and are never removed from the queue until the entire queue is purged.
These two characteristics make transient data inappropriate for scratchpad data but
suitable for queued data such as audit trails and output to be printed. In fact, for data that
is read sequentially once, transient data is preferable to temporary storage because:

Items in a temporary storage queue can be changed; items in transient data cannot.

Transient data queues are always written to a file. (There is no form of transient data that
corresponds to main temporary storage.)

You can define transient data queues so that writing items to the queue causes a specific
transaction to be initiated (for example, to process the queue). Temporary storage has
nothing that corresponds to this trigger mechanism, although you may be able to use a
START command to perform a similar function.

Transient data has more varied recovery options than temporary storage. It can be
physically or logically recoverable.

Because the commands for intrapartition and extrapartition transient data are identical,
you can switch easily between the internal CICS facility (intrapartition) and an external
data set, described in "External files". To do this, you need only change the TDD, not
your application programs. Temporary storage has no corresponding function of this kind.
"Transient data queue services"

"Temporary storage queue services"

Transient data queue services


CICS transient data queue services provide a generalized queueing facility. Data can be
queued (stored) for subsequent internal or external processing. Selected data, specified in
the application program, can be routed to or from predefined symbolic destinations, either
intrapartition or extrapartition.
You can:

Write data to a transient data queue (EXEC CICS WRITEQ TD)


Read data from a transient data queue (EXEC CICS READQ TD)
Delete an intrapartition transient data queue (EXEC CICS DELETEQ TD)
If TD is omitted, the command is assumed to be for temporary storage (see "Temporary
storage queue services" for details).

Intrapartition destinations
Intrapartition destinations are queues of data on direct-access storage devices for use with
one or more programs running as separate tasks within the CICS region. Data directed to
or from these internal destinations is called intrapartition data.

Typical uses of intrapartition data include:

Message switching

Broadcasting

Database access

Routing of output to several terminals (for example, for order distribution)

Queuing of data (for example, for assignment of order numbers or priority by arrival)

Data collection

Extrapartition destinations
Extrapartition destinations are queues (files) residing on any file system file (disk, tape,
printer, and so on) that are accessible by programs outside (or inside) the region. In
general, sequential extrapartition destinations are used for storing and retrieving data
outside the region. For example, one task may read data from a remote terminal, edit the
data, and write the results to a file for subsequent processing in another region. Logging
data, statistics, and transaction error messages are examples of data that can be written to
extrapartition destinations. In general, extrapartition data created by CICS is intended for
subsequent input to non-CICS programs. Data can also be routed to an output device such
as a line printer.

Data directed to or from an external destination is called extrapartition data and consists
of sequential records that are fixed-length or variable-length. The record format for an
extrapartition destination must be defined in the TDD. You cannot delete an extrapartition
queue.
CICS provides three different logical organizations for the byte-stream data stored in
extrapartition queue data files:

Fixed length records


Variable records
Terminated records, which subdivide into:
Line-oriented records
Null-terminated records
Byte-terminated records
Fixed-length record files partition the byte stream into adjacent, non overlapping blocks
of bytes, all of the same length. The size of the block for a given queue may take any
value between 1 and the maximum permitted record size (32767), but must remain fixed
for all records in the file. Users must supply records of the chosen length in an EXEC
CICS WRITEQ TD call and expect to receive a record of that length when performing an
EXEC CICS READQ TD call.

Files whose length is not a multiple of the chosen record size are regarded as incorrectly
formatted and may lead to IOERR conditions being raised if a task attempts to operate on
the corresponding queue.

Variable-length record files partition the file byte stream into adjacent, non-overlapping
blocks of bytes of varying length, each of which is preceded by a two-byte length count
used to determine the length of the following record. The record can be of any length
between 1 and the maximum permitted record size. Users should not supply the length
bytes in the record passed to an EXEC CICS WRITEQ TD call as it is written to the file
by CICS. The record returned on an EXEC CICS READQ TD call will not contain the
length bytes. Refer to the TDD RecordLen attribute description in the CICS
Administration Reference for information on how the permitted record size is established.

The length count is stored in the file high byte first. Applications reading a file written by
CICS may reconstitute the record length by reading the first byte, multiplying it by 256
and then adding the second byte. This should generate a value between 1 and the
maximum permitted record size, giving the size of the following record in bytes. The next
record may be obtained by reading this number of bytes from the file. If another record is
stored in the file (end of file is not reached), the same procedure may be repeated to
obtain subsequent records.

Files with negative or zero record lengths and files whose last record falls short of the last
record length are regarded as incorrectly formatted and may lead to IOERR conditions
being raised if a task attempts to operate on the corresponding queue.

Terminated record files partition the file byte stream into adjacent, nonoverlapping blocks
of bytes of varying length, each of which ends with a common terminating byte. The
three sub-categories correspond to different choices for this terminating byte:
Line-oriented record files employ X'10', the ASCII newline character, as a terminator
(this is particularly useful as a format for queues containing readable text as it allows the
file to be viewed/written using conventional text editors).

Null-terminated record files employ X'00', the ASCII null character, as a terminator.

Byte-terminated record files employ a user-defined byte in the range 0 to 255 as a


terminator (this actually subsumes the preceding categories; they are merely provided as
convenience interfaces to support commonly employed formats).
Users should not append the terminator byte to the record passed to an EXEC CICS
WRITEQ TD call as it is written to the file by CICS. The record returned on an EXEC
CICS READQ TD call will not contain the terminator byte.

Normally, the terminator byte should not appear embedded anywhere in the record
supplied in an EXEC CICS WRITEQ TD call. Any program which subsequently reads
the file will not be able to distinguish such embedded terminator bytes from the byte
appended by the EXEC CICS WRITEQ TD call (this would apply in particular should
the file be reused as the source for an input TD queue). The result of embedding
terminator bytes in the record data will be an apparent fragmentation of the record into
separate sub-records. In the case where a line-oriented queue is employed to write
readable text, this may not be a restriction.

Indirect destinations
Intrapartition and extrapartition destinations can be used as indirect destinations. Indirect
destinations provide some flexibility in program maintenance in that data can be routed to
one of several destinations with only the TDD, not the program, having to be changed.

When the TDD has been changed, application programs continue to route data to the
destination using the original symbolic name; however, this name is now an indirect
destination that refers to the new symbolic name. Because indirect destinations are
established by means of TDD entries, you need not usually be concerned with how this is
done.

Triggered transaction initiation


For intrapartition destinations, CICS provides the option of automatic transaction
initiation. A basis for automatic transaction initiation (ATI) is established by the system
administrator by specifying a nonzero trigger level and a triggered transaction identifier
for a particular intrapartition destination in the TDD. When the number of entries (created
by EXEC CICS WRITEQ TD commands issued by one or more programs) in the queue
(destination) reaches the specified trigger level, the transaction specified in the definition
of the destination is automatically initiated. The transaction must issue repetitive EXEC
CICS READQ TD commands to deplete the queue.
Once the queue has been emptied, a new ATI cycle begins. That is, a new task is
scheduled for initiation when the specified trigger level is again reached, whether or not
execution of the earlier task has ended.

If an automatically initiated task does not empty the queue, access to the queue is not
inhibited. The task may be normally or abnormally ended before the queue is emptied
(that is, before a QZERO condition occurs in response to an EXEC CICS READQ TD
command). Regardless of the facility type, the task is not started until the specified
trigger level is reached. If the triggered transaction does not read from the TD queue, it is
not re-initiated. If the trigger level of a queue is zero, no task is automatically initiated. If
the trigger level is already exceeded because the last triggered transaction abended before
clearing the queue, a task is scheduled the next time a record is written to the queue. To
ensure that completion of an automatically initiated task occurs when the queue is empty,
the application program should test for a QZERO condition rather than for some
application-dependent factor such as an anticipated number of records. Only the QZERO
condition indicates an emptied queue

Temporary storage queue services


CICS temporary storage queue services provide the application programmer with the
ability to store data in temporary storage queues, either in main storage, or in auxiliary
storage on a direct-access storage device. Data stored in a temporary storage queue is
known as temporary data.

You can:

Write data to a temporary storage queue (EXEC CICS WRITEQ TS).

Update data in a temporary storage queue (EXEC CICS WRITEQ TS with the
REWRITE and ITEM options).

Read data from a temporary storage queue (EXEC CICS READQ TS).

Delete a temporary storage queue (EXEC CICS DELETEQ TS).


If TS is omitted, the command is assumed to refer to temporary storage.

Conditions that occur during execution of a temporary storage control command are
handled as described in "Error-handling services".

Naming temporary storage queues


Temporary storage queues are not defined in the region database, but created the first
time you write to that queue. When you write to a queue that does not already exist (and
you have not specified SYSID), CICS creates a new queue, locally based on a Temporary
Storage Definitions (TSD) entry.
Temporary storage queue templates are defined in the region database and in the TSD.
The purpose of the TSD is to determine the attributes given to temporary storage queues
for that region. TSD entry names (the TSD key) can be from one to eight characters long.

Temporary storage queues are identified by symbolic names that must be exactly eight
characters long, assigned by the originating task. When CICS creates a new queue, it tries
to match this eight character name with a TSD entry name, and uses the template name
that matches the most characters at the start of the queue name.

For example, a queue called FIRSTTSQ is to be created by an application. If there is a


TSD entry with a key of FIRSTTSQ for the region, CICS uses this template when
creating FIRSTTSQ. If there is no match, CICS searches for FIRSTTS, then FIRSTT,
then FIRST, and so on.

If no match is found, the queue automatically becomes a non-recoverable, local queue


with private access. Note: TSD entry names that are exactly eight characters long are a
special case. When a queue is written to that exactly matches an eight character TSD
name, the TSD entry becomes a temporary storage queue.

Temporary storage queue names are byte strings, not character strings. They can be made
up from any bytes including binary zeros, and are not null terminated.

If you read from or write to a temporary storage queue using CECI and the name you
pass is shorter than eight bytes, CECI pads the name with spaces. The name is not null
terminated (unlike other names in CICS). The name has pattern matching rules associated
with it that vary depending on whether the queue is local or remote, as explained in
"Temporary Storage Definitions (TSD)" in the CICS Administration Reference.

If you write to a temporary storage queue from a transaction and the queue name is less
than eight characters, CICS reads eight bytes from the start of the queue name, resulting
in unexpected characters at the end of the queue name. Therefore, it is recommended that
you always allocate eight bytes for the temporary storage queue name.

Temporary data can be retrieved by the originating task or by any other task using the
symbolic name assigned to it. Specific items (logical records) within a queue are referred
to by relative position numbers. To avoid conflicts caused by duplicate names, establish a
naming convention. For example, the user identifier, terminal identifier, or transaction
identifier could be used as a prefix or suffix to each programmer-supplied symbolic
name.

TSD entries can resolve to remote temporary storage queue templates, by entering values
for the RemoteSysId and the RemoteName attributes in the TSD. Enter the sysid (up to
four ASCII characters) of the remote region on which the queue is to reside in the
RemoteSysId and the Communications Definitions (CD), and the name of the temporary
storage template on that remote region in the RemoteName. The local temporary storage
queue template name and the remote TSD entry name must be the same length. If you
write to a queue that matches the local template, CICS replaces the template name at the
start of the queue with the remote template name.

For example, you could have a local TSD entry with the name LOCALQ, defined with
RemoteName=REMOTQ and with a RemoteSysid specified. If you write to a queue
called LOCALQXX locally, the queue that is written to on the remote region is called
REMOTQXX.

Deleting temporary storage queues


Temporary storage queues remain intact until they are deleted by the originating task or
by any other task; before deletion, they can be accessed any number of times. Even after
the originating task is terminated, temporary data can be accessed by other tasks through
references to the symbolic name under which it is stored.

You can use the EXEC CICS API on temporary storage queues, but not on TSD entries.
Note: The CICS Administration Reference provides complete descriptions of how to
make changes to the resource definitions.

In the special case where a template name is exactly eight characters long, and the TSD
entry becomes a temporary storage queue, you must use EXEC CICS DELETEQ TS to
delete all items from the queue before you delete this TSD entry using cicsdelete.

Location of temporary data


Temporary data can be stored either in main storage or in auxiliary storage. Generally,
use main storage if the data is needed for short periods of time; use auxiliary storage if
the data is to be kept for long periods of time.

Data stored in auxiliary recoverable temporary storage queues is retained after CICS
termination and can be recovered in a subsequent restart. Data stored in auxiliary non-
recoverable temporary storage queues is retained only across a normal shutdown, but not
across an immediate shutdown or system failure unless a database is being used as the
file manager.

Data stored in main storage is not retained across any type of shutdown and so cannot be
recovered.

Queue aging
Temporary storage has a queue aging facility that automatically deletes queues that have
not been accessed for a specified number of days. The number of days are defined with
the Region Definitions (RD) TSQAgeLimit attribute. The storage occupied by these
queues is freed and becomes available to temporary storage once again.

This feature is useful for temporary storage where queues are created dynamically when
required. It is not needed for files or transient data queues that must be predefined before
use.

Queue attributes
Temporary storage queues are created when they are first written to. Attributes (such as
RemoteSysId, RemoteName, and RecoverFlag) are inherited from the longest matching
queue template found in the TSD.

To use main storage for a queue, use the MAIN option on the EXEC CICS WRITEQ TS
command that writes the first item to the queue. Temporary storage queues use auxiliary
storage by default.

Typical uses of temporary storage control


A temporary storage queue having only one record can be treated as a single unit of data
that can be accessed using its symbolic name. Using temporary storage control in this
way provides a typical scratch pad capability. This type of storage should be accessed
using the EXEC CICS READQ TS command with the ITEM(data area) option; failure to
do so may cause the ITEMERR condition to be raised.

In general, temporary storage queues of more than one record should be used only when
direct access or repeated access to records is necessary; transient data control provides
facilities for efficient handling of sequential files.

Some uses of temporary storage queues follow:

A suspend file. Assume a data collection task is in progress at a terminal. The task reads
one or more units of input and then allows the terminal operator to interrupt the process
by some kind of coded input. If not interrupted, the task repeats the data collection
process. If interrupted, the task writes its incomplete data to temporary storage and
terminates. The terminal is now free to process a different transaction (perhaps a high-
priority inquiry). When the terminal is available to continue data collection, the operator
initiates the task in a resume mode, causing the task to recall its suspended data from
temporary storage and continue as though it had not been interrupted.

Preprinted forms. An application program can accept data to be written as output on a


preprinted form. This data can be stored in temporary storage as it arrives. When all the
data has been stored, it can first be validated and then transmitted in the order required by
the format of the preprinted form.
Data sharing, particularly of scratchpad data, is most suited to temporary storage, as there
is no need to predefine the facility (cf. files).

Paging through large quantities of data. You can read from a file in sections (for example,
10K) and put the sections into a temporary storage queue. Display only as much as the
screen can hold and allow paging up and down. This is quicker than successive file
access, especially if the data is being accessed remotely. This is not recommended if an
update to the file is required.

Você também pode gostar