Asynchronous app server call, won't fires EVENT-PROCEDUR

Posted by OctavioOlguin on 08-Mar-2015 17:51

I came to his procedures to experiment with async calls:

&ANALYZE-SUSPEND _VERSION-NUMBER AB_v10r12 GUI
&ANALYZE-RESUME
&Scoped-define WINDOW-NAME C-Win
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS C-Win 
/*------------------------------------------------------------------------

  File: 

  Description: 

  Input Parameters:
      <none>

  Output Parameters:
      <none>

  Author: 

  Created: 

------------------------------------------------------------------------*/
/*          This .W file was created with the Progress AppBuilder.      */
/*----------------------------------------------------------------------*/

ROUTINE-LEVEL ON ERROR UNDO, THROW.

/* Create an unnamed pool to store all the widgets created 
     by this procedure. This is a good default which assures
     that this procedure's triggers and internal procedures 
     will execute in this procedure's storage, and that proper
     cleanup will occur on deletion of the procedure. */

CREATE WIDGET-POOL.

/* ***************************  Definitions  ************************** */

/* Parameters Definitions ---                                           */

/* Local Variable Definitions ---                                       */
DEFINE VARIABLE hServer AS HANDLE        NO-UNDO.
DEFINE VARIABLE hAsync  AS HANDLE        NO-UNDO.

DEFINE VARIABLE pStatus AS CHARACTER     NO-UNDO.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


&ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK 

/* ********************  Preprocessor Definitions  ******************** */

&Scoped-define PROCEDURE-TYPE Window
&Scoped-define DB-AWARE no

/* Name of designated FRAME-NAME and/or first browse and/or first query */
&Scoped-define FRAME-NAME DEFAULT-FRAME

/* Standard List Definitions                                            */
&Scoped-Define ENABLED-OBJECTS rTipo fEcho tAsync fPAusa bLlamar fRespuesta ~
Gotit bProcessEvents 
&Scoped-Define DISPLAYED-OBJECTS rTipo fEcho tAsync fPAusa fRespuesta Gotit 

/* Custom List Definitions                                              */
/* List-1,List-2,List-3,List-4,List-5,List-6                            */

/* _UIB-PREPROCESSOR-BLOCK-END */
&ANALYZE-RESUME



/* ***********************  Control Definitions  ********************** */

/* Define the widget handle for the window                              */
DEFINE VAR      C-Win   AS WIDGET-HANDLE NO-UNDO.

/* Definitions of the field level widgets                               */
DEFINE BUTTON bLlamar 
    LABEL "Llamar" 
    SIZE 15 BY 1.43.

DEFINE BUTTON bProcessEvents 
    LABEL "?" 
    SIZE 15 BY 1.14.

DEFINE VARIABLE fRespuesta AS CHARACTER 
    VIEW-AS EDITOR NO-WORD-WRAP SCROLLBAR-HORIZONTAL SCROLLBAR-VERTICAL
    SIZE 63 BY 4.76 NO-UNDO.

DEFINE VARIABLE fEcho      AS CHARACTER FORMAT "X(256)":U 
    LABEL "Echo" 
    VIEW-AS FILL-IN 
    SIZE 27 BY 1 NO-UNDO.

DEFINE VARIABLE fPAusa     AS INTEGER   FORMAT ">9":U INITIAL 0 
    LABEL "Pausa" 
    VIEW-AS FILL-IN 
    SIZE 14 BY 1 NO-UNDO.

DEFINE VARIABLE Gotit      AS CHARACTER FORMAT "X(256)":U 
    VIEW-AS FILL-IN 
    SIZE 14 BY 1 NO-UNDO.

DEFINE VARIABLE rTipo      AS INTEGER 
    VIEW-AS RADIO-SET VERTICAL
    RADIO-BUTTONS 
    "1.- No error", 1,
    "2.- Error", 2,
    "3.- Echo", 3
    SIZE 39 BY 3 NO-UNDO.

DEFINE VARIABLE tAsync     AS LOGICAL   INITIAL NO 
    LABEL "Asynchronous" 
    VIEW-AS TOGGLE-BOX
    SIZE 26 BY .81 NO-UNDO.


/* ************************  Frame Definitions  *********************** */

