isCOBOL WebClient : Embedding the COBOL application in an HTML page : Communicating between the browser and the COBOL application
Communicating between the browser and the COBOL application
Javascript API:
Once the application is embedded on the web page, you have access to the Javascript API:
The webclientInstance object contains a method, performAction, that is used to send messages to the COBOL app.
Usage:
performAction(options)
options is an object with the following properties:
actionName [string],mandatory
data [string], optional
binaryData [binary] optional
Example:
webclientInstance.performAction({actionName: "myAction", data: "100", binaryData: someBinaryData})
To be able to receive messages coming from the COBOL app, a listener callback can be created in the webclientInstance’s customization property:
var webclientInstance = {
  options: {
    ...
    customization: function(injector) {
    injector.services.base.handleActionEvent = function(actionName, data, binaryData)       {
          // javascript code to handle action 
      }
    }
  }
COBOL Api
To support communication on the COBOL app, a data structure needs to be defined to map the messages:
   01 IWC-STRUCT.
      03 IWC-ACTION PIC X(n).
      03 IWC-DATA   PIC X(n).
      03 IWC-BYTES  PIC X(n).
New routines are available to handle communication: IWC$INIT, IWC$GET, IWC$SET, and IWC$STOP.
CALL "IWC$INIT" USING crt-status-value
This CALL is used to initiate the communication between COBOL and html and specifies the value of crt status that will be used to terminate the ACCEPT when a message sent by the javascript application is received
CALL "IWC$GET" USING iwc-struct [timeout]
This CALL is used to retrieve the incoming message. The function will wait for a message to be available, in the message queue is empty unless a value is specified as timeout (in hundreds of a second)
CALL "IWC$SEND" USING iwc-struct
This CALL is used to send a message to the javascript application. Sending an action will cause the browser to execute the callback defined in the handleActionEvent function.
CALL "IWC$STOP"
This CALL stops communication with the javascript app. All messages sent from javascript after this routine is executed will be ignored.
All ACCEPT statements in execution will terminate as a result of receiving a message, and the program needs to call the IWC$GET routine to check if the message needs to be handled. If not, the ACCEPT can be reissued.
Message are stored in a queue and are removed from the queue as soon as IWC$GET has read them. Every run unit (the main run unit and separate run unit generated by CALL RUN statements) has its own queue and every message from html is duplicated in these queues.
IWC-PANEL
Javascript components can be embedded in the COBOL application screen section, when running in WebClient.
03 my-panel IWC-PANEL
   LINE 2COL 2
   LINES 20SIZE 6
   js-name "<component-name>"
   VALUE IWC-STRUCT
   EVENT EV-PROC
IWC-PANEL is a placeholder control, that is ignored unless the application is run in WebClient. When it is, it will trigger events in the Javascipt application that allow developers to create web components and handle interactions with the COBOL program.
The webclientInstance object has a compositingWindowsListener listener object that can be used to capture IWC-PANEL creation events.
webclientInstance = {
 options: {
 compositingWindowsListener : {
  windowOpening: function(win) {},
  windowOpened: function(win) {},
  }
 }
}
The callbacks will be invoked just before and right after the panel is created. The win object passaed as parameter of the callback identifies which panel has been created. The js-name attribute of the IWC-PANEL will be available in the win.name property in the callback.
For example:
compositingWindowsListener:{
  windowOpened: function(win) {
    if (win.name === 'f-map'){
      createMap(win)
    }
  },
},
Other useful properties available in the win object are:
id [string]
unique string identifier of this panel
ownerId [string]
unique string identifier of this panels’s owner
tabId [string]
id (window.name) of the browser window where this canvas is rendered
element [Element]
DOM element (canvas) representing this panel
name [string]
panel name in your application (js-name property in the screen section)
webswingInstance [object]
refers back to the webclientInstance object that owns the panel
handleActionEvent [function]
assign a callback to handle communication with the COBOL program (discussed later) handleActionEvent = function(actionName, data, binaryData)
performAction(options)
is used to send events to the control’s event procedure in the COBOL application. options is an object with properties actionName [string], data [string], binaryData [binary]. Only the actionName property is required.
When the COBOL program needs the web component to perform an action, it can issue the following statement:
modify my-panel value iwc-struct
This code will cause the handleActionEvent callback of the win object in the javascript code to be executed, and the iwc-struct parameters will be passed to the callback.
For example, the following code captures messages coming from COBOL’s MODIFY VALUE statement:
win.handleActionEvent = function(actionName, data, binaryData) {
  if (actionName === 'addOffices'){
    offices = JSON.parse(data);
  ...
  }
  if (actionName === 'selectOffice'){
    let office = JSON.parse(data);
  ...
  }
}
The javascript program may need to perform actions on the control, and can do so by calling the win.performAction methods, for example:
win.performAction({actionName: 'pinClicked', data: marker.title});
In the COBOL application the IWC-PANEL event procedure will be called, the message can then be retrieved and handled, for example:
       EV-PROC.
           if event-type = ntf-iwc-event
             inquire f-map value in fmap-struct
             if fmap-action = "pinClicked"
                ...
             end-if
           end-if
           .