CICS Scrolling logic with examples

CICS scrolling logic looks very simple in algorithm representation but implementing it practically so many questions arises. This topic is to clear all the queries related to CICS scrolling (page Up / Down) logic with suitable examples.

Let me give few basic points before getting into detailed implementation logic.

  • Decide the number of rows(MAX-SCRN-SIZE) to be displayed on a single screen.
  • First time MAX-SCRN-SIZE rows needs to be displayed and data items that are required for the page up or Page down logic should be stored so as to available for the next execution of the program(i:e It should be available for PF7 or Pf8 transaction execution)
  • For PF8, we need the last key data displayed on the screen and for Pf7, we need the first Key data displayed on the screen. Also we may need one indicator to tell whether the next page exists or not and one variable to tell in Screen number (first screen or 2nd screen or on last screen etc)
  • These data items can be stored either in Commarea or in TSQs.

NOTES →

  • Here I am using COMMAREA to store the data between transactions and VSAM ESDS files as the database.
  • Lets take the example of displaying the Customer latest Bank transactions on the screen.
  • Input for this would be the Customer number
  • Bank transaction data would be stored in a VSAM file.

Declaration →

Declare Commarea fields that are to be preserved for the next execution of the transaction in working storage area like below.

DATA DIVISION.

WORKING-STORAGE SECTION.

** MAP AREA

01 WW-SCREEN.
    05 WW-SCREEN-FEILDS PIC X(10) OCCURS 10 TIMES.

** communication Area

01 WW-COMM-AREA.
   05 WW-CA-LAST-KEY        PIC X(10).
   05 WW-CA-FIRST-KEY       PIC X(10).
   05 WW-CA-SCREEN-NUM      PIC 9(01).
   05 WW-CA-NEXT-PAGE-IND   PIC X(01).
      88 CA-NEXT-PAGE-EXISTS          VALUE 'Y'.
      88 CA-NEXT-PAGE-NOT-EXISTS      VALUE 'N'.

** WW-COMM-AREA is used in RETRUN after sending the map***

LINKAGE SECTION.

01 DFHCOMMAREA.
    05 LK-COMM-AREA PIC X(11).

LK-COMM-AREA is used to receive the data in next transaction.

Procedure Division.

A000-MAINPARA.
*
EXEC CICS HANDLE ABEND
     LABEL(Z9999-ABEND-PARA)
END-EXEC

In case if the Formatted date & time are needed

EXEC CICS ASKTIME
     ABSTIME(WW-ABS-TIME)
END-EXEC

EXEC CICS FORMATTIME
    ABSTIME(WW-ABS-TIME)
    YYYYMMDD(WW--DATE)
    TIME(WW-TIME)
END-EXEC

IF EIBCALEN=0–> Do nothing, just return the control back to CICS and clear the screen

IF EIBCALEN = ZERO
   EXEC CICS SEND CONTROL
       ERASE
       FREEKB
   END-EXEC
   EXEC CICS RETURN END-EXEC.
END-IF
MOVE DFHCOMMAREA TO WW-COMM-AREA

First time, Nothing will be in DFHCOMMAREA, but in PF7/PF8 case Last Key, First Key and Page Exists indicator would be present as these items would be sent in RETURN command.

Receive the map and check the response. If it is normal proceed further.

EXEC CICS RECEIVE MAP(MAP1)
     MAPSET(MAP1-SET)
     INTO(WW-MAP1)
     RESP(WW-RESP)
END-EXEC

EVALUATE TRUE
  WHEN ENTER
       PERFORM A100-GET-INITIAL-DATA
  WHEN PFKEY7
       PERFORM A200-SCROLL-UP
  WHEN PFKEY8
       PERFORM A300-SCROLL-DOWN
END-EVALUATE .

A100-GET-INITIAL-DATA .

  • Start Browse using the input Key
  • Read thru the file until it reaches the MAX-SCRN-SIZE or no more records are present.
  • Save the first record & Last record key in Commarea fields
  • Once all the screen is filled to its MAX size, check whether the next record in the file exists or not and set the COMMAREA Next page indicator accordingly.
  • Send map And issue a RETURN command
ADD +1 TO WW-CA-SCREEN-NUM
EXEC CICS STARTBR
    DATASET(WW-FILE-NAME)
    RIDFLD(WW-KEY)
    KEYLENGTH(WW-KEY-LNGTH)
    RESP(WW-RESP)
END-EXEC

MOVE ZEROES TO WW-SCRN-SIZE-COUNTER
SET CA-NEXT-PAGE-NOT-EXISTS TO TRUE

PERFORM UNTIL END-OF-PROCESS
    EXEC CICS READNEXT
         DATASET(-FILE-NAME)
         INTO(WW-FILE-DATA)
         LENGTH(WW-FILE-LNGTH)
         RIDFLD(WW-KEY)
         KEYLENGTH(WW-KEY-LNGTH)
         RESP(WS-RESP)
    END-EXEC

    IF SUCCESS
       ADD +1 TO WW-SCRN-COUNTER
       MOVE WW-FILE-DATA TO WW-SCREEN-FEILDS(WW-SCRN-COUNTER)
       IF WW-SCRN-COUNTER = 1