DEFINE FRAME DEFAULT-FRAME
    rTipo AT ROW 4.1 COL 16 NO-LABEL WIDGET-ID 2
    fEcho AT ROW 7.24 COL 22 COLON-ALIGNED WIDGET-ID 8
    tAsync AT ROW 8.67 COL 24 WIDGET-ID 18
    fPAusa AT ROW 9.81 COL 22 COLON-ALIGNED WIDGET-ID 20
    bLlamar AT ROW 9.91 COL 61 WIDGET-ID 12
    fRespuesta AT ROW 11.57 COL 10 NO-LABEL WIDGET-ID 10
    Gotit AT ROW 16.48 COL 8 COLON-ALIGNED NO-LABEL WIDGET-ID 22
    bProcessEvents AT ROW 16.52 COL 25 WIDGET-ID 24
    "Tipo Llamada" VIEW-AS TEXT
    SIZE 16 BY .62 AT ROW 3.1 COL 14 WIDGET-ID 6
    WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY 
    SIDE-LABELS NO-UNDERLINE THREE-D 
    AT COL 1 ROW 1
    SIZE 80 BY 18.33 WIDGET-ID 100.


/* *********************** Procedure Settings ************************ */

&ANALYZE-SUSPEND _PROCEDURE-SETTINGS
/* Settings for THIS-PROCEDURE
   Type: Window
   Allow: Basic,Browse,DB-Fields,Window,Query
   Other Settings: COMPILE
 */
&ANALYZE-RESUME _END-PROCEDURE-SETTINGS

/* *************************  Create Window  ************************** */

&ANALYZE-SUSPEND _CREATE-WINDOW
IF SESSION:DISPLAY-TYPE = "GUI":U THEN
    CREATE WINDOW C-Win ASSIGN
        HIDDEN             = YES
        TITLE              = "<insert window title>"
        HEIGHT             = 18.33
        WIDTH              = 80
        MAX-HEIGHT         = 18.33
        MAX-WIDTH          = 80
        VIRTUAL-HEIGHT     = 18.33
        VIRTUAL-WIDTH      = 80
        RESIZE             = YES
        SCROLL-BARS        = NO
        STATUS-AREA        = NO
        BGCOLOR            = ?
        FGCOLOR            = ?
        KEEP-FRAME-Z-ORDER = YES
        THREE-D            = YES
        MESSAGE-AREA       = NO
        SENSITIVE          = YES.
ELSE {&WINDOW-NAME} = CURRENT-WINDOW.
/* END WINDOW DEFINITION                                                */
&ANALYZE-RESUME



/* ***********  Runtime Attributes and AppBuilder Settings  *********** */

&ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
/* SETTINGS FOR WINDOW C-Win
  VISIBLE,,RUN-PERSISTENT                                               */
/* SETTINGS FOR FRAME DEFAULT-FRAME
   FRAME-NAME                                                           */
IF SESSION:DISPLAY-TYPE = "GUI":U AND VALID-HANDLE(C-Win)
    THEN C-Win:HIDDEN = NO.

/* _RUN-TIME-ATTRIBUTES-END */
&ANALYZE-RESUME

 



/* ************************  Control Triggers  ************************ */

&Scoped-define SELF-NAME C-Win
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL C-Win C-Win
ON END-ERROR OF C-Win /* <insert window title> */
    OR ENDKEY OF {&WINDOW-NAME} ANYWHERE 
    DO:
        /* This case occurs when the user presses the "Esc" key.
           In a persistently run window, just ignore this.  If we did not, the
           application would exit. */
        IF THIS-PROCEDURE:PERSISTENT THEN RETURN NO-APPLY.
    END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL C-Win C-Win
ON WINDOW-CLOSE OF C-Win /* <insert window title> */
    DO:
        /* This event will close the window and terminate the procedure.  */
        APPLY "CLOSE":U TO THIS-PROCEDURE.
        RETURN NO-APPLY.
    END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


