You are on page 1of 5

Paging logic or scrolling logic

http://ibmmainframes.com/viewtopic.php?t=28964&highlight=paging

There are multiple methods, but here is one that has worked successfully for me. By your
description, you are trying to display multiple records on a given screen, and you are
writing a single row to the TS Queue for every record you want to display on the screen.
You also want to be able to Page Forward and Backward between the screens. Based on
these assumptions, this is what my example will be guiding you thru. I am also going to
assume that you have studied and understand the basics of TS Queues as well as knowing
the basics of COBOL in a CICS command level environment.

The code below is NOT exact code or even all the code, but a general example of a
process to load and access your TS Queue. I’m using a VSAM example. A DB2 FETCH
or IMS call could easily be substituted.

The key to this simplistic method is to capture and store two values in your commarea.
The first is NUMITEMS, which is an option of the WRITEQ TS command, defined as a
binary halfword:

03 CA-NUMITEMS PIC S9(04) COMP VALUE ZEROS.

The second is ITEM, which you will use as an option of the READQ TS command,
defined as a binary halfword:

03 CA-ITEM PIC S9(04) COMP VALUE +1.

Let’s say you want to display 10 records on every screen (I will use ‘map’
interchangeably with screen) along with 5 columns for every record. Define a table in
working storage that has 10 occurrences:

01 TSQ-PAGE-TABLE.
03 TSQ-PAGE-ENTRY OCCURS 10 TIMES.
05 TSQ-RECORD.
07 TSQ-REC-ELEMENT-1 PIC X(05) VALUE SPACES.
07 TSQ-REC-ELEMENT-2 PIC X(10) VALUE SPACES.
07 TSQ-REC-ELEMENT-3 PIC X(05) VALUE SPACES.
07 TSQ-REC-ELEMENT-4 PIC X(08) VALUE SPACES.

(You will probably want to redefine the output part of your symbolic map as a table that
occurs 10 times … easier, consistent processing later in your code).

Now you want to perform logic, as part of your first time in process (or maybe after some
key values were entered on the screen for specific data retrieval), that will ‘read input,
load the page table, writeq the page table’ until you have reached some ending condition.
The important thing here is that when you have completed loading the TS Queue, CA-
NUMITEMS will contain a constant value of the total number of items (in this case
‘pages’) in the Queue. (Constant unless you issue more writeqs for some odd reason …
and there are those odd reasons)
Read thru your file (generic), until you’ve reached end-of-file or some other condition,
and load the TSQ table with up to 10 records. After the 10th record is loaded, write the
TS Queue from TSQ-PAGE-TABLE. CA-NUMITEMS is updated with the total number
of items (pages) in the TS Queue every time you writeq a “Page” of records.

Once you’ve successfully loaded the queue, you want to load the screen with what is in
the queue. So you READQ TS, (CA-ITEM is initially +1 so you will get the first page),
move the TSQ-REC-ELEMENT-1 thru 5 (TSQ-SUB) to their respective map elements,
set the display attributes, send the map and then return to your transaction.

You now will always know where you are in your paging (PF7 / PF8) process. If PF7 is
pressed, you compute the ITEM (page) you want to access from the TS queue, by
subtracting 1 from the current ITEM, which is stored in CA-ITEM. If the resulting value
is 0*, you know you are already at the first page and can send a message accordingly,
otherwise, you use the result value to retrieve the corresponding page (ITEM) from the
TS queue, load the map fields, set the attributes, send the map and return to the
transaction.

The process is basically the same for PF8, except that you compute the ITEM (page) you
want to access by adding 1 to the current ITEM (page) which is stored in CA-ITEM. If
the resulting value is greater than the last possible page, i.e. *CA-NUMITEMS, then you
are already at the last page and can send a message accordingly, otherwise you use the
result value to retrieve the corresponding page (ITEM) from the TS Queue, load the map
fields, set the attributes, send the map and return to the transaction.

*Note: If resulting value is 0, reset CA-ITEM back to +1. If resulting value is greater than
CA-NUMITEMS, reset CA-ITEM to CA-NUMITEMS.

