Properties of a cell.

Posted by josephathieu on 01-Jan-2015 09:17

Hello. I know enable, disable, a full column into a browse (created with DEFINE into AppBuilder) but how can i, for an example, disable just one cell into a column that is defined with ENABLE into browse's DISPLAY trigger? Thanks in advance...

All Replies

Posted by James Palmer on 01-Jan-2015 12:27

As far as I know you have to get a handle to the column and then on value changed of the browse set that column read only property based on your criteria.

James Palmer | Application Developer
Tel: 01253 785103

[collapse]From: josephathieu
Sent: ‎01/‎01/‎2015 15:20
To: TU.OE.Development@community.progress.com
Subject: [Technical Users - OE Development] Properties of a cell.

Thread created by josephathieu
Hello. I know enable, disable, a full column into a browse (created with DEFINE into AppBuilder) but how can i, for an example, disable just one cell into a column that is defined with ENABLE into browse's DISPLAY trigger? Thanks in advance...
Stop receiving emails on this subject.

Flag this post as spam/abuse.




This email has been scanned for email related threats and delivered safely by Mimecast.
For more information please visit http://www.mimecast.com
[/collapse]

Posted by olivier.dunemann on 02-Jan-2015 03:19

In MS Windows, you can also play with the "ENTRY" trigger of the column, and force a "TAB" event.

ON ENTRY OF BrowseColumnX
DO:
  /* We don't want to stay on this enabled cell */

  DEF VAR i AS INT NO-UNDO.

  &SCOPED-DEFINE VK_TAB 9
  &SCOPED-DEFINE WM_KEYDOWN 256

  /* Simulate a TAB Key-Down event... */
  RUN PostMessageA (SELF:HWND, {&WM_KEYDOWN}, {&VK_TAB}, 0, OUTPUT i).
END.

PROCEDURE PostMessageA EXTERNAL "user32":u:
  DEF INPUT  PARAM hHWND   AS LONG.
  DEF INPUT  PARAM Msg     AS LONG.
  DEF INPUT  PARAM wParam  AS LONG.
  DEF INPUT  PARAM lParam  AS LONG.
  DEF RETURN PARAM bReturn AS LONG.
END PROCEDURE.


Posted by josephathieu on 03-Jan-2015 02:55

I read this: community.progress.com/.../2096.aspx.

