CBL XOPTS(ANSI85)
CBL NODYNAM,LIB,OBJECT,RENT,RES,APOST,NUMPROC(NOPFD)
* ------------------------------------------------------------- *
IDENTIFICATION DIVISION.
* ------------------------------------------------------------- *
PROGRAM-ID. CSQ4CVD3.
*REMARKS
* ************************************************************* *
* @START_COPYRIGHT@ *
* Statement: Licensed Materials - Property of IBM *
* *
* 5695-137 *
* (C) Copyright IBM Corporation. 1993, 1997 *
* *
* Status: Version 1 Release 2 *
* @END_COPYRIGHT@ *
* ************************************************************* *
* *
* Product Number : 5695-137 *
* *
* Module Name : CSQ4CVD3 *
* *
* Environment : CICS/ESA Version 3.3; COBOL II *
* *
* Function : This program provides the display chosen *
* message function for the mail manager *
* sample. *
* See IBM MQSeries for MVS/ESA *
* Application Programming Reference, *
* for further details. *
* *
* Description : This program displays the chosen message *
* using panel MAIL-VD3 until the user *
* presses PF3. *
* *
* ************************************************************* *
* *
* Program Logic *
* ------------- *
* *
* Start (A-MAIN SECTION) *
* ----- *
* Initialize the variable for the get call *
* Get the chosen message *
* If the get fails *
* Build an error message *
* Else *
* Move the message details into the screen map *
* End-if *
* *
* Do while PF3 is not pressed *
* If Help (PF1) key pressed *
* Display the help screen until PF12 is pressed *
* Else *
* Display the received mail screen (MAIL-VD3) *
* End-if *
* End-do *
* *
* Return to CICS *
* *
* *
* DISPLAY-HELP SECTION *
* -------------------- *
* Do until PF12 key is pressed *
* Exec CICS send help screen map *
* Exec CICS receive help screen map *
* End-do *
* *
* Return to performing section *
* *
* ************************************************************* *
* ------------------------------------------------------------- *
ENVIRONMENT DIVISION.
* ------------------------------------------------------------- *
* ------------------------------------------------------------- *
DATA DIVISION.
* ------------------------------------------------------------- *
WORKING-STORAGE SECTION.
* ------------------------------------------------------------- *
*
* W00 - General work fields
*
01 W00-RECD-MAILQ.
05 PIC X(17).
05 W00-SENT-FROM PIC X(08) VALUE SPACES.
05 PIC X(23).
*
* W01 - MQM API fields
*
01 W01-DATA-LENGTH PIC S9(9) BINARY.
01 W01-COMPCODE PIC S9(9) BINARY VALUE ZERO.
01 W01-REASON PIC S9(9) BINARY VALUE ZERO.
*
* W02 - Screen map name definitions
*
01 W02-MAPSET-NAME PIC X(08) VALUE 'CSQ4VDM'.
01 W02-CSQ4VD3 PIC X(08) VALUE 'CSQ4VD3'.
01 W02-CSQ4VD6 PIC X(08) VALUE 'CSQ4VD6'.
*
* Fields used for communication between programs in mail
* manager sample
*
COPY CSQ4VD3.
*
* Mail manager message definition
*
COPY CSQ4VD4.
*
* The following copy book contains messages that will be
* displayed to the user
*
COPY CSQ4VD0.
*
* Screen map definitions used by this sample program
*
COPY CSQ4VDM.
*
* DFHAID contains the constants used for checking for
* attention identifiers
*
COPY DFHAID SUPPRESS.
*
* API control blocks
*
01 W05-MQM-OBJECT-DESCRIPTOR.
COPY CMQODV SUPPRESS.
01 W05-MQM-MESSAGE-DESCRIPTOR.
COPY CMQMDV SUPPRESS.
01 W05-MQM-GET-MESSAGE-OPTIONS.
COPY CMQGMOV SUPPRESS.
*
* Copy book of constants (for filling in the control blocks)
* and return codes (for testing the result of a call)
*
01 CMQV.
COPY CMQV SUPPRESS.
EJECT
* ------------------------------------------------------------- *
LINKAGE SECTION.
01 DFHCOMMAREA PIC X(200).
* ------------------------------------------------------------- *
EJECT
* ------------------------------------------------------------- *
PROCEDURE DIVISION.
* ------------------------------------------------------------- *
* ------------------------------------------------------------- *
A-MAIN SECTION.
* ------------------------------------------------------------- *
* *
* This section gets the chosen message and displays it until *
* the user presses PF3. *
* *
* ------------------------------------------------------------- *
*
* Get the commarea passed
*
IF EIBCALEN = 0 THEN
Move VD0-MESSAGE-27 TO VD3-MSG
GO TO A-MAIN-EXIT
END-IF.
MOVE DFHCOMMAREA TO VD3-MAIL-COMMAREA.
*
MOVE LOW-VALUES TO CSQ4VD3O.
*
* Initialise the variables for the get call
*
MOVE MQGMO-SYNCPOINT TO MQGMO-OPTIONS.
ADD MQGMO-NO-WAIT TO MQGMO-OPTIONS.
MOVE VD3-MSGID TO MQMD-MSGID.
MOVE VD3-CORRELID TO MQMD-CORRELID.
*
* Get the chosen message
*
CALL 'MQGET' USING VD3-HCONN
VD3-HOBJ
MQMD
MQGMO
VD4-MSG-LENGTH
VD4-MESSAGE
W01-DATA-LENGTH
W01-COMPCODE
W01-REASON.
*
* If the call fails build an error message, otherwise
* prepare the screen fields and display the message
*
IF W01-COMPCODE NOT = MQCC-OK
MOVE 'GET MSG' TO VD0-MSG1-TYPE
MOVE W01-COMPCODE TO VD0-MSG1-COMPCODE
MOVE W01-REASON TO VD0-MSG1-REASON
MOVE VD0-MESSAGE-1 TO VD3MSG1O
ELSE
*
MOVE VD3-USERID TO VD3IDO
MOVE VD3-SUBSYS TO VD3QMO
*
MOVE MQMD-REPLYTOQ TO W00-RECD-MAILQ
MOVE W00-SENT-FROM TO VD3USERO
*
MOVE MQMD-REPLYTOQMGR TO VD3QMGRO
MOVE VD3-DISPDATE TO VD3DATEO
MOVE VD3-DISPTIME TO VD3TIMEO
MOVE MSGL1 TO VD3L1O
MOVE MSGL2 TO VD3L2O
MOVE MSGL3 TO VD3L3O
MOVE MSGL4 TO VD3L4O
MOVE MSGL5 TO VD3L5O
MOVE MSGL6 TO VD3L6O
MOVE MSGL7 TO VD3L7O
MOVE MSGL8 TO VD3L8O
MOVE MSGL9 TO VD3L9O
MOVE MSGL10 TO VD3L10O
END-IF.
*
EXEC CICS IGNORE CONDITION
MAPFAIL
END-EXEC.
*
* Display the message until the user presses PF3
*
PERFORM WITH TEST AFTER UNTIL (EIBAID = DFHPF3) OR
(EIBAID = DFHPF15)
*
IF (EIBAID = DFHPF1) OR (EIBAID = DFHPF13) THEN
PERFORM DISPLAY-HELP
ELSE
*
EXEC CICS SEND
MAP(W02-CSQ4VD3)
MAPSET(W02-MAPSET-NAME)
FROM(CSQ4VD3O)
ERASE
END-EXEC
*
EXEC CICS RECEIVE
MAP(W02-CSQ4VD3)
MAPSET(W02-MAPSET-NAME)
INTO(CSQ4VD3O)
END-EXEC
*
END-IF
*
END-PERFORM.
*
A-MAIN-EXIT.
*
* Return to performing program
*
EXEC CICS RETURN
END-EXEC.
*
* ------------------------------------------------------------- *
DISPLAY-HELP SECTION.
* ------------------------------------------------------------- *
* *
* This section displays the help panel until PF12 is pressed *
* *
* ------------------------------------------------------------ *
*
PERFORM WITH TEST BEFORE UNTIL EIBAID = DFHPF12
OR EIBAID = DFHPF24
*
EXEC CICS SEND
MAP(W02-CSQ4VD6)
MAPSET(W02-MAPSET-NAME)
FROM(CSQ4VD6O)
ERASE
END-EXEC
*
EXEC CICS RECEIVE
MAP(W02-CSQ4VD6)
MAPSET(W02-MAPSET-NAME)
INTO(CSQ4VD6I)
END-EXEC
*
END-PERFORM.
*
DISPLAY-HELP-EXIT.
*
* Return to performing section
*
EXIT.
EJECT
*
* ---------------------------------------------------------------
* End of program
* ---------------------------------------------------------------
¤ Dauer der Verarbeitung: 0.0 Sekunden
(vorverarbeitet)
¤
|
Haftungshinweis
Die Informationen auf dieser Webseite wurden
nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit,
noch Qualität der bereit gestellten Informationen zugesichert.
Bemerkung:
Die farbliche Syntaxdarstellung ist noch experimentell.
|