Is there a way to cause the server runtime to exit when connectivity is lost?

0 Likes

Problem:

Using Thin Client is there a way to cause the runtime on the server to exit when the network connection is lost?

When this happens orphan runtimes are left and hold 1 license seat that is not released until the runtime is killed.

Resolution:

In some circumstances, in a Thin Client environment, the client can be unexpectedly disconnected from the server.  In order to capture this event, the TC_QUIT_MODE server runtime configuration variable was introduced.

TC_QUIT_MODE passes a numeric value to stdout when a client PC is unexpectedly disconnected.  This information can then be used by the operating system to perform any needed additional tasks.

Here is how it is implemented:

       IDENTIFICATION DIVISION.

       PROGRAM-ID. CLIENT-DISCONNECT.

       REMARKS.    This program demonstrates TC_QUIT_MODE implemention

           where in a Thin Client environment, unexpected client machine

           disconnects can be logged.

       ENVIRONMENT DIVISION.

       INPUT-OUTPUT SECTION.

       FILE-CONTROL.

           SELECT ERR-FILE

           ASSIGN TO "EVENTDATA2.TXT"

           ORGANIZATION LINE SEQUENTIAL

           FILE STATUS ERR-STAT.

              

       DATA DIVISION.

       FILE SECTION.

       FD ERR-FILE.

       01 ERR-REC  PIC X(3).

       

       WORKING-STORAGE SECTION.

       COPY "CRTVARS.DEF".

       01  WIN-HANDLE USAGE HANDLE OF WINDOW.

       01  ERR-STAT  PIC XX.

        

       SCREEN SECTION.

       01  SCREEN-1.

           03 PB-1 PUSH-BUTTON, "E&xit"

              CANCEL-BUTTON LINE 8 COL 12.

       PROCEDURE DIVISION.

       INITIAL-LOGIC.

      *  These variables tell the server runtime how often to check for

      *  client machine activity, and what value is to be sent to the

      *  server runtime should the client be disconnected.  They can

      *  also be set in the server runtime configuration file.

           SET ENVIRONMENT "TC_CHECK_ALIVE_INTERVAL" to "30".

      

      *  This value is sent to the Event-Status data structure

      *  EVENT-DATA-2 elementary item.

           SET ENVIRONMENT "TC_QUIT_MODE" TO "888".

           INITIALIZE EVENT-STATUS.     

           OPEN OUTPUT ERR-FILE.

                 

       MAIN-LOGIC.

       MAIN-SCREEN-EVENT-PROC.

           DISPLAY STANDARD GRAPHICAL WINDOW,

              BACKGROUND-LOW LINES 10 SIZE 25

              HANDLE WIN-HANDLE

              EVENT PROCEDURE SHUT-DOWN.

           DISPLAY SCREEN-1 UPON WIN-HANDLE.

           ACCEPT SCREEN-1.

      *  To test, disconnect client PC at this point.

       

       SHUT-DOWN.

           MOVE EVENT-DATA-2 TO ERR-REC.

           WRITE ERR-REC.

           CLOSE ERR-FILE.

           PERFORM 9999-EXIT-PROGRAM.

       9999-EXIT-PROGRAM.

           EXIT PROGRAM.

           STOP RUN.

For additional information regarding these server runtime configuration variables and others, see AcuConnect User's Guide > Chapter 3: Server Configuration > 3.4 Creating a Runtime Configuration File for the Remote Server Component.

Old KB# 2795
Comment List
Related
Recommended