Unfortunately, this code enable \ disable an entire column and not only cells of the row. (I'm working with the 10.0B).

Posted by josephathieu on 03-Jan-2015 03:00

The browse may not be appropriate, should I not use another object (smart...)?

Posted by josephathieu on 03-Jan-2015 03:06

Olivier, the entry occurs one time, when you enter into the browse. I tried in other triggers but i couldn't get succes. It is not the solution but the idea is good....

Posted by olivier.dunemann on 05-Jan-2015 00:53

Sorry, I should have double-checked it before posting.

Actually my suggestion works if you have another enabled column on the right of the one you want to conditionally disable.

This is a sample based on the sports2000 db.

&ANALYZE-SUSPEND _VERSION-NUMBER AB_v10r12 GUI
&ANALYZE-RESUME
/* Connected Databases 
          sports2000       PROGRESS
*/
&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.      */
/*----------------------------------------------------------------------*/

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

/* _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
&Scoped-define BROWSE-NAME BROWSE-1

/* Internal Tables (found by Frame, Query & Browse Queries)             */
&Scoped-define INTERNAL-TABLES Customer

/* Definitions for BROWSE BROWSE-1                                      */
&Scoped-define FIELDS-IN-QUERY-BROWSE-1 Customer.CustNum Customer.Name ~
Customer.Phone Customer.Fax 
&Scoped-define ENABLED-FIELDS-IN-QUERY-BROWSE-1 Customer.Phone Customer.Fax 
&Scoped-define ENABLED-TABLES-IN-QUERY-BROWSE-1 Customer
&Scoped-define FIRST-ENABLED-TABLE-IN-QUERY-BROWSE-1 Customer
&Scoped-define QUERY-STRING-BROWSE-1 FOR EACH Customer NO-LOCK INDEXED-REPOSITION
&Scoped-define OPEN-QUERY-BROWSE-1 OPEN QUERY BROWSE-1 FOR EACH Customer NO-LOCK INDEXED-REPOSITION.
&Scoped-define TABLES-IN-QUERY-BROWSE-1 Customer
&Scoped-define FIRST-TABLE-IN-QUERY-BROWSE-1 Customer


/* Definitions for FRAME DEFAULT-FRAME                                  */
&Scoped-define OPEN-BROWSERS-IN-QUERY-DEFAULT-FRAME ~
    ~{&OPEN-QUERY-BROWSE-1}

/* Standard List Definitions                                            */
&Scoped-Define ENABLED-OBJECTS FILL-IN-1 BROWSE-1 
&Scoped-Define DISPLAYED-OBJECTS FILL-IN-1 

/* 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 VARIABLE FILL-IN-1 AS CHARACTER FORMAT "X(256)":U 
     LABEL "Fill 1" 
     VIEW-AS FILL-IN 
     SIZE 14 BY 1 NO-UNDO.

/* Query definitions                                                    */
&ANALYZE-SUSPEND
DEFINE QUERY BROWSE-1 FOR 
      Customer SCROLLING.
&ANALYZE-RESUME

/* Browse definitions                                                   */
DEFINE BROWSE BROWSE-1
&ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS BROWSE-1 C-Win _STRUCTURED
  QUERY BROWSE-1 NO-LOCK DISPLAY
      Customer.CustNum FORMAT ">>>>9":U
      Customer.Name FORMAT "x(30)":U
      Customer.Phone FORMAT "x(20)":U
      Customer.Fax FORMAT "x(20)":U
  ENABLE
      Customer.Phone
      Customer.Fax
/* _UIB-CODE-BLOCK-END */
&ANALYZE-RESUME
    WITH NO-ROW-MARKERS SEPARATORS SIZE 87 BY 7.38.


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

DEFINE FRAME DEFAULT-FRAME
     FILL-IN-1 AT ROW 1.48 COL 15 COLON-ALIGNED WIDGET-ID 2
     BROWSE-1 AT ROW 2.91 COL 2 WIDGET-ID 200
    WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY 
         SIDE-LABELS NO-UNDERLINE THREE-D 
         AT COL 1 ROW 1
         SIZE 89.8 BY 9.81 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             = 9.81
         WIDTH              = 89.8
         MAX-HEIGHT         = 16
         MAX-WIDTH          = 156.4
         VIRTUAL-HEIGHT     = 16
         VIRTUAL-WIDTH      = 156.4
         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                                                           */
/* BROWSE-TAB BROWSE-1 FILL-IN-1 DEFAULT-FRAME */
IF SESSION:DISPLAY-TYPE = "GUI":U AND VALID-HANDLE(C-Win)
THEN C-Win:HIDDEN = no.

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


/* Setting information for Queries and Browse Widgets fields            */

&ANALYZE-SUSPEND _QUERY-BLOCK BROWSE BROWSE-1
/* Query rebuild information for BROWSE BROWSE-1
     _TblList          = "sports2000.Customer"
     _Options          = "NO-LOCK INDEXED-REPOSITION"
     _FldNameList[1]   = sports2000.Customer.CustNum
     _FldNameList[2]   = sports2000.Customer.Name
     _FldNameList[3]   > sports2000.Customer.Phone
"Phone" ? ? "character" ? ? ? ? ? ? yes ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
     _FldNameList[4]   > sports2000.Customer.Fax
"Fax" ? ? "character" ? ? ? ? ? ? yes ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
     _Query            is OPENED
*/  /* BROWSE BROWSE-1 */
&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 BROWSE-NAME BROWSE-1
&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}.

ON ENTRY OF Customer.Phone IN BROWSE browse-1
DO:
  /* We don't want to stay on this enabled cell */
 
  DEF VAR i AS INT NO-UNDO.
 
  &SCOPED-DEFINE VK_TAB 9
  &SCOPED-DEFINE WM_KEYDOWN 256
 
  IF Customer.custnum < 10 THEN
  /* Simulate a TAB Key-Down event... */
  RUN PostMessageA (SELF:HWND, {&WM_KEYDOWN}, {&VK_TAB}, 0, OUTPUT i).

END.

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

PROCEDURE PostMessageA EXTERNAL "user32":u:
  DEF INPUT  PARAM hHWND   AS LONG.
  DEF INPUT  PARAM Msg     AS LONG.
  DEF INPUT  PARAM wParam  AS LONG.
  DEF INPUT  PARAM lParam  AS LONG.
  DEF RETURN PARAM bReturn AS LONG.
END PROCEDURE.

/* _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.
------------------------------------------------------------------------------*/
  DISPLAY FILL-IN-1 
      WITH FRAME DEFAULT-FRAME IN WINDOW C-Win.
  ENABLE FILL-IN-1 BROWSE-1 
      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


This thread is closed