Using the COBOL Wrapper with Non-secure Natural RPC Server

This document explains how clients built with the COBOL Wrapper set the Natural library used to execute the RPC request programmatically when communicating to a non-secure Natural RPC Server (not running with Natural Security). If the Natural RPC Server is running with Natural Security, see Using the COBOL Wrapper with Natural Security and Impersonation.

You will need the following components:

Start of instruction setTo set the Natural library when communicating to a non-secure Natural RPC server

  1. Specify the Natural library in the RPC communication area:

    *  Client information :                  bytes 101-300
        10 COMM-USERID.
                  15 COMM-USERID1      PIC X(8).
                  15 COMM-USERID2      PIC X(8).
        10 COMM-PASSWORD               PIC X(8).
        10 COMM-LIBRARY                PIC X(8).
        10 COMM-SECURITY-TOKEN-LENGTH  PIC 9(4) BINARY.
        10 COMM-SECURITY-TOKEN         PIC X(100).
        10 FILLER                      PIC X(66).
    
  2. Create a security token with the function Create Security Token CT provided by the generic RPC services module.

    In the scenarios with the Call Interface for Micro Focus, Batch, CICS and IMS:

    • For RPC Communication Area setting Linkage and External:

        MOVE "2000" TO COMM-VERSION.
        MOVE "CT"   TO COMM-FUNCTION.
      * Set library in RPC Communication Area
        MOVE "NAT-LIB"   TO COMM-LIBRARY.
        CALL "COBSRVI" USING ERX-COMMUNICATION-AREA
        ON EXCEPTION
        . . .
        NOT ON EXCEPTION
        . . .
        END-CALL.
      
    • For RPC Communication Area setting Copybook. Add the following COBOL Statements to the COBINIT copybook:

         MOVE "CT"   TO COMM-FUNCTION. 
       * Set library in RPC Communication Area
         MOVE "NAT-LIB"   TO COMM-LIBRARY.
         CALL "COBSRVI" USING ERX-COMMUNICATION-AREA
      

      See also Using the Generated Copybooks.

    Or:
    In the scenario Using the COBOL Wrapper for CICS with DFHCOMMAREA Calling Convention (z/OS and z/VSE) with the EXEC CICS LINK interface:

      MOVE "2000" TO COMM-VERSION. 
      MOVE "CT"   TO COMM-FUNCTION. 
    * Set library in RPC Communication Area
      MOVE "NAT-LIB"   TO COMM-LIBRARY. 
      EXEC CICS LINK PROGRAM  ("COBSRVI")
                   RESP     (CICS-RESP1)
                   RESP2    (CICS-RESP2)
                   COMMAREA (ERX-COMMUNICATION-AREA)
                   LENGTH   (LENGTH OF ERX-COMMUNICATION-AREA)
      END-EXEC. 
      IF WORKRESP = DFHRESP(NORMAL)
         IF (COMM-RETURN-CODE = 0) THEN
    *       Perform success-handling
         ELSE
    *       Perform error-handling
         END-IF
      ELSE
    *    Perform error-handling
      END-IF. 
    

After successful return from the generic RPC services module, the required fields in the RPC communication area are properly set, so the non-secure Natural RPC server executes the RPC request in the library set.