Joined: 29 Nov 2002 Posts: 382 Topics: 27 Location: Chennai, India
Posted: Tue Mar 25, 2003 4:21 am Post subject:
Thanks a lot Glenn for your long and patient answer. It would be great if you can post the example. It would also be great if you could provide some more inputs regarding the last idea of yours - the one in which you use the shareable TSQ. How do you keep track of all the transactions and users using the TSQ. How do you know that the time has come to delete the TSQ when none of the users are using it. And some more inputs on the mechanism you would use to keep the data consistent and sorted in the TSQ would be really helpful.
Thanks again for your help.
Example - untested (it was a working production program but changed it to try to relate it to this and remove other business related logic and leave the browse part). The basic idea is there...if you have any questions or I forgot to change something, just ask...
IDENTIFICATION DIVISION.
PROGRAM-ID. SAMPLE.
*--------------------------------------------------------------*
* AUTHOR: Glenn
*
* Sample program to browse data in EMP_TABLE (10 items/screen):
* Columns: EMP_ID (primary unique key) , EMP_NAME
* Free for general use, credit Glenn/MVSFORUMS.COM
*--------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*
EXEC SQL
INCLUDE SQLCA
END-EXEC.
*
****************************************************************
* START SAMPLE SYMBOLIC MAP. DEFINED LIKE THIS SO 10 ITEMS CAN
* BE IN A TABLE FOR THE PROGRAM.
****************************************************************
01 SAMPLE-MAP.
04 SAMPLE-TABLE.
08 SAMPLE-MAPGROUP OCCURS 10 TIMES
INDEXED BY SAMPLE-NDX.
12 SAMPLE-CHKL PIC S9(4) COMP.
12 SAMPLE-CHKA PIC X.
12 SAMPLE-CHKI PIC X.
12 SAMPLE-EMPIDL PIC S9(4) COMP.
12 SAMPLE-EMPIDA PIC X.
12 SAMPLE-EMPIDI PIC X(09).
12 SAMPLE-EMPNAMEL PIC S9(4) COMP.
12 SAMPLE-EMPNAMEA PIC X.
12 SAMPLE-EMPNAMEI PIC X(35).
04 SAMPLE-MSGL PIC S9(4) COMP.
04 SAMPLE-MSGA PIC X.
04 SAMPLE-MSGI PIC X(60).
04 SAMPLE-F7L PIC S9(4) COMP.
04 SAMPLE-F7A PIC X.
04 SAMPLE-F7I PIC X(09).
04 SAMPLE-F8L PIC S9(4) COMP.
04 SAMPLE-F8A PIC X.
04 SAMPLE-F8I PIC X(09).
****************************************************************
* END SAMPLE SYMBOLIC MAP.
****************************************************************
01 PROCESSING-VARIABLES.
04 END-SESSION-MSG PIC X(30) VALUE
'NORMAL END OF SESSION OCCURRED'.
04 CHOICE-MADE PIC S9(4) BINARY VALUE ZERO.
04 SQL-EMP-ID PIC X(09).
04 SQL-EMP-NAME PIC X(35)
04 SQL-EOF PIC S9(4) BINARY.
04 INDEX-VENDOR PIC X(09).
04 TS-QUEUE-NAME.
08 TRANSACTION-ID PIC X(04).
08 TERMINAL-ID PIC X(04).
04 VALID-DATA-SWITCH PIC X VALUE 'Y'.
88 VALID-DATA VALUE 'Y'.
88 NOT-VALID-DATA VALUE 'N'.
0500-RESET-VALUES SECTION.
MOVE 1 TO SAMPLE-SCREEN-NUM.
MOVE 0 TO SAMPLE-TOTAL-SCREENS.
MOVE SPACES TO SAMPLE-EMP-ID.
EXEC CICS
IGNORE CONDITION QIDERR
END-EXEC.
EXEC CICS
DELETEQ TS QUEUE(SAMPLE-QUEUE)
END-EXEC.
1000-START-SESSION SECTION.
MOVE EIBTRMID TO TERMINAL-ID.
MOVE EIBTRNID TO TRANSACTION-ID.
MOVE TS-QUEUE-NAME TO SAMPLE-QUEUE.
PERFORM 0500-RESET-VALUES.
PERFORM 1710-LOAD-FROM-TABLE.
MOVE -1 TO SAMPLE-CHKL (1).
PERFORM 1010-SAMPLE-TIME.
MOVE 1 TO SAMPLE-STATUS-POINT.
EXEC CICS
SEND MAP('SAMPLE')
MAPSET('SAM1001')
FROM(SAMPLE-MAP)
CURSOR ERASE
END-EXEC.
1010-SAMPLE-TIME SECTION.
IF SAMPLE-SCREEN-NUM = 1
MOVE SPACES TO SAMPLE-F7I
ELSE
MOVE 'PF7-UP' TO SAMPLE-F7I
END-IF.
IF SAMPLE-SCREEN-NUM = SAMPLE-TOTAL-SCREENS
MOVE SPACES TO SAMPLE-F8I
ELSE
MOVE 'PF8-DOWN' TO SAMPLE-F8I
END-IF.
1100-PROCESS-SAMPLE-MAP SECTION.
EXEC CICS
HANDLE AID PF8(1100-PF8-PROCESS)
PF7(1100-PF7-PROCESS)
PF3(1100-PF3-PROCESS)
CLEAR(1100-PF3-PROCESS)
PF12(1100-PF12-PROCESS)
ANYKEY(1100-ANYKEY-PROCESS)
END-EXEC.
EXEC CICS
RECEIVE MAP('SAMPLE')
MAPSET('SAM1001')
INTO(SAMPLE-MAP)
END-EXEC.
PERFORM 1200-CHECK-SAMPLE.
IF VALID-DATA
PERFORM 9999-RETURN
END-IF.
GO TO 1100-EXIT.
1100-PF8-PROCESS.
IF SAMPLE-SCREEN-NUM = SAMPLE-TOTAL-SCREENS
MOVE 'INVALID KEY PRESSED' TO SAMPLE-MSGI
ELSE
ADD 1 TO SAMPLE-SCREEN-NUM
PERFORM 1700-RELOAD-TABLES
MOVE SPACES TO SAMPLE-MSGI
END-IF.
MOVE -1 TO SAMPLE-CHKL (1).
GO TO 1100-EXIT.
1100-PF7-PROCESS.
IF SAMPLE-SCREEN-NUM = 1
MOVE 'INVALID KEY PRESSED' TO SAMPLE-MSGI
ELSE
SUBTRACT 1 FROM SAMPLE-SCREEN-NUM
PERFORM 1700-RELOAD-TABLES
MOVE SPACES TO SAMPLE-MSGI
END-IF.
MOVE -1 TO SAMPLE-CHKL (1).
GO TO 1100-EXIT.
1100-PF3-PROCESS.
PERFORM 9999-RETURN.
1100-ANYKEY-PROCESS.
MOVE -1 TO SAMPLE-CHKL (1).
MOVE 'INVALID KEY PRESSED' TO SAMPLE-MSGI.
GO TO 1100-EXIT.
1100-EXIT.
EXIT.
1200-CHECK-SAMPLE SECTION.
MOVE 0 TO CHOICE-MADE.
PERFORM 1230-SAMPLE-MAP-CHECKS
VARYING SAMPLE-NDX FROM 1 BY 1 UNTIL
SAMPLE-NDX > 10 OR (NOT-VALID-DATA)
IF VALID-DATA AND CHOICE-MADE = 0
SET NOT-VALID-DATA TO TRUE
MOVE -1 TO SAMPLE-CHKL (1)
MOVE 'YOU MUST CHOOSE AN OPTION' TO SAMPLE-MSGI
END-IF.
1230-SAMPLE-MAP-CHECKS SECTION.
IF SAMPLE-CHKI (SAMPLE-NDX) NOT = 'X' AND '_' AND ' '
MOVE -1 TO SAMPLE-CHKL (SAMPLE-NDX)
MOVE 'AN X MUST BE USED TO SELECT AN ITEM' TO
SAMPLE-MSGI
SET NOT-VALID-DATA TO TRUE
END-IF.
IF SAMPLE-CHKI (SAMPLE-NDX) = 'X' AND VALID-DATA
IF SAMPLE-VENI (SAMPLE-NDX) = SPACES
MOVE -1 TO SAMPLE-CHKL (SAMPLE-NDX)
MOVE 'THIS IS NOT A VALID CHOICE' TO
SAMPLE-MSGI
SET NOT-VALID-DATA TO TRUE
ELSE
SET CHOICE-MADE TO SAMPLE-NDX
END-IF
END-IF.
1700-RELOAD-TABLES SECTION.
EXEC CICS
HANDLE CONDITION ITEMERR(1700-ITEMERR)
END-EXEC.
EXEC CICS
READQ TS QUEUE(SAMPLE-QUEUE)
INTO(SAMPLE-TABLE)
LENGTH(LENGTH OF SAMPLE-TABLE)
ITEM(SAMPLE-SCREEN-NUM)
END-EXEC.
GO TO 1700-EXIT.
1700-ITEMERR.
PERFORM 1710-LOAD-FROM-TABLE.
GO TO 1700-EXIT.
1700-EXIT.
EXIT.
1710-LOAD-FROM-TABLE SECTION.
MOVE SAMPLE-EMP-ID TO INDEX-EMP-ID.
*++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++*
* FOR STATEMENT BELOW WHEN DB2 5.2 OR ABOVE PRECOMPILER IS *
* INSTALLED, MAY REMOVE "OPTIMIZE FOR 10 ROWS" AND "FOR READ *
* ONLY" LINES AND REPLACE THEM WITH "FETCH FIRST 10 ROWS *
* ONLY". THIS DOES THE SAME AS THE LINES ALREADY SPECIFIED *
* BUT WILL ONLY RETRIEVE 10 ROWS INTO THE RESULT TABLE *
*++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++*
EXEC SQL
DECLARE C-1 CURSOR FOR
SELECT EMP_ID, EMP_NAME
FROM EMP_TABLE
WHERE EMP_ID > :INDEX-EMP-ID
ORDER BY EMP_ID
OPTIMIZE FOR 10 ROWS
FOR READ ONLY
END-EXEC.
EXEC SQL
OPEN C-1
END-EXEC.
IF SQLCODE NOT = 0
PERFORM 9000-SQL-ERROR
END-IF.
PERFORM 1720-FETCH-SAMPLE
PERFORM VARYING SAMPLE-NDX FROM 1 BY 1 UNTIL SAMPLE-NDX > 10
IF SQL-EOF = 0
MOVE SQL-EMP-ID TO SAMPLE-EMPIDI (SAMPLE-NDX)
MOVE SQL-EMP-NAME TO SAMPLE-EMPNAMEI (SAMPLE-NDX)
PERFORM 1720-FETCH-SAMPLE
ELSE
MOVE SPACES TO SAMPLE-EMPIDI (SAMPLE-NDX)
SAMPLE-EMPNAMEI (SAMPLE-NDX)
END-IF
END-PERFORM.
EXEC SQL
CLOSE C-1
END-EXEC.
MOVE SAMPLE-EMPIDI (10) TO SAMPLE-EMP-ID.
IF SQLCODE NOT = 0
PERFORM 9000-SQL-ERROR
END-IF.
IF SQL-EOF = 1
MOVE SAMPLE-SCREEN-NUM TO SAMPLE-TOTAL-SCREENS
END-IF.
EXEC CICS
WRITEQ TS QUEUE(SAMPLE-QUEUE)
FROM(SAMPLE-TABLE)
LENGTH(LENGTH OF SAMPLE-TABLE)
MAIN
END-EXEC.
1720-FETCH-SAMPLE SECTION.
EXEC SQL
FETCH C-1 INTO :SQL-EMP-ID, :SQL-EMP-NAME
END-EXEC
IF SQLCODE NOT = 0
IF SQLCODE = +100
MOVE 1 TO SQL-EOF
ELSE
PERFORM 9000-SQL-ERROR
END-IF
END-IF.
Joined: 29 Nov 2002 Posts: 382 Topics: 27 Location: Chennai, India
Posted: Tue Mar 25, 2003 11:21 pm Post subject:
Hi Glenn,
Thanks a lot for the code. I got the idea. It would be great if you can provide some inputs about the last idea of yours - Making the TSQ shareable across transactions. As you had said, one has to create the TSQ when the very first instance of the transaction runs and all the instances of the transactions running on different terminals will access the same TSQ. The TSQ will be deleted only when all the transactions running on different terminals and by different users have ended. How do you ensure that?. And how do you maintain the data integrity and sort order on the TSQ in that case. Please refer to the last part of my previous post. Can you please provide me with some pointers on that.
The shared TSQ idea...basically I've told you most of where the idea got brought (there's no code present for it, none was attempted there wasn't enough time to even think the thought out or attempt coding it). Just an idea, nothing really was tried in practice. Of course, this would be very dependent on how the data are handled, how much it is updated, and how you want to handle updates with the transactions. Updating the TSQ would be very iffy with the thought of keeping the data sorted - how do you handle inserting and deleting data , would it pay to rewrite the whole queue? Updating is an easy one if you don't change the key, changing the key is essentially a delete and insert. Is it worth trying to update this TSQ as present or use a completely different approach like a balanced binary search tree?
I did give this a little more thought yesterday. One thought I did have which seems workable and easy enough to set up is this:
1) Put out a second TSQ which is essentially permanent. It holds the number of transactions active and a flag on whether the data were updated or not. The # of transactions active flag is updated when a transaction initially starts and when it finishes (ADD 1 TO TRANSACTIONS, REWRITE QUEUE).
2) When data are inserted, updated or deleted on the table, update the DATA-CHANGED field in the new TSQ.
3) When a transaction starts up (1000-START-SESSION in the code I posted) and adds itself to the transaction record, it checks whether the data changed flag is set. If TRANSACTIONS > 0, it calls the 1700 paragraph, otherwise the 1710 paragraph. This code would reside where the 1710 paragraph is called right now in the 1000 paragraph.
4) At the end of the transaction, if TRANSACTIONS = 1 is set, the queue could be deleted...
Of course, like the solution I posted the code for, it's very data change dependent. This means data changes might not show up for quite a while, at least until all users are off the browse transaction. This may not fit with user requirements very well.
I'm very hesitant to change the TSQ in memory for that data integrity reason - how it would affect the browse transactions currently being run? How do you handle sudden "partial" screens? And how would rewriting part or the whole TSQ affect system performance, especially considering this would be a true heavily shared resouce and browse transactions would be accessing it as well? Is there a better approach to this? Actually a doubly-linked linear list would be perfectly ideal in this situation in place of a table (which is what TSQ is) if there were a way to set it up under CICS and ensure sequential updates (i.e. two transactions aren't updating it at the same time). The data would be dynamic and a value could be easily inserted or deleted in the chain.
Definitely an interesting exercise and something that could use a lot more thought.
All times are GMT - 5 Hours Goto page Previous1, 2
Page 2 of 2
You cannot post new topics in this forum You cannot reply to topics in this forum You cannot edit your posts in this forum You cannot delete your posts in this forum You cannot vote in polls in this forum