X Marks the Spot (Exit)

Jenie888

Member
:rolleyes:

Hey there,

I have been working on a program for a while. One of the biggest problems I fear is the user clicking the "X" in the top right hand corner instead of exiting out of the screens correctly. I tried to capture the action, but I can't figure it out. I have seen some programs where they disabled the "X" .

Does any one have any info on this???

Jenie
 

Chris Kelleher

Administrator
Staff member
Sure, you can do this using Windows API calls. Here's a program that does it:

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

  File: w-disableX.w

  Description: This program will disable the close option for a window.


  Author:  Todd G. Nist
           Protech Systems Inc.
           [email]tnist@protech.com[/email]

  Created: July 30, 1998

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

/* 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 ---                                       */

&GLOB MF_BYPOSITION 1024
&GLOB MF_REMOVE     256

Procedure GetSystemMenu External "user32":
  define input parameter hwnd       as  long.
  define input parameter bRevert    as  long.
  define return parameter lRetCode  as  long.
End.

Procedure GetMenuItemCount External "user32":
  define input parameter hMenu      as  long.
  define return parameter iRetCode  as  long.
End.

Procedure DrawMenuBar External "user32":
  define input parameter hMenu      as  long.
  define return parameter iRetCode  as  long.
End.

Procedure RemoveMenu External "user32":
  define input parameter hMenu      as  long.
  define input parameter nPosition  as  long.
  define input parameter wFlags     as  long.
  define return parameter iRetCode  as  long.
End.

Procedure GetParent External "user32":
  define input  parameter thishwnd     as long.
  define return parameter parenthwnd   as long.
End.

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


&ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK 

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

&Scoped-define PROCEDURE-TYPE Window

/* Name of first Frame and/or Browse and/or first Query                 */
&Scoped-define FRAME-NAME DEFAULT-FRAME

/* Standard List Definitions                                            */
&Scoped-Define ENABLED-OBJECTS btnClose 

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

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


/* ************************  Function Prototypes ********************** */

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD DisableWindowClose C-Win 
FUNCTION DisableWindowClose RETURNS LOGICAL
  ( /* parameter-definitions */ )  FORWARD.

/* _UIB-CODE-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 btnClose 
     LABEL "Close Window" 
     SIZE 21 BY 1.14.


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

DEFINE FRAME DEFAULT-FRAME
     btnClose AT ROW 5 COL 2.8
    WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY 
         SIDE-LABELS NO-UNDERLINE THREE-D 
         AT COL 1 ROW 1
         SIZE 70.8 BY 5.67.


/* *********************** 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             = 5.71
         WIDTH              = 70.8
         MAX-HEIGHT         = 16
         MAX-WIDTH          = 80
         VIRTUAL-HEIGHT     = 16
         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 UIB Settings  ************** */

&ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
/* SETTINGS FOR WINDOW C-Win
  VISIBLE,,RUN-PERSISTENT                                               */
