Understanding context containers

It can be useful for CICS® applications to receive information about the context in which the API was called.

From IBM® z/OS® Connect V3.0.69 onwards, the CICS® z/OS Assets created by the IBM z/OS Connect Gradle plug-in are configured to send this information to the CICS application in context containers.

For the example URL, http://my.mainframe.com:9080/redbooks?author=Lydia Parziale, the following context containers are created and they are all of type CHAR.

DFHWS-URI
The URI for the request. For example, /redbooks.
DFHWS-URI-QUERY
The query string for the request. For example, author=Lydia Parziale.
DFHHTTPMETHOD
The HTTP method for the request. For example, GET.
Note:
  1. The DFHWS-URI-QUERY container is created, but is empty, when no query string exists in the URL.
Code Example

The following code shows an example of obtaining the context containers and then using them to decide which application to call for a specific URI and method combination.

  
       IDENTIFICATION DIVISION.
       PROGRAM-ID. MYZCAPI.

       DATA DIVISION.
       WORKING-STORAGE SECTION.

       01 WS-CHANNEL-NAME          PIC X(16)  VALUE SPACES.
       
       01 WS-URI-CONT-NAME         PIC X(16)  VALUE 'DFHWS-URI       '.
       01 WS-REQUEST-URI           PIC X(256) VALUE SPACES.
       01 WS-REQUEST-URI-LENGTH    PIC 9(9)   VALUE 0 COMP-5.
       
       01 WS-METHOD-CONT-NAME      PIC X(16)  VALUE 'DFHHTTPMETHOD   '.
       01 WS-REQUEST-METHOD        PIC X(8)   VALUE SPACES.
       01 WS-REQUEST-METHOD-LENGTH PIC 9(9)   VALUE 0 COMP-5.

       PROCEDURE DIVISION.

           EXEC CICS ASSIGN CHANNEL(WS-CHANNEL-NAME) END-EXEC.

      * Tell CICS how large the working storage fields are
           MOVE LENGTH OF WS-REQUEST-URI TO WS-REQUEST-URI-LENGTH.
           MOVE LENGTH OF WS-REQUEST-METHOD TO WS-REQUEST-METHOD-LENGTH.

           EXEC CICS GET CONTAINER(WS-URI-CONT-NAME)
                         CHANNEL(WS-CHANNEL-NAME)
                         INTO(WS-REQUEST-URI)
                         FLENGTH(WS-REQUEST-URI-LENGTH)
           END-EXEC.

           EXEC CICS GET CONTAINER(WS-METHOD-CONT-NAME)
                         CHANNEL(WS-CHANNEL-NAME)
                         INTO(WS-REQUEST-METHOD)
                         FLENGTH(WS-REQUEST-METHOD-LENGTH)
           END-EXEC.

      * Decide which operation to call
           IF WS-REQUEST-URI(1:9) EQUAL '/redbook/' THEN
              IF WS-REQUEST-METHOD(1:3) EQUAL 'GET' THEN
                 EXEC CICS LINK PROGRAM('MYGETOP')
                                CHANNEL(WS-CHANNEL-NAME)
                 END-EXEC
              END-IF
              IF WS-REQUEST-METHOD(1:4) EQUAL 'POST' THEN
                 EXEC CICS LINK PROGRAM('MYCRTOP')
                                CHANNEL(WS-CHANNEL-NAME)
                 END-EXEC
              END-IF
           END-IF.

           IF WS-REQUEST-URI(1:9) EQUAL '/redbooks' THEN
              IF WS-REQUEST-METHOD(1:3) EQUAL 'GET' THEN
                 EXEC CICS LINK PROGRAM('MYGAROP')
                                CHANNEL(WS-CHANNEL-NAME)
                 END-EXEC
              END-IF
           END-IF.

       EXIT-PROGRAM.
           EXEC CICS RETURN END-EXEC.