&Scoped-define SELF-NAME bLlamar
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL bLlamar C-Win
ON CHOOSE OF bLlamar IN FRAME DEFAULT-FRAME /* Llamar */
    DO:
        ASSIGN FRAME {&FRAME-NAME} rTipo fEcho tAsync  fPausa .
        ASSIGN 
            fRespuesta = "".
        DISPLAY fRespuesta "" @ gotit WITH FRAME {&FRAME-NAME} .
        
        CREATE SERVER hServer.
        hServer:CONNECT("-H myservre.com -DirectConnect -S 3090 -AppService schAS1 -sessionModel Session-free"). 
        
        
        IF tASync THEN 
        DO:
            RUN test.p ON SERVER hServer ASYNCHRONOUS SET hAsync
                EVENT-PROCEDURE "AsyncProcessor" IN this-procedure
                (rtipo, fEcho, fPausa, OUTPUT pStatus ) .  
        END.
        ELSE 
        DO:
            RUN test.p ON SERVER hServer (rtipo, fEcho, fPausa, OUTPUT pStatus ) .
            ASSIGN 
                fRespuesta = pStatus.
            DISPLAY fRespuesta WITH FRAME {&FRAME-NAME}.   
            
        END.
    
        hServer:DISCONNECT ().
        DELETE OBJECT hServer.    

            CATCH myApp1 AS Progress.Lang.AppError :
                  MESSAGE "myApp1"
                        VIEW-AS ALERT-BOX.
            END CATCH.
            CATCH mySys1 AS Progress.Lang.SysError :
                  MESSAGE "mySys1"
                        VIEW-AS ALERT-BOX.
            END CATCH.

    END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


&Scoped-define SELF-NAME bProcessEvents
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL bProcessEvents C-Win
ON CHOOSE OF bProcessEvents IN FRAME DEFAULT-FRAME /* ? */
    DO:
        PROCESS EVENTS.  
    END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME



&Scoped-define SELF-NAME rTipo
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL rTipo C-Win
ON VALUE-CHANGED OF rTipo IN FRAME DEFAULT-FRAME
    DO:
        ASSIGN FRAME {&FRAME-NAME}  {&SELF-NAME}.
        IF {&SELF-NAME} = 3 THEN
            ENABLE fEcho WITH FRAME {&FRAME-NAME} .
        ELSE
            DISABLE fEcho WITH FRAME {&FRAME-NAME} .
    END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


&UNDEFINE SELF-NAME

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK C-Win 


/* ***************************  Main Block  *************************** */

/* Set CURRENT-WINDOW: this will parent dialog-boxes and frames.        */
ASSIGN CURRENT-WINDOW                = {&WINDOW-NAME} 
       THIS-PROCEDURE:CURRENT-WINDOW = {&WINDOW-NAME}.

/* The CLOSE event can be used from inside or outside the procedure to  */
/* terminate it.                                                        */
ON CLOSE OF THIS-PROCEDURE 
    RUN disable_UI.

/* Best default for GUI applications is...                              */
PAUSE 0 BEFORE-HIDE.

/* Now enable the interface and wait for the exit condition.            */
/* (NOTE: handle ERROR and END-KEY so cleanup code will always fire.    */
MAIN-BLOCK:
DO ON ERROR   UNDO MAIN-BLOCK, LEAVE MAIN-BLOCK
    ON END-KEY UNDO MAIN-BLOCK, LEAVE MAIN-BLOCK:
        
    RUN enable_UI.
    IF NOT THIS-PROCEDURE:PERSISTENT THEN
        WAIT-FOR CLOSE OF THIS-PROCEDURE.
        
    CATCH myE AS Progress.Lang.SysError :
        MESSAGE "SysError"
            VIEW-AS ALERT-BOX.
    END CATCH.
    CATCH myA AS Progress.Lang.AppError :
        MESSAGE "AppError"
            VIEW-AS ALERT-BOX.
    END CATCH.    
END.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME


/* **********************  Internal Procedures  *********************** */

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE AsyncProcessor C-Win 
PROCEDURE AsyncProcessor :
    /*------------------------------------------------------------------------------
             Purpose:
             Notes:
            ------------------------------------------------------------------------------*/
    DEFINE INPUT  PARAMETER pTipo   AS INTEGER NO-UNDO.
    DEFINE INPUT  PARAMETER pEcho   AS CHARACTER NO-UNDO.
    DEFINE INPUT  PARAMETER Pausa   AS INTEGER NO-UNDO. /* cuantos segundos debo esperar antes de regresar la respuesta */
    DEFINE OUTPUT PARAMETER pStatus AS CHARACTER NO-UNDO.

    ASSIGN 
        fRespuesta = pStatus.
    DISPLAY fRespuesta
        "Got it!" @ gotit  WITH FRAME {&FRAME-NAME}.   

