1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS V-table-Win
8 /*------------------------------------------------------------------------
11 ------------------------------------------------------------------------*/
13 /* *************************** Definitions
************************** */
15 DEF VAR adding-new-record
AS LOGICAL INITIAL no
NO-UNDO.
17 /* _UIB-CODE-BLOCK-END
*/
21 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
23 /* ******************** Preprocessor Definitions
******************** */
25 &Scoped-define PROCEDURE-TYPE SmartViewer
27 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
29 /* Name of first Frame and
/or Browse and
/or first Query
*/
30 &Scoped-define FRAME-NAME F-Main
33 &Scoped-define EXTERNAL-TABLES LinkNode
34 &Scoped-define FIRST-EXTERNAL-TABLE LinkNode
37 /* Need to scope the external tables to this procedure
*/
38 DEFINE QUERY external_tables
FOR LinkNode.
39 /* Standard List Definitions
*/
40 &Scoped-Define ENABLED-FIELDS LinkNode.NodeType LinkNode.Description ~
41 LinkNode.File LinkNode.RunFile
42 &Scoped-define FIELD-PAIRS~
43 ~
{&FP1}Description ~{&FP2}Description ~{&FP3}~
44 ~
{&FP1}File ~{&FP2}File ~{&FP3}~
45 ~
{&FP1}RunFile ~{&FP2}RunFile ~{&FP3}
46 &Scoped-define ENABLED-TABLES LinkNode
47 &Scoped-define FIRST-ENABLED-TABLE LinkNode
48 &Scoped-Define ENABLED-OBJECTS RECT-21 cmb_runfile Btn_OK Btn_Cancel
49 &Scoped-Define DISPLAYED-FIELDS LinkNode.NodeType LinkNode.Description ~
50 LinkNode.File LinkNode.RunFile
51 &Scoped-Define DISPLAYED-OBJECTS cmb_runfile
53 /* Custom List Definitions
*/
54 /* ADM-CREATE-FIELDS
,ADM-ASSIGN-FIELDS
,List-3
,List-4
,List-5
,List-6
*/
56 /* _UIB-PREPROCESSOR-BLOCK-END
*/
61 /* *********************** Control Definitions
********************** */
64 /* Definitions of the field level widgets
*/
65 DEFINE BUTTON Btn_Cancel
AUTO-END-KEY DEFAULT
70 DEFINE BUTTON Btn_OK
AUTO-GO DEFAULT
75 DEFINE VARIABLE cmb_runfile
AS CHARACTER FORMAT "X(256)":U
76 VIEW-AS COMBO-BOX INNER-LINES 5
77 LIST-ITEMS "win/drl/w-defdrl.w","win/w-defsel.w","win/w-defwiz.w","win/w-defmnt.w","win/w-defmnu.w"
78 SIZE 40 BY 1.05 NO-UNDO.
80 DEFINE RECTANGLE RECT-21
81 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
85 /* ************************ Frame Definitions
*********************** */
88 LinkNode.NodeType
AT ROW 1.5 COL 10 NO-LABEL
90 LIST-ITEMS "DW","MW","SW","MN","MV"
93 LinkNode.Description
AT ROW 2.5 COL 10 NO-LABEL
97 LinkNode.File
AT ROW 4 COL 8 COLON-ALIGNED NO-LABEL FORMAT "X(50)"
101 cmb_runfile
AT ROW 5 COL 8.14 COLON-ALIGNED NO-LABEL
102 LinkNode.RunFile
AT ROW 5 COL 8.14 COLON-ALIGNED NO-LABEL FORMAT "X(50)"
106 Btn_OK
AT ROW 6.5 COL 39.57
107 Btn_Cancel
AT ROW 6.5 COL 43.86
108 RECT-21
AT ROW 1 COL 1
110 SIZE 8 BY 1 AT ROW 1.5 COL 2
113 SIZE 8 BY 1 AT ROW 2.5 COL 2
116 SIZE 5 BY 1 AT ROW 4 COL 2
118 "RunFile:" VIEW-AS TEXT
119 SIZE 7 BY 1 AT ROW 5.15 COL 2
121 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
122 SIDE-LABELS NO-UNDERLINE THREE-D
123 AT COL 1 ROW 1 SCROLLABLE
125 DEFAULT-BUTTON Btn_OK
CANCEL-BUTTON Btn_Cancel.
128 /* *********************** Procedure Settings
************************ */
130 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
131 /* Settings for
THIS-PROCEDURE
133 External Tables
: TTPL.LinkNode
134 Allow
: Basic
,DB-Fields
136 Add Fields to
: EXTERNAL-TABLES
137 Other Settings
: PERSISTENT-ONLY
COMPILE
140 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
141 /* then cleanup and return.
*/
142 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
143 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
144 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
148 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
150 /* ************************* Create Window
************************** */
152 &ANALYZE-SUSPEND _CREATE-WINDOW
153 /* DESIGN Window definition
(used by the UIB
)
154 CREATE WINDOW V-table-Win
ASSIGN
157 /* END WINDOW DEFINITION
*/
162 /* *************** Runtime Attributes and UIB Settings
************** */
164 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
165 /* SETTINGS
FOR WINDOW V-table-Win
166 VISIBLE,,RUN-PERSISTENT
*/
167 /* SETTINGS
FOR FRAME F-Main
168 NOT-VISIBLE Size-to-Fit
*/
170 FRAME F-Main
:SCROLLABLE = FALSE
171 FRAME F-Main
:HIDDEN = TRUE.
173 /* SETTINGS
FOR FILL-IN LinkNode.Description
IN FRAME F-Main
175 /* SETTINGS
FOR FILL-IN LinkNode.File
IN FRAME F-Main
176 EXP-LABEL EXP-FORMAT
*/
177 /* SETTINGS
FOR COMBO-BOX LinkNode.NodeType
IN FRAME F-Main
179 /* SETTINGS
FOR FILL-IN LinkNode.RunFile
IN FRAME F-Main
180 EXP-LABEL EXP-FORMAT
*/
181 /* _RUN-TIME-ATTRIBUTES-END
*/
185 /* Setting information for Queries and Browse Widgets fields
*/
187 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
188 /* Query rebuild information for
FRAME F-Main
191 */ /* FRAME F-Main
*/
197 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
198 /* ************************* Included-Libraries
*********************** */
200 {src
/adm
/method
/viewer.i
}
202 /* _UIB-CODE-BLOCK-END
*/
208 /* ************************ Control Triggers
************************ */
210 &Scoped-define SELF-NAME Btn_Cancel
211 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_Cancel V-table-Win
212 ON CHOOSE OF Btn_Cancel
IN FRAME F-Main
/* Cancel
*/
214 IF adding-new-record
THEN DO TRANSACTION:
215 FIND CURRENT LinkNode
EXCLUSIVE-LOCK.
219 RUN dispatch
( 'exit'
:U
).
222 /* _UIB-CODE-BLOCK-END
*/
226 &Scoped-define SELF-NAME Btn_OK
227 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK V-table-Win
228 ON CHOOSE OF Btn_OK
IN FRAME F-Main
/* OK */
230 RUN dispatch
( 'update-record'
:U
).
231 IF adding-new-record
THEN RUN dispatch
( 'open-query
,Record-Source'
:U
).
232 RUN dispatch
( 'exit'
:U
).
235 /* _UIB-CODE-BLOCK-END
*/
239 &Scoped-define SELF-NAME cmb_runfile
240 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_runfile V-table-Win
241 ON VALUE-CHANGED
OF cmb_runfile
IN FRAME F-Main
243 ASSIGN LinkNode.RunFile
:SCREEN-VALUE = SELF:SCREEN-VALUE.
246 /* _UIB-CODE-BLOCK-END
*/
252 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
255 /* *************************** Main Block
*************************** */
257 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
258 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
261 /************************ INTERNAL PROCEDURES
********************/
263 /* _UIB-CODE-BLOCK-END
*/
267 /* ********************** Internal Procedures
*********************** */
269 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
270 PROCEDURE adm-row-available
:
271 /*------------------------------------------------------------------------------
272 Purpose
: Dispatched to this procedure when the Record-
273 Source has a new row available. This procedure
274 tries to get the new row
(or foriegn keys
) from
275 the Record-Source and process it.
277 ------------------------------------------------------------------------------*/
279 /* Define variables needed by this internal procedure.
*/
280 {src
/adm
/template
/row-head.i
}
282 /* Create a list of all the tables that we need to get.
*/
283 {src
/adm
/template
/row-list.i
"LinkNode"}
285 /* Get the record
ROWID's from the RECORD-SOURCE.
*/
286 {src
/adm
/template
/row-get.i
}
288 /* FIND each record specified by the RECORD-SOURCE.
*/
289 {src
/adm
/template
/row-find.i
"LinkNode"}
291 /* Process the newly available records
(i.e. display fields
,
292 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
293 {src
/adm
/template
/row-end.i
}
297 /* _UIB-CODE-BLOCK-END
*/
301 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
302 PROCEDURE disable_UI
:
303 /*------------------------------------------------------------------------------
304 Purpose
: DISABLE the User Interface
306 Notes
: Here we clean-up the user-interface by deleting
307 dynamic widgets we have created and
/or hide
308 frames. This procedure is usually called when
309 we are ready to
"clean-up" after running.
310 ------------------------------------------------------------------------------*/
311 /* Hide all frames.
*/
313 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
316 /* _UIB-CODE-BLOCK-END
*/
320 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-add-record V-table-Win
321 PROCEDURE local-add-record
:
322 /*------------------------------------------------------------------------------
323 Purpose
: Override standard ADM method
325 ------------------------------------------------------------------------------*/
326 adding-new-record
= yes.
328 RUN dispatch
( 'display-fields'
:U
).
329 RUN dispatch
( 'enable-fields'
:U
).
333 /* _UIB-CODE-BLOCK-END
*/
337 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-enable-fields V-table-Win
338 PROCEDURE local-enable-fields
:
339 /*------------------------------------------------------------------------------
340 Purpose
: Override standard ADM method
342 ------------------------------------------------------------------------------*/
344 /* Code placed here will execute PRIOR to standard behavior.
*/
346 /* Dispatch standard ADM method.
*/
347 RUN dispatch
IN THIS-PROCEDURE ( INPUT 'enable-fields'
:U
) .
349 /* Code placed here will execute AFTER standard behavior.
*/
350 IF cmb_runfile
:MOVE-TO-BOTTOM() IN FRAME {&FRAME-NAME} THEN.
351 IF LinkNode.RunFile
:MOVE-TO-TOP() IN FRAME {&FRAME-NAME} THEN.
355 /* _UIB-CODE-BLOCK-END
*/
359 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
360 PROCEDURE send-records
:
361 /*------------------------------------------------------------------------------
362 Purpose
: Send record
ROWID's for all tables used by
364 Parameters
: see template
/snd-head.i
365 ------------------------------------------------------------------------------*/
367 /* Define variables needed by this internal procedure.
*/
368 {src
/adm
/template
/snd-head.i
}
370 /* For each requested table
, put it's
ROWID in the output list.
*/
371 {src
/adm
/template
/snd-list.i
"LinkNode"}
373 /* Deal with any unexpected table requests before closing.
*/
374 {src
/adm
/template
/snd-end.i
}
378 /* _UIB-CODE-BLOCK-END
*/
382 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
383 PROCEDURE state-changed
:
384 /* -----------------------------------------------------------
388 -------------------------------------------------------------*/
389 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
390 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
393 /* Object instance CASEs can go here to replace standard behavior
395 {src
/adm
/template
/vstates.i
}
399 /* _UIB-CODE-BLOCK-END
*/