1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS B-table-Win
8 /*------------------------------------------------------------------------
12 Description
: from BROWSER.W
- Basic SmartBrowser Object Template
20 ------------------------------------------------------------------------*/
21 /* This .W file was created with the Progress UIB.
*/
22 /*----------------------------------------------------------------------*/
24 /* Create an unnamed pool to store all the widgets created
25 by this procedure. This is a good default which assures
26 that this procedure's triggers and internal procedures
27 will execute in this procedure's storage
, and that proper
28 cleanup will occur on deletion of the procedure.
*/
32 /* *************************** Definitions
************************** */
34 /* Parameters Definitions
--- */
36 /* Local Variable Definitions
--- */
38 {inc
/topic
/tpproper.i
}
39 DEF VAR all-properties
AS LOGI
NO-UNDO.
40 DEF VAR filter-val
AS CHAR NO-UNDO.
42 DEF VAR gap-1
AS CHAR NO-UNDO FORMAT "X" LABEL "".
44 /* _UIB-CODE-BLOCK-END
*/
48 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
50 /* ******************** Preprocessor Definitions
******************** */
52 &Scoped-define PROCEDURE-TYPE SmartBrowser
54 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
56 /* Name of first Frame and
/or Browse and
/or first Query
*/
57 &Scoped-define FRAME-NAME F-Main
58 &Scoped-define BROWSE-NAME br_table
60 /* Internal Tables
(found by Frame
, Query
& Browse Queries) */
61 &Scoped-define INTERNAL-TABLES Property
63 /* Define KEY-PHRASE in case it is used by any query.
*/
64 &Scoped-define KEY-PHRASE TRUE
66 /* Definitions for
BROWSE br_table
*/
67 &Scoped-define FIELDS-IN-QUERY-br_table Property.ShortName Property.Active ~
68 Property.Name Property.PropertyCode Property.CompanyCode gap-1 @ gap-1 ~
69 Property.StreetAddress
70 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table
71 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table
72 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH Property WHERE ~{&KEY-PHRASE} ~
73 AND ( all-properties
OR Property.Active
) ~
75 Property.ShortName
BEGINS filter-val
NO-LOCK ~
77 &Scoped-define TABLES-IN-QUERY-br_table Property
78 &Scoped-define FIRST-TABLE-IN-QUERY-br_table Property
81 /* Definitions for
FRAME F-Main
*/
83 /* Standard List Definitions
*/
84 &Scoped-Define ENABLED-OBJECTS br_table
86 /* Custom List Definitions
*/
87 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
89 /* _UIB-PREPROCESSOR-BLOCK-END
*/
93 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
94 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
100 BuildingType||y|TTPL.Property.BuildingType
101 CompanyCode||y|TTPL.Property.CompanyCode
102 PropertyCode||y|TTPL.Property.PropertyCode
103 NoteCode||y|TTPL.Property.NoteCode
106 **************************
107 * Set attributes related to FOREIGN
KEYS
109 RUN set-attribute-list
(
111 Keys-Supplied
= "BuildingType,CompanyCode,PropertyCode,NoteCode"'
:U
).
113 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
114 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
115 /**************************
117 /* _UIB-CODE-BLOCK-END
*/
120 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
121 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
127 Company|||TTPL.Property.CompanyCode|yes
128 Code|y||TTPL.Property.PropertyCode|yes
129 Short Name|||TTPL.Property.ShortName|yes
132 ************************
133 * Set attributes related to SORTBY-OPTIONS
*/
134 RUN set-attribute-list
(
135 'SortBy-Options
= "Company,Code,Short Name",
136 SortBy-Case
= Code'
:U
).
138 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
139 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
141 /* This SmartObject is a valid SortBy-Target.
*/
142 &IF '{&user-supported-links}':U ne '':U &THEN
143 &Scoped-define user-supported-links {&user-supported-links},SortBy-Target
145 &Scoped-define user-supported-links SortBy-Target
148 /************************
151 </FILTER-ATTRIBUTES
> */
153 /* _UIB-CODE-BLOCK-END
*/
157 /* *********************** Control Definitions
********************** */
160 /* Definitions of the field level widgets
*/
161 /* Query definitions
*/
163 DEFINE QUERY br_table
FOR
167 /* Browse definitions
*/
168 DEFINE BROWSE br_table
169 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
170 QUERY br_table
NO-LOCK DISPLAY
171 Property.ShortName
FORMAT "X(15)"
172 Property.Active
FORMAT "Yes/---"
174 Property.PropertyCode
FORMAT "Z99999"
177 Property.StreetAddress
178 /* _UIB-CODE-BLOCK-END
*/
180 WITH NO-ASSIGN SEPARATORS SIZE 93.14 BY 15.2
184 /* ************************ Frame Definitions
*********************** */
187 br_table
AT ROW 1 COL 1
188 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
189 SIDE-LABELS NO-UNDERLINE THREE-D
190 AT COL 1 ROW 1 SCROLLABLE
194 /* *********************** Procedure Settings
************************ */
196 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
197 /* Settings for
THIS-PROCEDURE
201 Add Fields to
: EXTERNAL-TABLES
202 Other Settings
: PERSISTENT-ONLY
COMPILE
205 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
206 /* then cleanup and return.
*/
207 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
208 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
209 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
213 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
215 /* ************************* Create Window
************************** */
217 &ANALYZE-SUSPEND _CREATE-WINDOW
218 /* DESIGN Window definition
(used by the UIB
)
219 CREATE WINDOW B-table-Win
ASSIGN
222 /* END WINDOW DEFINITION
*/
227 /* *************** Runtime Attributes and UIB Settings
************** */
229 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
230 /* SETTINGS
FOR WINDOW B-table-Win
231 NOT-VISIBLE
,,RUN-PERSISTENT
*/
232 /* SETTINGS
FOR FRAME F-Main
233 NOT-VISIBLE Size-to-Fit
*/
234 /* BROWSE-TAB br_table
1 F-Main
*/
236 FRAME F-Main
:SCROLLABLE = FALSE
237 FRAME F-Main
:HIDDEN = TRUE.
239 /* _RUN-TIME-ATTRIBUTES-END
*/
243 /* Setting information for Queries and Browse Widgets fields
*/
245 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
246 /* Query rebuild information for
BROWSE br_table
247 _TblList
= "TTPL.Property"
248 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
249 _Where
[1] = "( all-properties OR Property.Active )
251 Property.ShortName BEGINS filter-val"
252 _FldNameList
[1] > TTPL.Property.ShortName
253 "Property.ShortName" ?
"X(15)" "character" ? ? ? ? ? ? no ?
254 _FldNameList
[2] > TTPL.Property.Active
255 "Property.Active" ?
"Yes/---" "logical" ? ? ? ? ? ? no ?
256 _FldNameList
[3] = TTPL.Property.Name
257 _FldNameList
[4] > TTPL.Property.PropertyCode
258 "Property.PropertyCode" ?
"Z99999" "integer" ? ? ? ? ? ? no ?
259 _FldNameList
[5] = TTPL.Property.CompanyCode
260 _FldNameList
[6] > "_<CALC>"
261 "gap-1 @ gap-1" ? ? ? ? ? ? ? ? ? no ?
262 _FldNameList
[7] = TTPL.Property.StreetAddress
264 */ /* BROWSE br_table
*/
267 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
268 /* Query rebuild information for
FRAME F-Main
271 */ /* FRAME F-Main
*/
277 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
278 /* ************************* Included-Libraries
*********************** */
280 {src
/adm
/method
/browser.i
}
281 {inc
/method
/m-selvwr.i
}
283 /* _UIB-CODE-BLOCK-END
*/
289 /* ************************ Control Triggers
************************ */
291 &Scoped-define BROWSE-NAME br_table
292 &Scoped-define SELF-NAME br_table
293 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
294 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
296 /* This code displays initial values for newly added or copied rows.
*/
297 {src
/adm
/template
/brsentry.i
}
300 /* _UIB-CODE-BLOCK-END
*/
304 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
305 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
307 /* Do not disable this code or no updates will take place except
308 by pressing the Save button on an Update SmartPanel.
*/
309 {src
/adm
/template
/brsleave.i
}
312 /* _UIB-CODE-BLOCK-END
*/
316 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
317 ON VALUE-CHANGED
OF br_table
IN FRAME F-Main
319 /* This ADM trigger code must be preserved in order to notify other
320 objects when the browser's current row changes.
*/
321 {src
/adm
/template
/brschnge.i
}
325 /* _UIB-CODE-BLOCK-END
*/
331 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
334 /* *************************** Main Block
*************************** */
336 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
337 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
340 RUN set-attribute-list
( 'FilterBy-Options
= Active|All
, FilterBy-Case
= Active'
:U
).
341 RUN set-attribute-list
( 'Filter-Valeu
='
:U
).
343 /* _UIB-CODE-BLOCK-END
*/
347 /* ********************** Internal Procedures
*********************** */
349 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-open-query-cases B-table-Win adm/support/_adm-opn.p
350 PROCEDURE adm-open-query-cases
:
351 /*------------------------------------------------------------------------------
352 Purpose
: Opens different cases of the query based on attributes
353 such as the 'Key-Name'
, or 'SortBy-Case'
355 ------------------------------------------------------------------------------*/
357 /* No Foreign keys are accepted by this SmartObject.
*/
359 RUN get-attribute
('SortBy-Case'
:U
).
361 WHEN 'Company'
:U
THEN DO:
362 &Scope SORTBY-PHRASE BY Property.CompanyCode
363 {&OPEN-QUERY-{&BROWSE-NAME}}
365 WHEN 'Code'
:U
THEN DO:
366 &Scope SORTBY-PHRASE BY Property.PropertyCode
367 {&OPEN-QUERY-{&BROWSE-NAME}}
369 WHEN 'Short Name'
:U
THEN DO:
370 &Scope SORTBY-PHRASE BY Property.ShortName
371 {&OPEN-QUERY-{&BROWSE-NAME}}
374 &Undefine SORTBY-PHRASE
375 {&OPEN-QUERY-{&BROWSE-NAME}}
376 END.
/* OTHERWISE...
*/
381 /* _UIB-CODE-BLOCK-END
*/
385 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
386 PROCEDURE adm-row-available
:
387 /*------------------------------------------------------------------------------
388 Purpose
: Dispatched to this procedure when the Record-
389 Source has a new row available. This procedure
390 tries to get the new row
(or foriegn keys
) from
391 the Record-Source and process it.
393 ------------------------------------------------------------------------------*/
395 /* Define variables needed by this internal procedure.
*/
396 {src
/adm
/template
/row-head.i
}
398 /* Process the newly available records
(i.e. display fields
,
399 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
400 {src
/adm
/template
/row-end.i
}
404 /* _UIB-CODE-BLOCK-END
*/
408 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
409 PROCEDURE disable_UI
:
410 /*------------------------------------------------------------------------------
411 Purpose
: DISABLE the User Interface
413 Notes
: Here we clean-up the user-interface by deleting
414 dynamic widgets we have created and
/or hide
415 frames. This procedure is usually called when
416 we are ready to
"clean-up" after running.
417 ------------------------------------------------------------------------------*/
418 /* Hide all frames.
*/
420 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
423 /* _UIB-CODE-BLOCK-END
*/
427 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
429 /*------------------------------------------------------------------------------
430 Purpose
: Sends a requested
KEY value back to the calling
432 Parameters
: <see adm
/template
/sndkytop.i
>
433 ------------------------------------------------------------------------------*/
435 /* Define variables needed by this internal procedure.
*/
436 {src
/adm
/template
/sndkytop.i
}
438 /* Return the key value associated with each key case.
*/
439 {src
/adm
/template
/sndkycas.i
"BuildingType" "Property" "BuildingType"}
440 {src
/adm
/template
/sndkycas.i
"CompanyCode" "Property" "CompanyCode"}
441 {src
/adm
/template
/sndkycas.i
"PropertyCode" "Property" "PropertyCode"}
442 {src
/adm
/template
/sndkycas.i
"NoteCode" "Property" "NoteCode"}
444 /* Close the
CASE statement and end the procedure.
*/
445 {src
/adm
/template
/sndkyend.i
}
449 /* _UIB-CODE-BLOCK-END
*/
453 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
454 PROCEDURE send-records
:
455 /*------------------------------------------------------------------------------
456 Purpose
: Send record
ROWID's for all tables used by
458 Parameters
: see template
/snd-head.i
459 ------------------------------------------------------------------------------*/
461 /* Define variables needed by this internal procedure.
*/
462 {src
/adm
/template
/snd-head.i
}
464 /* For each requested table
, put it's
ROWID in the output list.
*/
465 {src
/adm
/template
/snd-list.i
"Property"}
467 /* Deal with any unexpected table requests before closing.
*/
468 {src
/adm
/template
/snd-end.i
}
472 /* _UIB-CODE-BLOCK-END
*/
476 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
477 PROCEDURE state-changed
:
478 /* -----------------------------------------------------------
482 -------------------------------------------------------------*/
483 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
484 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
487 /* Object instance CASEs can go here to replace standard behavior
489 {src
/adm
/template
/bstates.i
}
493 /* _UIB-CODE-BLOCK-END
*/
497 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-Filter-Value B-table-Win
498 PROCEDURE use-Filter-Value
:
499 /*------------------------------------------------------------------------------
503 ------------------------------------------------------------------------------*/
505 DEF INPUT PARAMETER new-value
AS CHAR NO-UNDO.
506 filter-val
= new-value.
510 /* _UIB-CODE-BLOCK-END
*/
514 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-FilterBy-Case B-table-Win
515 PROCEDURE use-FilterBy-Case
:
516 /*------------------------------------------------------------------------------
520 ------------------------------------------------------------------------------*/
522 DEF INPUT PARAMETER new-case
AS CHAR NO-UNDO.
523 all-properties
= new-case
= "All".
527 /* _UIB-CODE-BLOCK-END
*/