END PROCEDURE.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI C-Win  _DEFAULT-DISABLE
PROCEDURE disable_UI :
    /*------------------------------------------------------------------------------
      Purpose:     DISABLE the User Interface
      Parameters:  <none>
      Notes:       Here we clean-up the user-interface by deleting
                   dynamic widgets we have created and/or hide 
                   frames.  This procedure is usually called when
                   we are ready to "clean-up" after running.
    ------------------------------------------------------------------------------*/
    /* Delete the WINDOW we created */
    IF SESSION:DISPLAY-TYPE = "GUI":U AND VALID-HANDLE(C-Win)
        THEN DELETE WIDGET C-Win.
    IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
END PROCEDURE.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enable_UI C-Win  _DEFAULT-ENABLE
PROCEDURE enable_UI :
    /*------------------------------------------------------------------------------
      Purpose:     ENABLE the User Interface
      Parameters:  <none>
      Notes:       Here we display/view/enable the widgets in the
                   user-interface.  In addition, OPEN all queries
                   associated with each FRAME and BROWSE.
                   These statements here are based on the "Other 
                   Settings" section of the widget Property Sheets.
    ------------------------------------------------------------------------------*/
    DISPLAY rTipo fEcho tAsync fPAusa fRespuesta Gotit 
        WITH FRAME DEFAULT-FRAME IN WINDOW C-Win.
    ENABLE rTipo fEcho tAsync fPAusa bLlamar fRespuesta Gotit bProcessEvents 
        WITH FRAME DEFAULT-FRAME IN WINDOW C-Win.
    {&OPEN-BROWSERS-IN-QUERY-DEFAULT-FRAME}
    VIEW C-Win.
END PROCEDURE.

/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME

and this is the test procedure in appserver:
&ANALYZE-SUSPEND _VERSION-NUMBER AB_v10r12
/* Procedure Description
"Structured Procedure File Template.
Use this template to create a new Structured Procedure file to compile and run PROGRESS 4GL code. You edit structured procedure files using the AB's Section Editor."
*/
&ANALYZE-RESUME
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS Procedure 
/*------------------------------------------------------------------------
    File        : test.p
    Purpose     : 
    Syntax      :
                RUN test in
                    (1, "", 5, OUTPUT pStatus).
                MESSAGE pStatus
                    VIEW-AS ALERT-BOX.
                    
                    
    Description : Recibe y regresa diferentes codigos, segun indique el cliente.
    Author(s)   : 
    Created     : Sun Mar 08 14:22:31 CST 2015
    Notes       :
  ----------------------------------------------------------------------*/
/*----------------------------------------------------------------------*/
/* ***************************  Definitions  ************************** */
BLOCK-LEVEL ON ERROR UNDO, THROW.
DEFINE INPUT  PARAMETER pTipo   AS INTEGER NO-UNDO.
DEFINE INPUT  PARAMETER pEcho   AS CHARACTER NO-UNDO.
DEFINE INPUT  PARAMETER Pausa   AS INTEGER NO-UNDO. /* cuantos segundos debo esperar antes de regresar la respuesta */
DEFINE OUTPUT PARAMETER pStatus AS CHARACTER NO-UNDO.
/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME
&ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK 
/* ********************  Preprocessor Definitions  ******************** */
/* _UIB-PREPROCESSOR-BLOCK-END */
&ANALYZE-RESUME
/* *********************** Procedure Settings ************************ */
&ANALYZE-SUSPEND _PROCEDURE-SETTINGS
/* Settings for THIS-PROCEDURE
   Type: Procedure Template
   Allow: 
   Frames: 0
   Add Fields to: Neither
   Other Settings: CODE-ONLY COMPILE
 */
&ANALYZE-RESUME _END-PROCEDURE-SETTINGS
/* *************************  Create Window  ************************** */
&ANALYZE-SUSPEND _CREATE-WINDOW
/* DESIGN Window definition (used by the UIB) 
  CREATE WINDOW Procedure ASSIGN
         HEIGHT             = 15
         WIDTH              = 60.
/* END WINDOW DEFINITION */
                                                                        */