** Communication area field to be used in PF7/8 logic
         MOVE WW-KEY TO WW-CA-FIRST-KEY
       END-IF

       IF WW-SCRN-SIZE-COUNTER = MAX-SCRN-SIZE
          SET END-OF-PROCESS TO TRUE
** Communication area field to be used in PF7/8 logic
          MOVE WW-KEY TO WW-CA-LAST-KEY
*** This is to check whether the next record exists or not
          EXEC CICS READNEXT
               DATASET(-FILE-NAME)
               INTO(WW-FILE-DATA)
               LENGTH(WW-FILE-LNGTH)
               RIDFLD(WW-KEY)
               KEYLENGTH(WW-KEY-LNGTH)
               RESP(WS-RESP)
          END-EXEC

          IF RECORD-FND
             SET CA-NEXT-PAGE-EXISTS TO TRUE
          END-IF
       END-IF
   ELSE
       IF NO-RECORDS-IN-FILE
          SET END-OF-PROCESS TO TRUE
       END-IF
   END-IF
END-PERFORM

** Send the map & Issue a return command with Commarea

PERFORM A999-SEND-MAP-AND-RETURN.

A200-SCROLL-UP.

  • Get the Communication area into working storage
  • Check the screen number, If it is in the first page itself, Then no scrolling is possible
  • Otherwise move the Stored first key of previous screen to Key field to set the browsing point
  • Start reading the previous records from that point and set the counters accordingly and populate the screen fields.
  • Once all the screen fields are populated, populate the communication area fields.
  • Send Map and issue a return command with COMMAREA option.
MOVE DFHCOMMAREA TO WW-COMM-AREA

IF WW-CA-SCREEN-NUM = 1
   MOVE 'ALREADY AT THE FIRST PAGE' TO SCREEN-WARNING-MSG
**send map & return
   PERFORM A999-SEND-MAP-AND-RETURN
ELSE
   MOVE WW-CA-FIRST-KEY TO WW-KEY
** Issue a Start Browse and read previous records from that point
   EXEC CICS STARTBR
        DATASET(WW-FILE-NAME)
        RIDFLD(WW-KEY)
        KEYLENGTH(WW-KEY-LNGTH)
        RESP(WW-RESP)
   END-EXEC

   MOVE MAX-SCRN-SIZE TO WW-SCRN-SIZE-COUNTER
   SET CA-NEXT-PAGE-EXISTS TO TRUE

   PERFORM UNTIL END-OF-PROCESS

     EXEC CICS READPREV
          DATASET(-FILE-NAME)
          INTO(WW-FILE-DATA)
          LENGTH(WW-FILE-LNGTH)
          RIDFLD(WW-KEY)
          KEYLENGTH(WW-KEY-LNGTH)
          RESP(WS-RESP)
     END-EXEC
     IF SUCCESS
        MOVE WW-FILE-DATA TO WW-SCREEN-FEILDS(WW-SCRN-COUNTER)
        IF WW-SCRN-COUNTER = 1
** Communication area field to be used in PF7/8 logic
          SET END-OF-PROCESS TO TRUE
          MOVE WW-KEY TO WW-CA-FIRST-KEY
        END-IF

        IF WW-SCRN-SIZE-COUNTER = MAX-SCRN-SIZE
** Communication area field to be used in PF7/8 logic
           MOVE WW-KEY TO WW-CA-LAST-KEY
        END-IF
     ELSE
        IF NO-RECORDS-IN-FILE
           SET END-OF-PROCESS TO TRUE
        END-IF
     END-IF
     SUBTRACT 1 FROM WW-SCRN-COUNTER
END-PERFORM

** Send the map & Issue a return command with Commarea
PERFORM A999-SEND-MAP-AND-RETURN

A300-SCROLL-DOWN.

  • Get the Communication area into working storage.
  • Check whether Next page exists or not using the indicator variable of COMMAREA
  • If it does not exists send a suitable message to screen along with the current map.
  • If it exists perform the same logic as A000 para and populate the ww-comm-area fields and send MAP and Issue RETURN command with COMMAREA option.
MOVE DFHCOMMAREA TO WW-COMM-AREA

IF CA-NEXT-PAGE-EXISTS
    ADD +1 TO WW-CA-SCREEN-NUM
    MOVE WW-CA-LAST-KEY TO WW-KEY
ELSE
    MOVE 'Further scrolling not possible ' to SCREEN-WARNING-MSG
END-IF.

A999-SEND-MAP-AND-RETURN.

EXEC CICS SEND MAP(MAP1)
     MAPSET(MAP1-SET)
     FROM(WW-SCREEN)
     CURSOR
     ERASE
     RESP(WW-RESP)
END-EXEC

EXEC CICS RETURN
     TRANSID(MAP1-TRAN) 
     COMMAREA(WW-COMM-AREA)
     LENGTH(WW-COMM-AREA-LGTH)
END-EXEC.
2 Comments

Leave a Reply to Ankita Cancel reply

Your email address will not be published. Required fields are marked *

Close Bitnami banner