By capturing these values, not only will you always know where you are in your paging,
you can display a “page number of page numbers” on the screen, something like “PAGE:
16 OF 250”. If you open page number for entry, you can go directly to the page. These
are “features” that customers/users like to see.

First time loading and retrieving the TS Queue:


A100-SOME-PARA-NAME.

PERFORM
UNTIL NO-MORE-RECORDS OR SOME-ERROR

EXEC CICS READNEXT ….

IF RESP-CODE = ZEROS
IF TSQ-SUB > 10
PERFORM A999-WRITEQ-TS THRU A999-EXIT
ELSE
ADD 1 TO TSQ-SUB
MOVE record elements TO TSQ-REC-ELEMENT-1 thru 5 (TSQ-SUB)
END-IF
ELSE
IF RESP-CODE = DFHRESP(NOTFND) OR DFHRESP(ENDFILE)
SET NO-MORE-RECORDS TO TRUE
IF TSQ-SUB > 0
PERFORM A999-WRITEQ-TS THRU A999-EXIT
END-IF
ELSE
SET SOME-ERROR TO TRUE
END-IF
END-IF
END-PERFORM.

IF SOME-ERROR
PERFORM some error routine ….
END-IF.

PERFORM Y000-READQ-TS THRU Y000-EXIT.


PERFORM Z900-LOAD-MAP THRU Z900-EXIT.
PERFORM Z997-SEND-MAP THRU Z997-EXIT.
PERFORM Z998-RETURN-TRANSID THRU Z998-EXIT.

A100-EXIT.
EXIT.

A999-WRITEQ-TS.

EXEC CICS WRITEQ TS QUEUE (name)


FROM (TSQ-PAGE-TABLE)
NUMITEMS (CA-NUMITEMS)
RESP (RESP-CODE)
END-EXEC.

IF RESP-CODE = ZEROS
INITIALIZE TSQ-PAGE-TABLE
MOVE ZEROS TO TSQ-SUB
ELSE
SET SOME-ERROR TO TRUE
END-IF.

A999-EXIT.
EXIT.
Paging process – Reached only if EIBAID is DFHPF7 or DFHPF8
P000-PAGING-PROCESS.

IF EIBAID = DFHPF7
COMPUTE CA-ITEM = CA-ITEM – 1
END-COMPUTE
IF CA-ITEM = 0
MOVE +1 TO CA-ITEM
MOVE first page message to message area on the map
ELSE
PERFORM Y000-READQ-TS THRU Y000-EXIT
PERFORM Z900-LOAD-MAP THRU Z900-EXIT
END-IF
ELSE
COMPUTE CA-ITEM = CA-NUMITEMS + 1
END-COMPUTE
IF CA-ITEM > CA-NUMITEMS
MOVE CA-NUMITEMS TO CA-ITEM
MOVE last page message to message area on the map
ELSE
PERFORM Y000-READQ-TS THRU Y000-EXIT
PERFORM Z900-LOAD-MAP THRU Z900-EXIT
END-IF
END-IF.

PERFORM Z997-SEND-MAP THRU Z997-EXIT.


PERFORM Z998-RETURN-TRANSID THRU Z998-EXIT.

P000-EXIT.
EXIT.

Support paragraphs -
Y000-READQ-TS.

EXEC CICS READQ TS QUEUE (name)


INTO (TSQ-PAGE-TABLE)
ITEM (CA-ITEM)
RESP (RESP-CODE)
END-EXEC.

IF RESP-CODE > ZEROS


PERFORM some error routine
END-IF.

Y000-EXIT.
EXIT.

Z900-LOAD-MAP.

PEFORM VARYING TSQ-SUB FROM 1 BY 1


UNTIL TSQ-SUB > 10
MOVE TSQ-REC-ELEMENT-1 thru 5 (TSQ-SUB) TO
MAP-REC-ELEMENT-1 thru 5 (TSQ-SUB) – redefined symbolic map
END-PERFORM.

Z900-EXIT.
EXIT.

Z997-SEND-MAP.

Set map field attributes, date & time, page number, etc …

EXEC CICS SEND MAP ….

Z997-EXIT.
EXIT.

Z998-RETURN-TRANSID
EXEC CICS RETURN TRANSID ….

Z998-EXIT.
EXIT.

You might also like