&ANALYZE-RESUME
 
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK Procedure 
/* ***************************  Main Block  *************************** */
PAUSE Pausa.
CASE pTipo:
    WHEN 1 THEN 
        DO:
            ASSIGN 
                pStatus = STRING(NOW).
        END.
    WHEN 2 THEN 
        DO: 
            RETURN ERROR.
        END.
    WHEN 3 THEN 
        DO: 
            ASSIGN 
                pStatus = pEcho.
        END.    
END CASE.
    
/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME
But I can't achieve to fire the  AsyncProcessor  procedure in the client.
Any clue what's wrong?
Thnaks.

All Replies

Posted by Laura Stern on 08-Mar-2015 21:29

There's a lot of extraneous stuff here that has nothing to do with running the async procedure.  So it's hard to focus in on what you're doing. Are you even sure that this code is compiling on the server?  I'm confused as to why you're creating a window on the AppServer side. Make sure the AppServer code is running at all by looking in the AppServer log.  If it's good, do you get an error on the client side?  I don't remember if the 1st parameter of the event handler is supposed to be the async handle or if you get that by accessing SELF.

Posted by Frank Meulblok on 09-Mar-2015 05:21

One thing that does stand out: in this part of the code you're disconnecting the AppServer without checking if the async requests completed or not.

...
CREATE SERVER hServer.         
hServer:CONNECT("-H myservre.com -DirectConnect -S 3090 -AppService schAS1 -sessionModel Session-free").  

IF tASync THEN          
DO:             
    RUN test.p ON SERVER hServer ASYNCHRONOUS SET hAsync                 
        EVENT-PROCEDURE "AsyncProcessor" IN this-procedure
        (rtipo, fEcho, fPausa, OUTPUT pStatus ) .
END.         
ELSE          
DO:
   ...
END.

hServer:DISCONNECT ().
DELETE OBJECT hServer.


That's not a good idea. 

Try moving the code that connects to and disconnect from the appserver outside of that trigger block, and into a wider scope - I don't see any reason not to persist the connection in between requests in this case.

Posted by mopfer on 09-Mar-2015 06:51

The code for disconnecting should go in the event procedure if you're going to disconnect after the call is done.  Because the call is asynchronous, the client won't wait for it to finish before executing the next line of code in the client program.  In this case, the next line of client code is disconnecting from the appserver immediately after calling the .p. 

 

The connection is the path back to the client from the appserver when the .p is done running - without the connection the event that the event procedure is waiting for will never happen.  Disconnecting while the .p is running will also cause the .p to be interrupted.


[collapse]
From: Frank Meulblok <bounce-fmeulblo@community.progress.com>
Sent: Monday, March 9, 2015 5:21 AM
To: TU.OE.Development@community.progress.com
Subject: RE: [Technical Users - OE Development] Asynchronous app server call, won't fires EVENT-PROCEDURE
 
Reply by Frank Meulblok

One thing that does stand out: in this part of the code you're disconnecting the AppServer without checking if the async requests completed or not.

...
CREATE SERVER hServer.        
hServer:CONNECT("-H myservre.com -DirectConnect -S 3090 -AppService schAS1 -sessionModel Session-free"). 

IF tASync THEN DO: RUN test.p ON SERVER hServer ASYNCHRONOUS SET hAsync EVENT-PROCEDURE "AsyncProcessor" IN this-procedure (rtipo, fEcho, fPausa, OUTPUT pStatus ) . END. ELSE DO: ... END. hServer:DISCONNECT (). DELETE OBJECT hServer.


That's not a good idea. 

Try moving the code that connects to and disconnect from the appserver outside of that trigger block, and into a wider scope - I don't see any reason not to persist the connection in between requests in this case.

Stop receiving emails on this subject.

Flag this post as spam/abuse.

[/collapse]

Posted by OctavioOlguin on 09-Mar-2015 09:10

Hi Laura, thanks for your concern.

But, the window is run from the client side, and the test procedure is the one that runs inside the appserver,  I'll try the tips that followed, not disconnecting right away from the server.

Posted by Laura Stern on 09-Mar-2015 09:37

One more thing now that I'm at work and could check about SELF.  Your code is correct - the ASYNC-REQUEST handle is not a parameter and you can get at via SELF.  But you should definitely be checking SELF:STOP and SELF:ERROR before you proceed to assume that you can rely on the output value.

Posted by OctavioOlguin on 09-Mar-2015 10:49

Thanks Laura... I'll be checking that as you instruct.!

This thread is closed