performAction(options) |
webclientInstance.performAction({actionName: "myAction", data: "100", binaryData: someBinaryData}) |
var webclientInstance = { options: { ... customization: function(injector) { injector.services.base.handleActionEvent = function(actionName, data, binaryData) { // javascript code to handle action } } } |
01 IWC-STRUCT. 03 IWC-ACTION PIC X(n). 03 IWC-DATA PIC X(n). 03 IWC-BYTES PIC X(n). |
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. |
03 my-panel IWC-PANEL LINE 2, COL 2 LINES 20, SIZE 6 js-name "<component-name>" VALUE IWC-STRUCT EVENT EV-PROC |
webclientInstance = { options: { compositingWindowsListener : { windowOpening: function(win) {}, windowOpened: function(win) {}, } } } |
compositingWindowsListener:{ windowOpened: function(win) { if (win.name === 'f-map'){ createMap(win) } }, }, |
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. |
modify my-panel value iwc-struct |
win.handleActionEvent = function(actionName, data, binaryData) { if (actionName === 'addOffices'){ offices = JSON.parse(data); ... } if (actionName === 'selectOffice'){ let office = JSON.parse(data); ... } } |
win.performAction({actionName: 'pinClicked', data: marker.title}); |
EV-PROC. if event-type = ntf-iwc-event inquire f-map value in fmap-struct if fmap-action = "pinClicked" ... end-if end-if . |