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
/tpapprvr.i
}
39 DEF VAR PersonName
AS CHAR FORMAT "X(30)" LABEL "Name".
41 /* _UIB-CODE-BLOCK-END
*/
45 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
47 /* ******************** Preprocessor Definitions
******************** */
49 &Scoped-define PROCEDURE-TYPE SmartBrowser
51 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
53 /* Name of first Frame and
/or Browse and
/or first Query
*/
54 &Scoped-define FRAME-NAME F-Main
55 &Scoped-define BROWSE-NAME br_table
57 /* Internal Tables
(found by Frame
, Query
& Browse Queries) */
58 &Scoped-define INTERNAL-TABLES Approver Person
60 /* Define KEY-PHRASE in case it is used by any query.
*/
61 &Scoped-define KEY-PHRASE TRUE
63 /* Definitions for
BROWSE br_table
*/
64 &Scoped-define FIELDS-IN-QUERY-br_table Approver.ApproverCode ~
65 Person.FirstName
+ ' '
+ Person.LastName @ PersonName ~
66 Approver.ApprovalLimit Approver.SignatoryLimit
67 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table
68 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table
69 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH Approver WHERE ~{&KEY-PHRASE} ~
70 AND Approver.Active
NO-LOCK, ~
71 EACH Person
OF Approver
OUTER-JOIN NO-LOCK ~
73 &Scoped-define TABLES-IN-QUERY-br_table Approver Person
74 &Scoped-define FIRST-TABLE-IN-QUERY-br_table Approver
77 /* Definitions for
FRAME F-Main
*/
79 /* Standard List Definitions
*/
80 &Scoped-Define ENABLED-OBJECTS br_table
82 /* Custom List Definitions
*/
83 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
85 /* _UIB-PREPROCESSOR-BLOCK-END
*/
89 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
90 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
96 PersonCode||y|TTPL.Approver.PersonCode
97 ApproverCode||y|TTPL.Approver.ApproverCode
100 **************************
101 * Set attributes related to FOREIGN
KEYS
103 RUN set-attribute-list
(
105 Keys-Supplied
= "PersonCode,ApproverCode"'
:U
).
107 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
108 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
109 /**************************
111 /* _UIB-CODE-BLOCK-END
*/
114 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
115 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
123 ************************
124 * Set attributes related to SORTBY-OPTIONS
*/
125 RUN set-attribute-list
(
126 'SortBy-Options
= ""'
:U
).
127 /************************
130 </FILTER-ATTRIBUTES
> */
132 /* _UIB-CODE-BLOCK-END
*/
136 /* *********************** Control Definitions
********************** */
139 /* Definitions of the field level widgets
*/
140 /* Query definitions
*/
142 DEFINE QUERY br_table
FOR
145 FIELDS(Person.FirstName
146 Person.LastName
) SCROLLING.
149 /* Browse definitions
*/
150 DEFINE BROWSE br_table
151 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
152 QUERY br_table
NO-LOCK DISPLAY
153 Approver.ApproverCode
COLUMN-LABEL "Initials"
154 Person.FirstName
+ ' '
+ Person.LastName @ PersonName
COLUMN-LABEL "Name"
155 Approver.ApprovalLimit
COLUMN-LABEL "Approval Limit"
156 Approver.SignatoryLimit
COLUMN-LABEL "Signatory Limit"
157 /* _UIB-CODE-BLOCK-END
*/
159 WITH NO-ASSIGN SEPARATORS SIZE 50.86 BY 16.4
163 /* ************************ Frame Definitions
*********************** */
166 br_table
AT ROW 1 COL 1
167 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
168 SIDE-LABELS NO-UNDERLINE THREE-D
169 AT COL 1 ROW 1 SCROLLABLE
173 /* *********************** Procedure Settings
************************ */
175 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
176 /* Settings for
THIS-PROCEDURE
180 Add Fields to
: EXTERNAL-TABLES
181 Other Settings
: PERSISTENT-ONLY
COMPILE
184 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
185 /* then cleanup and return.
*/
186 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
187 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
188 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
192 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
194 /* ************************* Create Window
************************** */
196 &ANALYZE-SUSPEND _CREATE-WINDOW
197 /* DESIGN Window definition
(used by the UIB
)
198 CREATE WINDOW B-table-Win
ASSIGN
201 /* END WINDOW DEFINITION
*/
206 /* *************** Runtime Attributes and UIB Settings
************** */
208 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
209 /* SETTINGS
FOR WINDOW B-table-Win
210 NOT-VISIBLE
,,RUN-PERSISTENT
*/
211 /* SETTINGS
FOR FRAME F-Main
212 NOT-VISIBLE Size-to-Fit
*/
213 /* BROWSE-TAB br_table
1 F-Main
*/
215 FRAME F-Main
:SCROLLABLE = FALSE
216 FRAME F-Main
:HIDDEN = TRUE.
218 /* _RUN-TIME-ATTRIBUTES-END
*/
222 /* Setting information for Queries and Browse Widgets fields
*/
224 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
225 /* Query rebuild information for
BROWSE br_table
226 _TblList
= "ttpl.Approver,ttpl.Person OF ttpl.Approver"
227 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
228 _TblOptList
= ", OUTER USED"
229 _Where
[1] = "Approver.Active"
230 _FldNameList
[1] > TTPL.Approver.ApproverCode
231 "Approver.ApproverCode" "Initials" ?
"character" ? ? ? ? ? ? no ?
232 _FldNameList
[2] > "_<CALC>"
233 "Person.FirstName + ' ' + Person.LastName @ PersonName" "Name" ? ? ? ? ? ? ? ? no ?
234 _FldNameList
[3] > TTPL.Approver.ApprovalLimit
235 "Approver.ApprovalLimit" "Approval Limit" ?
"decimal" ? ? ? ? ? ? no ?
236 _FldNameList
[4] > TTPL.Approver.SignatoryLimit
237 "Approver.SignatoryLimit" "Signatory Limit" ?
"decimal" ? ? ? ? ? ? no ?
239 */ /* BROWSE br_table
*/
242 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
243 /* Query rebuild information for
FRAME F-Main
246 */ /* FRAME F-Main
*/
252 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
253 /* ************************* Included-Libraries
*********************** */
255 {src
/adm
/method
/browser.i
}
256 {inc
/method
/m-selvwr.i
}
258 /* _UIB-CODE-BLOCK-END
*/
264 /* ************************ Control Triggers
************************ */
266 &Scoped-define BROWSE-NAME br_table
267 &Scoped-define SELF-NAME br_table
268 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
269 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
271 /* This code displays initial values for newly added or copied rows.
*/
272 {src
/adm
/template
/brsentry.i
}
275 /* _UIB-CODE-BLOCK-END
*/
279 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
280 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
282 /* Do not disable this code or no updates will take place except
283 by pressing the Save button on an Update SmartPanel.
*/
284 {src
/adm
/template
/brsleave.i
}
287 /* _UIB-CODE-BLOCK-END
*/
291 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
292 ON VALUE-CHANGED
OF br_table
IN FRAME F-Main
294 /* This ADM trigger code must be preserved in order to notify other
295 objects when the browser's current row changes.
*/
296 {src
/adm
/template
/brschnge.i
}
300 /* _UIB-CODE-BLOCK-END
*/
306 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
309 /* *************************** Main Block
*************************** */
311 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
312 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
315 /* _UIB-CODE-BLOCK-END
*/
319 /* ********************** Internal Procedures
*********************** */
321 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-open-query-cases B-table-Win adm/support/_adm-opn.p
322 PROCEDURE adm-open-query-cases
:
323 /*------------------------------------------------------------------------------
324 Purpose
: Opens different cases of the query based on attributes
325 such as the 'Key-Name'
, or 'SortBy-Case'
327 ------------------------------------------------------------------------------*/
329 /* No Foreign keys are accepted by this SmartObject.
*/
331 {&OPEN-QUERY-{&BROWSE-NAME}}
335 /* _UIB-CODE-BLOCK-END
*/
339 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
340 PROCEDURE adm-row-available
:
341 /*------------------------------------------------------------------------------
342 Purpose
: Dispatched to this procedure when the Record-
343 Source has a new row available. This procedure
344 tries to get the new row
(or foriegn keys
) from
345 the Record-Source and process it.
347 ------------------------------------------------------------------------------*/
349 /* Define variables needed by this internal procedure.
*/
350 {src
/adm
/template
/row-head.i
}
352 /* Process the newly available records
(i.e. display fields
,
353 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
354 {src
/adm
/template
/row-end.i
}
358 /* _UIB-CODE-BLOCK-END
*/
362 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
363 PROCEDURE disable_UI
:
364 /*------------------------------------------------------------------------------
365 Purpose
: DISABLE the User Interface
367 Notes
: Here we clean-up the user-interface by deleting
368 dynamic widgets we have created and
/or hide
369 frames. This procedure is usually called when
370 we are ready to
"clean-up" after running.
371 ------------------------------------------------------------------------------*/
372 /* Hide all frames.
*/
374 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
377 /* _UIB-CODE-BLOCK-END
*/
381 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
383 /*------------------------------------------------------------------------------
384 Purpose
: Sends a requested
KEY value back to the calling
386 Parameters
: <see adm
/template
/sndkytop.i
>
387 ------------------------------------------------------------------------------*/
389 /* Define variables needed by this internal procedure.
*/
390 {src
/adm
/template
/sndkytop.i
}
392 /* Return the key value associated with each key case.
*/
393 {src
/adm
/template
/sndkycas.i
"PersonCode" "Approver" "PersonCode"}
394 {src
/adm
/template
/sndkycas.i
"ApproverCode" "Approver" "ApproverCode"}
396 /* Close the
CASE statement and end the procedure.
*/
397 {src
/adm
/template
/sndkyend.i
}
401 /* _UIB-CODE-BLOCK-END
*/
405 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
406 PROCEDURE send-records
:
407 /*------------------------------------------------------------------------------
408 Purpose
: Send record
ROWID's for all tables used by
410 Parameters
: see template
/snd-head.i
411 ------------------------------------------------------------------------------*/
413 /* Define variables needed by this internal procedure.
*/
414 {src
/adm
/template
/snd-head.i
}
416 /* For each requested table
, put it's
ROWID in the output list.
*/
417 {src
/adm
/template
/snd-list.i
"Approver"}
418 {src
/adm
/template
/snd-list.i
"Person"}
420 /* Deal with any unexpected table requests before closing.
*/
421 {src
/adm
/template
/snd-end.i
}
425 /* _UIB-CODE-BLOCK-END
*/
429 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
430 PROCEDURE state-changed
:
431 /* -----------------------------------------------------------
435 -------------------------------------------------------------*/
436 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
437 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
440 /* Object instance CASEs can go here to replace standard behavior
442 {src
/adm
/template
/bstates.i
}
446 /* _UIB-CODE-BLOCK-END
*/