Really, this should be it, for the passing income.
[capital-apms-progress.git] / workflow / b-flow-rule-type.w
blob8b2e0063642336acc628dcf5d55cb12d58ab5843
1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
2 &ANALYZE-RESUME
3 /* Connected Databases
4 ttpl PROGRESS
5 */
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS B-table-Win
8 /*------------------------------------------------------------------------
10 File:
12 Description: from BROWSER.W - Basic SmartBrowser Object Template
14 Input Parameters:
15 <none>
17 Output Parameters:
18 <none>
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. */
30 CREATE WIDGET-POOL.
32 /* *************************** Definitions ************************** */
34 /* Parameters Definitions --- */
36 /* Local Variable Definitions --- */
38 /* _UIB-CODE-BLOCK-END */
39 &ANALYZE-RESUME
42 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
44 /* ******************** Preprocessor Definitions ******************** */
46 &Scoped-define PROCEDURE-TYPE SmartBrowser
48 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
50 /* Name of first Frame and/or Browse and/or first Query */
51 &Scoped-define FRAME-NAME F-Main
52 &Scoped-define BROWSE-NAME br_table
54 /* Internal Tables (found by Frame, Query & Browse Queries) */
55 &Scoped-define INTERNAL-TABLES FlowRuleType
57 /* Define KEY-PHRASE in case it is used by any query. */
58 &Scoped-define KEY-PHRASE TRUE
60 /* Definitions for BROWSE br_table */
61 &Scoped-define FIELDS-IN-QUERY-br_table FlowRuleType.FlowRuleType ~
62 FlowRuleType.Description
63 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table FlowRuleType.FlowRuleType ~
64 FlowRuleType.Description
65 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table~
66 ~{&FP1}FlowRuleType ~{&FP2}FlowRuleType ~{&FP3}~
67 ~{&FP1}Description ~{&FP2}Description ~{&FP3}
68 &Scoped-define ENABLED-TABLES-IN-QUERY-br_table FlowRuleType
69 &Scoped-define FIRST-ENABLED-TABLE-IN-QUERY-br_table FlowRuleType
70 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH FlowRuleType WHERE ~{&KEY-PHRASE} NO-LOCK ~
71 ~{&SORTBY-PHRASE}.
72 &Scoped-define TABLES-IN-QUERY-br_table FlowRuleType
73 &Scoped-define FIRST-TABLE-IN-QUERY-br_table FlowRuleType
76 /* Definitions for FRAME F-Main */
78 /* Standard List Definitions */
79 &Scoped-Define ENABLED-OBJECTS br_table
81 /* Custom List Definitions */
82 /* List-1,List-2,List-3,List-4,List-5,List-6 */
84 /* _UIB-PREPROCESSOR-BLOCK-END */
85 &ANALYZE-RESUME
88 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
89 /* Actions: ? adm/support/keyedit.w ? ? ? */
90 /* STRUCTURED-DATA
91 <KEY-OBJECT>
92 &BROWSE-NAME
93 </KEY-OBJECT>
94 <FOREIGN-KEYS>
95 </FOREIGN-KEYS>
96 <EXECUTING-CODE>
97 **************************
98 * Set attributes related to FOREIGN KEYS
100 RUN set-attribute-list (
101 'Keys-Accepted = "",
102 Keys-Supplied = ""':U).
103 /**************************
104 </EXECUTING-CODE> */
106 /* _UIB-CODE-BLOCK-END */
107 &ANALYZE-RESUME
109 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
110 /* Actions: ? adm/support/advqedit.w ? ? ? */
111 /* STRUCTURED-DATA
112 <KEY-OBJECT>
113 &BROWSE-NAME
114 </KEY-OBJECT>
115 <SORTBY-OPTIONS>
116 </SORTBY-OPTIONS>
117 <SORTBY-RUN-CODE>
118 ************************
119 * Set attributes related to SORTBY-OPTIONS */
120 RUN set-attribute-list (
121 'SortBy-Options = ""':U).
122 /************************
123 </SORTBY-RUN-CODE>
124 <FILTER-ATTRIBUTES>
125 </FILTER-ATTRIBUTES> */
127 /* _UIB-CODE-BLOCK-END */
128 &ANALYZE-RESUME
131 /* *********************** Control Definitions ********************** */
134 /* Definitions of the field level widgets */
135 /* Query definitions */
136 &ANALYZE-SUSPEND
137 DEFINE QUERY br_table FOR
138 FlowRuleType SCROLLING.
139 &ANALYZE-RESUME
141 /* Browse definitions */
142 DEFINE BROWSE br_table
143 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
144 QUERY br_table NO-LOCK DISPLAY
145 FlowRuleType.FlowRuleType COLUMN-LABEL "Rule Type"
146 FlowRuleType.Description
147 ENABLE
148 FlowRuleType.FlowRuleType
149 FlowRuleType.Description
150 /* _UIB-CODE-BLOCK-END */
151 &ANALYZE-RESUME
152 WITH NO-ASSIGN SEPARATORS SIZE 49.72 BY 12.8
153 BGCOLOR 16 .
156 /* ************************ Frame Definitions *********************** */
158 DEFINE FRAME F-Main
159 br_table AT ROW 1 COL 1
160 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
161 SIDE-LABELS NO-UNDERLINE THREE-D
162 AT COL 1 ROW 1 SCROLLABLE
163 BGCOLOR 8 FGCOLOR 0 .
166 /* *********************** Procedure Settings ************************ */
168 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
169 /* Settings for THIS-PROCEDURE
170 Type: SmartBrowser
171 Allow: Basic,Browse
172 Frames: 1
173 Add Fields to: EXTERNAL-TABLES
174 Other Settings: PERSISTENT-ONLY COMPILE
177 /* This procedure should always be RUN PERSISTENT. Report the error, */
178 /* then cleanup and return. */
179 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
180 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
181 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
182 RETURN.
183 END.
185 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
187 /* ************************* Create Window ************************** */
189 &ANALYZE-SUSPEND _CREATE-WINDOW
190 /* DESIGN Window definition (used by the UIB)
191 CREATE WINDOW B-table-Win ASSIGN
192 HEIGHT = 14.35
193 WIDTH = 76.86.
194 /* END WINDOW DEFINITION */
196 &ANALYZE-RESUME
199 /* *************** Runtime Attributes and UIB Settings ************** */
201 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
202 /* SETTINGS FOR WINDOW B-table-Win
203 NOT-VISIBLE,,RUN-PERSISTENT */
204 /* SETTINGS FOR FRAME F-Main
205 NOT-VISIBLE Size-to-Fit */
206 /* BROWSE-TAB br_table 1 F-Main */
207 ASSIGN
208 FRAME F-Main:SCROLLABLE = FALSE
209 FRAME F-Main:HIDDEN = TRUE.
211 /* _RUN-TIME-ATTRIBUTES-END */
212 &ANALYZE-RESUME
215 /* Setting information for Queries and Browse Widgets fields */
217 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
218 /* Query rebuild information for BROWSE br_table
219 _TblList = "TTPL.FlowRuleType"
220 _Options = "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
221 _FldNameList[1] > TTPL.FlowRuleType.FlowRuleType
222 "FlowRuleType.FlowRuleType" "Rule Type" ? "character" ? ? ? ? ? ? yes ?
223 _FldNameList[2] > TTPL.FlowRuleType.Description
224 "FlowRuleType.Description" ? ? "character" ? ? ? ? ? ? yes ?
225 _Query is NOT OPENED
226 */ /* BROWSE br_table */
227 &ANALYZE-RESUME
229 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
230 /* Query rebuild information for FRAME F-Main
231 _Options = "NO-LOCK"
232 _Query is NOT OPENED
233 */ /* FRAME F-Main */
234 &ANALYZE-RESUME
239 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
240 /* ************************* Included-Libraries *********************** */
242 {src/adm/method/browser.i}
243 {inc/method/m-drlvwr.i}
245 /* _UIB-CODE-BLOCK-END */
246 &ANALYZE-RESUME
251 /* ************************ Control Triggers ************************ */
253 &Scoped-define BROWSE-NAME br_table
254 &Scoped-define SELF-NAME br_table
255 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
256 ON ROW-ENTRY OF br_table IN FRAME F-Main
258 /* This code displays initial values for newly added or copied rows. */
259 {src/adm/template/brsentry.i}
260 END.
262 /* _UIB-CODE-BLOCK-END */
263 &ANALYZE-RESUME
266 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
267 ON ROW-LEAVE OF br_table IN FRAME F-Main
269 /* Do not disable this code or no updates will take place except
270 by pressing the Save button on an Update SmartPanel. */
271 {src/adm/template/brsleave.i}
272 END.
274 /* _UIB-CODE-BLOCK-END */
275 &ANALYZE-RESUME
278 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
279 ON VALUE-CHANGED OF br_table IN FRAME F-Main
281 /* This ADM trigger code must be preserved in order to notify other
282 objects when the browser's current row changes. */
283 {src/adm/template/brschnge.i}
284 END.
286 /* _UIB-CODE-BLOCK-END */
287 &ANALYZE-RESUME
290 &UNDEFINE SELF-NAME
292 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
295 /* *************************** Main Block *************************** */
297 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
298 RUN dispatch IN THIS-PROCEDURE ('initialize':U).
299 &ENDIF
301 /* _UIB-CODE-BLOCK-END */
302 &ANALYZE-RESUME
305 /* ********************** Internal Procedures *********************** */
307 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
308 PROCEDURE adm-row-available :
309 /*------------------------------------------------------------------------------
310 Purpose: Dispatched to this procedure when the Record-
311 Source has a new row available. This procedure
312 tries to get the new row (or foriegn keys) from
313 the Record-Source and process it.
314 Parameters: <none>
315 ------------------------------------------------------------------------------*/
317 /* Define variables needed by this internal procedure. */
318 {src/adm/template/row-head.i}
320 /* Process the newly available records (i.e. display fields,
321 open queries, and/or pass records on to any RECORD-TARGETS). */
322 {src/adm/template/row-end.i}
324 END PROCEDURE.
326 /* _UIB-CODE-BLOCK-END */
327 &ANALYZE-RESUME
330 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
331 PROCEDURE disable_UI :
332 /*------------------------------------------------------------------------------
333 Purpose: DISABLE the User Interface
334 Parameters: <none>
335 Notes: Here we clean-up the user-interface by deleting
336 dynamic widgets we have created and/or hide
337 frames. This procedure is usually called when
338 we are ready to "clean-up" after running.
339 ------------------------------------------------------------------------------*/
340 /* Hide all frames. */
341 HIDE FRAME F-Main.
342 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
343 END PROCEDURE.
345 /* _UIB-CODE-BLOCK-END */
346 &ANALYZE-RESUME
349 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
350 PROCEDURE send-records :
351 /*------------------------------------------------------------------------------
352 Purpose: Send record ROWID's for all tables used by
353 this file.
354 Parameters: see template/snd-head.i
355 ------------------------------------------------------------------------------*/
357 /* Define variables needed by this internal procedure. */
358 {src/adm/template/snd-head.i}
360 /* For each requested table, put it's ROWID in the output list. */
361 {src/adm/template/snd-list.i "FlowRuleType"}
363 /* Deal with any unexpected table requests before closing. */
364 {src/adm/template/snd-end.i}
366 END PROCEDURE.
368 /* _UIB-CODE-BLOCK-END */
369 &ANALYZE-RESUME
372 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
373 PROCEDURE state-changed :
374 /* -----------------------------------------------------------
375 Purpose:
376 Parameters: <none>
377 Notes:
378 -------------------------------------------------------------*/
379 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
380 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
382 CASE p-state:
383 /* Object instance CASEs can go here to replace standard behavior
384 or add new cases. */
385 {src/adm/template/bstates.i}
386 END CASE.
387 END PROCEDURE.
389 /* _UIB-CODE-BLOCK-END */
390 &ANALYZE-RESUME