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 /* _UIB-CODE-BLOCK-END
*/
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 FlowTaskType
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 FlowTaskType.FlowTaskType ~
62 FlowTaskType.Description FlowTaskType.InitialStep
63 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table
64 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table
65 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH FlowTaskType WHERE ~{&KEY-PHRASE} NO-LOCK ~
67 &Scoped-define TABLES-IN-QUERY-br_table FlowTaskType
68 &Scoped-define FIRST-TABLE-IN-QUERY-br_table FlowTaskType
71 /* Definitions for
FRAME F-Main
*/
73 /* Standard List Definitions
*/
74 &Scoped-Define ENABLED-OBJECTS br_table
76 /* Custom List Definitions
*/
77 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
79 /* _UIB-PREPROCESSOR-BLOCK-END
*/
83 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
84 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
90 FlowTaskType||y|TTPL.FlowTaskType.FlowTaskType
93 **************************
94 * Set attributes related to FOREIGN
KEYS
96 RUN set-attribute-list
(
98 Keys-Supplied
= "FlowTaskType"'
:U
).
100 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
101 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
102 /**************************
104 /* _UIB-CODE-BLOCK-END
*/
107 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
108 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
116 ************************
117 * Set attributes related to SORTBY-OPTIONS
*/
118 RUN set-attribute-list
(
119 'SortBy-Options
= ""'
:U
).
120 /************************
123 </FILTER-ATTRIBUTES
> */
125 /* _UIB-CODE-BLOCK-END
*/
129 /* *********************** Control Definitions
********************** */
132 /* Definitions of the field level widgets
*/
133 /* Query definitions
*/
135 DEFINE QUERY br_table
FOR
136 FlowTaskType
SCROLLING.
139 /* Browse definitions
*/
140 DEFINE BROWSE br_table
141 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
142 QUERY br_table
NO-LOCK DISPLAY
143 FlowTaskType.FlowTaskType
COLUMN-LABEL "Task Type"
144 FlowTaskType.Description
145 FlowTaskType.InitialStep
COLUMN-LABEL "Initial Step"
146 /* _UIB-CODE-BLOCK-END
*/
148 WITH NO-ASSIGN SEPARATORS SIZE 58.29 BY 12.8
152 /* ************************ Frame Definitions
*********************** */
155 br_table
AT ROW 1 COL 1
156 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
157 SIDE-LABELS NO-UNDERLINE THREE-D
158 AT COL 1 ROW 1 SCROLLABLE
159 BGCOLOR 8 FGCOLOR 0 .
162 /* *********************** Procedure Settings
************************ */
164 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
165 /* Settings for
THIS-PROCEDURE
169 Add Fields to
: EXTERNAL-TABLES
170 Other Settings
: PERSISTENT-ONLY
COMPILE
173 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
174 /* then cleanup and return.
*/
175 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
176 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
177 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
181 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
183 /* ************************* Create Window
************************** */
185 &ANALYZE-SUSPEND _CREATE-WINDOW
186 /* DESIGN Window definition
(used by the UIB
)
187 CREATE WINDOW B-table-Win
ASSIGN
190 /* END WINDOW DEFINITION
*/
195 /* *************** Runtime Attributes and UIB Settings
************** */
197 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
198 /* SETTINGS
FOR WINDOW B-table-Win
199 NOT-VISIBLE
,,RUN-PERSISTENT
*/
200 /* SETTINGS
FOR FRAME F-Main
201 NOT-VISIBLE Size-to-Fit
*/
202 /* BROWSE-TAB br_table
1 F-Main
*/
204 FRAME F-Main
:SCROLLABLE = FALSE
205 FRAME F-Main
:HIDDEN = TRUE.
207 /* _RUN-TIME-ATTRIBUTES-END
*/
211 /* Setting information for Queries and Browse Widgets fields
*/
213 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
214 /* Query rebuild information for
BROWSE br_table
215 _TblList
= "TTPL.FlowTaskType"
216 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
217 _FldNameList
[1] > TTPL.FlowTaskType.FlowTaskType
218 "FlowTaskType" "Task Type" ?
"character" ? ? ? ? ? ? no ?
219 _FldNameList
[2] = TTPL.FlowTaskType.Description
220 _FldNameList
[3] > TTPL.FlowTaskType.InitialStep
221 "InitialStep" "Initial Step" ?
"character" ? ? ? ? ? ? no ?
223 */ /* BROWSE br_table
*/
226 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
227 /* Query rebuild information for
FRAME F-Main
230 */ /* FRAME F-Main
*/
236 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
237 /* ************************* Included-Libraries
*********************** */
239 {src
/adm
/method
/browser.i
}
240 {inc
/method
/m-drlvwr.i
}
242 /* _UIB-CODE-BLOCK-END
*/
248 /* ************************ Control Triggers
************************ */
250 &Scoped-define BROWSE-NAME br_table
251 &Scoped-define SELF-NAME br_table
252 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
253 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
255 /* This code displays initial values for newly added or copied rows.
*/
256 {src
/adm
/template
/brsentry.i
}
259 /* _UIB-CODE-BLOCK-END
*/
263 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
264 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
266 /* Do not disable this code or no updates will take place except
267 by pressing the Save button on an Update SmartPanel.
*/
268 {src
/adm
/template
/brsleave.i
}
271 /* _UIB-CODE-BLOCK-END
*/
275 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
276 ON VALUE-CHANGED
OF br_table
IN FRAME F-Main
278 /* This ADM trigger code must be preserved in order to notify other
279 objects when the browser's current row changes.
*/
280 {src
/adm
/template
/brschnge.i
}
283 /* _UIB-CODE-BLOCK-END
*/
289 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
292 /* *************************** Main Block
*************************** */
294 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
295 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
298 /* _UIB-CODE-BLOCK-END
*/
302 /* ********************** Internal Procedures
*********************** */
304 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-open-query-cases B-table-Win adm/support/_adm-opn.p
305 PROCEDURE adm-open-query-cases
:
306 /*------------------------------------------------------------------------------
307 Purpose
: Opens different cases of the query based on attributes
308 such as the 'Key-Name'
, or 'SortBy-Case'
310 ------------------------------------------------------------------------------*/
312 /* No Foreign keys are accepted by this SmartObject.
*/
314 {&OPEN-QUERY-{&BROWSE-NAME}}
318 /* _UIB-CODE-BLOCK-END
*/
322 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
323 PROCEDURE adm-row-available
:
324 /*------------------------------------------------------------------------------
325 Purpose
: Dispatched to this procedure when the Record-
326 Source has a new row available. This procedure
327 tries to get the new row
(or foriegn keys
) from
328 the Record-Source and process it.
330 ------------------------------------------------------------------------------*/
332 /* Define variables needed by this internal procedure.
*/
333 {src
/adm
/template
/row-head.i
}
335 /* Process the newly available records
(i.e. display fields
,
336 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
337 {src
/adm
/template
/row-end.i
}
341 /* _UIB-CODE-BLOCK-END
*/
345 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
346 PROCEDURE disable_UI
:
347 /*------------------------------------------------------------------------------
348 Purpose
: DISABLE the User Interface
350 Notes
: Here we clean-up the user-interface by deleting
351 dynamic widgets we have created and
/or hide
352 frames. This procedure is usually called when
353 we are ready to
"clean-up" after running.
354 ------------------------------------------------------------------------------*/
355 /* Hide all frames.
*/
357 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
360 /* _UIB-CODE-BLOCK-END
*/
364 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-delete-record B-table-Win
365 PROCEDURE local-delete-record
:
366 /*------------------------------------------------------------------------------
367 Purpose
: Override standard ADM method
369 ------------------------------------------------------------------------------*/
370 DEF VAR yes-do-it
AS LOGI
NO-UNDO INITIAL Yes.
372 IF NOT AVAILABLE(FlowTaskType
) THEN RETURN.
374 MESSAGE "Are you sure you want to delete" SKIP
375 "the current Workflow Task record?"
376 VIEW-AS ALERT-BOX QUESTION BUTTONS OK-CANCEL
377 TITLE "Are you sure?" UPDATE yes-do-it .
379 IF yes-do-it
THEN DO TRANSACTION:
380 FIND CURRENT FlowTaskType
EXCLUSIVE-LOCK.
382 RUN dispatch
( 'open-query'
:U
).
386 /* _UIB-CODE-BLOCK-END
*/
390 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
392 /*------------------------------------------------------------------------------
393 Purpose
: Sends a requested
KEY value back to the calling
395 Parameters
: <see adm
/template
/sndkytop.i
>
396 ------------------------------------------------------------------------------*/
398 /* Define variables needed by this internal procedure.
*/
399 {src
/adm
/template
/sndkytop.i
}
401 /* Return the key value associated with each key case.
*/
402 {src
/adm
/template
/sndkycas.i
"FlowTaskType" "FlowTaskType" "FlowTaskType"}
404 /* Close the
CASE statement and end the procedure.
*/
405 {src
/adm
/template
/sndkyend.i
}
409 /* _UIB-CODE-BLOCK-END
*/
413 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
414 PROCEDURE send-records
:
415 /*------------------------------------------------------------------------------
416 Purpose
: Send record
ROWID's for all tables used by
418 Parameters
: see template
/snd-head.i
419 ------------------------------------------------------------------------------*/
421 /* Define variables needed by this internal procedure.
*/
422 {src
/adm
/template
/snd-head.i
}
424 /* For each requested table
, put it's
ROWID in the output list.
*/
425 {src
/adm
/template
/snd-list.i
"FlowTaskType"}
427 /* Deal with any unexpected table requests before closing.
*/
428 {src
/adm
/template
/snd-end.i
}
432 /* _UIB-CODE-BLOCK-END
*/
436 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
437 PROCEDURE state-changed
:
438 /* -----------------------------------------------------------
442 -------------------------------------------------------------*/
443 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
444 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
447 /* Object instance CASEs can go here to replace standard behavior
449 {src
/adm
/template
/bstates.i
}
453 /* _UIB-CODE-BLOCK-END
*/