/* SETTINGS FOR FRAME DEFAULT-FRAME
                                                                        */
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 btnClose
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL btnClose C-Win
ON CHOOSE OF btnClose IN FRAME DEFAULT-FRAME /* Close Window */
DO:
  /* provide a means to close the window in testing */
  apply "window-close" to {&window-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:
  /* call function to disable the window close ("X") button and remove   */
  /* the close option from the menu.                                     */ 
  DisableWindowClose().
  RUN enable_UI.
  IF NOT THIS-PROCEDURE:PERSISTENT THEN
    WAIT-FOR CLOSE OF THIS-PROCEDURE.
END.

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


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

&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.
------------------------------------------------------------------------------*/
  ENABLE btnClose 
      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


/* ************************  Function Implementations ***************** */

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION DisableWindowClose C-Win 
FUNCTION DisableWindowClose RETURNS LOGICAL
  ( /* parameter-definitions */ ) :
/*------------------------------------------------------------------------------
  Purpose:  
    Notes:  
------------------------------------------------------------------------------*/
  define var hSysMenu   as  int no-undo.
  define var hParent    as  int no-undo.
  define var hInstance  as  int no-undo.
  define var iRetCode   as  int no-undo.
  define var iCnt       as  int no-undo.

  run GetParent(input {&window-name}:hWnd,
                output hParent).

  /* Get handle to our the window's system menu (Restore, Maximize, Move, close etc.) */
  run GetSystemMenu(input  hParent, 
                    input  0,
                    output hSysMenu).

  if hSysMenu <> 0 then
  do:
    /* Get System menu's menu count */
    run GetMenuItemCount(input hSysMenu,
                         output iCnt).
      
    if iCnt <> 0 then
    do:
      /* Menu count is based on 0 (0, 1, 2, 3...) */

      /* remove the "close option" */
      run RemoveMenu(input hSysMenu, 
                     input iCnt - 1, 
                     input {&MF_BYPOSITION} + {&MF_REMOVE},
                     output iRetCode).

      /* remove the seperator */
      run RemoveMenu(input hSysMenu, 
                     input iCnt - 2, 
                     input {&MF_BYPOSITION} + {&MF_REMOVE},
                     output iRetCode).
            
      /* Force caption bar's refresh which will disable the window close ("X") button */
      run DrawMenuBar(input  hParent,
                      output iRetCode).
      {&window-name}:title = "Try to close me!".
    end. /* if iCnt <> 0... */
  end. /* if hSysMenu <> 0... */  

  RETURN FALSE.   /* Function return value. */

END FUNCTION.

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

tsspdx

New Member
Wow, that's a lot of code.

Maybe Jennie has to do exactly what she asked. But before changing how Windows operates, I'd look again at my design. How about a WINDOWS-CLOSE event to protect the integrity of the database?
 

gregscott

New Member
Why not just change the WINDOW-CLOSE triger.

Instead of -
DO:
/* This event will close the window and terminate the procedure. */
APPLY "CLOSE" TO THIS-PROCEDURE.
RETURN NO-APPLY.
END.

DO:
RETURN NO-APPLY.
END.

When they click the X nothing happens.
 

tsspdx

New Member
We all got it wrong!

By default Progress (at least my v.8) doesn't do anything on a window-close event. It's up to the programmer to have the application do something. Typical is to enable a bunch of buttons, and then a

WAIT-FOR WINDOW-CLOSE OF CURRENT-WINDOW.

This can be followed by appropriate clean-up and then a RETURN or LEAVE.

I think it's normally good practice for an application in a GUI environment to honor a Window-Close. If for some reason you can't, I'd do so with explicit code like gregscott's. But I'd give the user some direction:

ON WINDOW-CLOSE OF CURRENT-WINDOW DO:
MESSAGE "Don't exit this way, dummy. Press the Quit button" VIEW-AS ALERT-BOX INFORMATION.
RETURN NO-APPLY.
End.
 

gregscott

New Member
By default in v 9.1A does put the following code in when you create a new window.

DO:
/* This event will close the window and terminate the procedure. */
APPLY "CLOSE":U TO THIS-PROCEDURE.
RETURN NO-APPLY.
END.

FYI

Originally posted by tsspdx
We all got it wrong!

By default Progress (at least my v.8) doesn't do anything on a window-close event. It's up to the programmer to have the application do something. Typical is to enable a bunch of buttons, and then a

WAIT-FOR WINDOW-CLOSE OF CURRENT-WINDOW.

This can be followed by appropriate clean-up and then a RETURN or LEAVE.

I think it's normally good practice for an application in a GUI environment to honor a Window-Close. If for some reason you can't, I'd do so with explicit code like gregscott's. But I'd give the user some direction:

ON WINDOW-CLOSE OF CURRENT-WINDOW DO:
MESSAGE "Don't exit this way, dummy. Press the Quit button" VIEW-AS ALERT-BOX INFORMATION.
RETURN NO-APPLY.
End.
 

Jenie888

Member
Thanx

I am a bit confused where to put this stuff though. I have tried what you said... but I'm lost. Should it go in th main block? I am working on a dialogue box right now. Here is my main block.

&ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK Dialog-Frame


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

/* Parent the dialog-box to the ACTIVE-WINDOW, if there is no parent. */
IF VALID-HANDLE(ACTIVE-WINDOW) AND FRAME {&FRAME-NAME}:pARENT eq ?
THEN FRAME {&FRAME-NAME}:pARENT = ACTIVE-WINDOW.


/* 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:

ON WINDOW-CLOSE OF CURRENT-WINDOW DO:
MESSAGE "Don't exit this way, dummy. Press the Quit button" VIEW-AS ALERT-BOX INFORMATION.
RETURN NO-APPLY.
End.

RUN enable_UI.
chCtrl = chCtrlFrame:MailX.
RUN LoadProgrammers.
FIND Programmers WHERE Programmers.User-or-group-id = USERID("WorkDB").
ASSIGN cb-Programmer:SCREEN-VALUE = Programmers.LName.
ASSIGN i-Programmer = cb-Programmer:SCREEN-VALUE.
ASSIGN i-UserID = USERID("ProWork").
RUN DispMessage.
RUN OpenBr-Task.

RUN LoadProducts.

WAIT-FOR GO OF FRAME {&FRAME-NAME}.
END.
RUN disable_UI.

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


Thanks!

Jenie:rolleyes:
 

tsspdx

New Member
What you have works in plain Progress. Just make sure you've given the user some other way out!

CAVEAT: You are apparently using SmartObjects. SmartObjects essentially are giant macros. Probably it would be useful for ProgressTalk to establish a separate SmartObject discussion group.

In 9.1B which I just loaded I find around 30 different treatments of WINDOW-CLOSE in SmartObjects. Look in your DLC directory, folder src/adm. In support/browserd.w, which handles SmartBrowsers, the WINDOW-CLOSE event is converted to an END-ERROR (lines 237-241):

ON WINDOW-CLOSE OF FRAME Attribute-Dlg
DO:
APPLY "END-ERROR":U TO SELF.
End.

Your main block, therefore, probably "sees" the WINDOW-CLOSE as an ERROR or END-KEY, and so just applies your UNDO, LEAVE directive.

I'm not exactly sure what gregscott is referring to, but v 9.1b SmartObject Dynamic Windows uses the code he cites. So yes, I would expect v. 9 SmartWindows to close themselves down upon receipt of a WINDOW-CLOSE. This is not native Progress treatment, but happens only because of this added code.
 

Jenie888

Member
Hey Raymond

Hey there,

Thanks for responding. The truth is my code did not disable or deactivate my X. I did give them a way out. There is an exit button.....

No unfortunatly where I work does not use smart objects. I wish they did! Right now it is standard preference by my boss not to though.

I also tried Chris's code..... but that didn't work either... I am going to keeo tring maybe I just missed something.

Thanks for your help

Jenie
 

Jenie888

Member
What about dialogue boxes? Chris's code ened up working... but it was for a window. What about a dialogue box.


Jenie:awink:
 
U

Unregistered

Guest
now this is all very interesting , but how would it be done for a dialog box. Thats what my employers want since most of our stuff is in dialog boxes.
 

Samj

Member
Every window the the UIB creates has the default trigger for the WINDOW-CLOSE event in the Main-Block.

/* These events will close the window and terminate the procedure. */
/* (NOTE: this will override any user-defined triggers previously */
/* defined on the window.) */
ON WINDOW-CLOSE OF {&WINDOW-NAME}
DO:
APPLY "CLOSE":U TO THIS-PROCEDURE.
RETURN NO-APPLY.
END.

If you want the program to do anything else just add it to the trigger before the apply close event fires.

Dialog boxes have trigger that is similar:

ON WINDOW-CLOSE OF FRAME {&FRAME-NAME}
DO:
APPLY "END-ERROR" TO SELF.
END.

Where you can also put in clean-up code.

Sam Johnson
Professional Data Systems, Inc.
samj@pdsi.com
 
Top