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 /*------------------------------------------------------------------------
10 File
: compliance
/v-building-system.w
12 Description
: Viewer for maintaining
/adding building systems
20 ------------------------------------------------------------------------*/
24 /* *************************** Definitions
************************** */
26 {inc
/topic
/tpbldsys.i
}
28 DEF VAR mode
AS CHAR NO-UNDO.
30 /* _UIB-CODE-BLOCK-END
*/
34 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
36 /* ******************** Preprocessor Definitions
******************** */
38 &Scoped-define PROCEDURE-TYPE SmartViewer
40 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
42 /* Name of first Frame and
/or Browse and
/or first Query
*/
43 &Scoped-define FRAME-NAME F-Main
46 &Scoped-define EXTERNAL-TABLES BuildingSystem
47 &Scoped-define FIRST-EXTERNAL-TABLE BuildingSystem
50 /* Need to scope the external tables to this procedure
*/
51 DEFINE QUERY external_tables
FOR BuildingSystem.
52 /* Standard List Definitions
*/
53 &Scoped-Define ENABLED-FIELDS BuildingSystem.PropertyCode ~
54 BuildingSystem.IQPCertificate
55 &Scoped-define FIELD-PAIRS~
56 ~
{&FP1}PropertyCode ~{&FP2}PropertyCode ~{&FP3}
57 &Scoped-define ENABLED-TABLES BuildingSystem
58 &Scoped-define FIRST-ENABLED-TABLE BuildingSystem
59 &Scoped-Define ENABLED-OBJECTS RECT-25 cmb_BuildingSystemType ~
60 cmb_InspectorIQP cmb_InspectorOwner
61 &Scoped-Define DISPLAYED-FIELDS BuildingSystem.PropertyCode ~
62 BuildingSystem.IQPCertificate
63 &Scoped-Define DISPLAYED-OBJECTS cmb_BuildingSystemType cmb_InspectorIQP ~
66 /* Custom List Definitions
*/
67 /* ADM-CREATE-FIELDS
,ADM-ASSIGN-FIELDS
,List-3
,List-4
,List-5
,List-6
*/
69 /* _UIB-PREPROCESSOR-BLOCK-END
*/
73 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" V-table-Win _INLINE
74 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
80 PropertyCode||y|TTPL.BuildingSystem.PropertyCode
81 BuildingSystemType||y|TTPL.BuildingSystem.BuildingSystemType
84 **************************
85 * Set attributes related to FOREIGN
KEYS
87 RUN set-attribute-list
(
89 Keys-Supplied
= "PropertyCode,BuildingSystemType"'
:U
).
90 /**************************
92 /* _UIB-CODE-BLOCK-END
*/
96 /* *********************** Control Definitions
********************** */
99 /* Definitions of the field level widgets
*/
100 DEFINE VARIABLE cmb_BuildingSystemType
AS CHARACTER FORMAT "X(256)":U
102 VIEW-AS COMBO-BOX INNER-LINES 5
104 SIZE 47.43 BY 1 NO-UNDO.
106 DEFINE VARIABLE cmb_InspectorIQP
AS CHARACTER FORMAT "X(256)":U
107 LABEL "IQP inspector"
108 VIEW-AS COMBO-BOX INNER-LINES 5
110 SIZE 47.43 BY 1 NO-UNDO.
112 DEFINE VARIABLE cmb_InspectorOwner
AS CHARACTER FORMAT "X(256)":U
113 LABEL "Owner inspector"
114 VIEW-AS COMBO-BOX INNER-LINES 5
116 SIZE 47.43 BY 1 NO-UNDO.
118 DEFINE RECTANGLE RECT-25
119 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
123 /* ************************ Frame Definitions
*********************** */
126 BuildingSystem.PropertyCode
AT ROW 1.2 COL 6.43 COLON-ALIGNED
130 cmb_BuildingSystemType
AT ROW 3 COL 12.72 COLON-ALIGNED
131 cmb_InspectorIQP
AT ROW 5.4 COL 12.72 COLON-ALIGNED
132 cmb_InspectorOwner
AT ROW 6.6 COL 12.72 COLON-ALIGNED
133 BuildingSystem.IQPCertificate
AT ROW 8.2 COL 14.72
136 RECT-25
AT ROW 1 COL 1
137 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
138 SIDE-LABELS NO-UNDERLINE THREE-D
139 AT COL 1 ROW 1 SCROLLABLE
143 /* *********************** Procedure Settings
************************ */
145 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
146 /* Settings for
THIS-PROCEDURE
148 External Tables
: TTPL.BuildingSystem
149 Allow
: Basic
,DB-Fields
151 Add Fields to
: EXTERNAL-TABLES
152 Other Settings
: PERSISTENT-ONLY
COMPILE
155 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
156 /* then cleanup and return.
*/
157 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
158 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
159 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
163 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
165 /* ************************* Create Window
************************** */
167 &ANALYZE-SUSPEND _CREATE-WINDOW
168 /* DESIGN Window definition
(used by the UIB
)
169 CREATE WINDOW V-table-Win
ASSIGN
172 /* END WINDOW DEFINITION
*/
177 /* *************** Runtime Attributes and UIB Settings
************** */
179 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
180 /* SETTINGS
FOR WINDOW V-table-Win
181 VISIBLE,,RUN-PERSISTENT
*/
182 /* SETTINGS
FOR FRAME F-Main
183 NOT-VISIBLE Size-to-Fit
*/
185 FRAME F-Main
:SCROLLABLE = FALSE
186 FRAME F-Main
:HIDDEN = TRUE.
188 /* SETTINGS
FOR FILL-IN BuildingSystem.PropertyCode
IN FRAME F-Main
190 /* _RUN-TIME-ATTRIBUTES-END
*/
194 /* Setting information for Queries and Browse Widgets fields
*/
196 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
197 /* Query rebuild information for
FRAME F-Main
200 */ /* FRAME F-Main
*/
206 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
207 /* ************************* Included-Libraries
*********************** */
209 {src
/adm
/method
/viewer.i
}
210 {inc
/method
/m-mntvwr.i
}
212 /* _UIB-CODE-BLOCK-END
*/
218 /* ************************ Control Triggers
************************ */
220 &Scoped-define SELF-NAME cmb_BuildingSystemType
221 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_BuildingSystemType V-table-Win
222 ON U1
OF cmb_BuildingSystemType
IN FRAME F-Main
/* System Type
*/
224 {inc
/selcmb
/scbldsys1.i
"BuildingSystem" "BuildingSystemType"}
227 /* _UIB-CODE-BLOCK-END
*/
231 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_BuildingSystemType V-table-Win
232 ON U2
OF cmb_BuildingSystemType
IN FRAME F-Main
/* System Type
*/
234 {inc
/selcmb
/scbldsys2.i
"BuildingSystem" "BuildingSystemType"}
237 /* _UIB-CODE-BLOCK-END
*/
241 &Scoped-define SELF-NAME cmb_InspectorIQP
242 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_InspectorIQP V-table-Win
243 ON U1
OF cmb_InspectorIQP
IN FRAME F-Main
/* IQP inspector
*/
245 {inc
/selcmb
/scinsp1.i
"BuildingSystem" "InspectorIQP"}
248 /* _UIB-CODE-BLOCK-END
*/
252 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_InspectorIQP V-table-Win
253 ON U2
OF cmb_InspectorIQP
IN FRAME F-Main
/* IQP inspector
*/
255 {inc
/selcmb
/scinsp2.i
"BuildingSystem" "InspectorIQP"}
258 /* _UIB-CODE-BLOCK-END
*/
262 &Scoped-define SELF-NAME cmb_InspectorOwner
263 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_InspectorOwner V-table-Win
264 ON U1
OF cmb_InspectorOwner
IN FRAME F-Main
/* Owner inspector
*/
266 {inc
/selcmb
/scinsp1.i
"BuildingSystem" "InspectorOwner"}
269 /* _UIB-CODE-BLOCK-END
*/
273 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_InspectorOwner V-table-Win
274 ON U2
OF cmb_InspectorOwner
IN FRAME F-Main
/* Owner inspector
*/
276 {inc
/selcmb
/scinsp2.i
"BuildingSystem" "InspectorOwner"}
279 /* _UIB-CODE-BLOCK-END
*/
285 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
288 /* *************************** Main Block
*************************** */
290 /* _UIB-CODE-BLOCK-END
*/
294 /* ********************** Internal Procedures
*********************** */
296 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-find-using-key V-table-Win adm/support/_key-fnd.p
297 PROCEDURE adm-find-using-key
:
298 /*------------------------------------------------------------------------------
299 Purpose
: Finds the current record using the contents of
300 the 'Key-Name' and 'Key-Value' attributes.
302 ------------------------------------------------------------------------------*/
304 /* No Foreign keys are accepted by this SmartObject.
*/
308 /* _UIB-CODE-BLOCK-END
*/
312 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
313 PROCEDURE adm-row-available
:
314 /*------------------------------------------------------------------------------
315 Purpose
: Dispatched to this procedure when the Record-
316 Source has a new row available. This procedure
317 tries to get the new row
(or foriegn keys
) from
318 the Record-Source and process it.
320 ------------------------------------------------------------------------------*/
322 /* Define variables needed by this internal procedure.
*/
323 {src
/adm
/template
/row-head.i
}
325 /* Create a list of all the tables that we need to get.
*/
326 {src
/adm
/template
/row-list.i
"BuildingSystem"}
328 /* Get the record
ROWID's from the RECORD-SOURCE.
*/
329 {src
/adm
/template
/row-get.i
}
331 /* FIND each record specified by the RECORD-SOURCE.
*/
332 {src
/adm
/template
/row-find.i
"BuildingSystem"}
334 /* Process the newly available records
(i.e. display fields
,
335 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
336 {src
/adm
/template
/row-end.i
}
340 /* _UIB-CODE-BLOCK-END
*/
344 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE cancel-changes V-table-Win
345 PROCEDURE cancel-changes
:
346 /*------------------------------------------------------------------------------
348 ------------------------------------------------------------------------------*/
350 IF mode
= "Add" THEN RUN delete-new-record.
ELSE RUN check-modified
( "CLEAR" ).
351 RUN dispatch
( 'exit'
:U
).
355 /* _UIB-CODE-BLOCK-END
*/
359 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE confirm-changes V-table-Win
360 PROCEDURE confirm-changes
:
361 /*------------------------------------------------------------------------------
363 ------------------------------------------------------------------------------*/
366 IF RETURN-VALUE = "FAIL" THEN RETURN.
368 RUN dispatch
( 'update-record'
:U
).
369 IF mode
= "Add":U
THEN RUN notify
( 'open-query
,record-source'
:U
).
370 RUN dispatch
( 'exit'
:U
).
374 /* _UIB-CODE-BLOCK-END
*/
378 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE delete-new-record V-table-Win
379 PROCEDURE delete-new-record
:
380 /*------------------------------------------------------------------------------
382 ------------------------------------------------------------------------------*/
384 FIND CURRENT BuildingSystem
EXCLUSIVE-LOCK NO-ERROR.
385 IF AVAILABLE BuildingSystem
THEN DELETE BuildingSystem.
389 /* _UIB-CODE-BLOCK-END
*/
393 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
394 PROCEDURE disable_UI
:
395 /*------------------------------------------------------------------------------
396 Purpose
: DISABLE the User Interface
398 Notes
: Here we clean-up the user-interface by deleting
399 dynamic widgets we have created and
/or hide
400 frames. This procedure is usually called when
401 we are ready to
"clean-up" after running.
402 ------------------------------------------------------------------------------*/
403 /* Hide all frames.
*/
405 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
408 /* _UIB-CODE-BLOCK-END
*/
412 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
413 PROCEDURE inst-initialize
:
414 /*------------------------------------------------------------------------------
416 ------------------------------------------------------------------------------*/
418 IF mode
= "Add" THEN DO:
420 RUN dispatch
( 'add-record'
:U
).
422 ELSE IF mode
= "View" THEN DO:
423 RUN dispatch
( 'disable-fields'
:U
).
426 RUN dispatch
( 'enable-fields'
:U
).
430 /* _UIB-CODE-BLOCK-END
*/
434 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE override-add-record V-table-Win
435 PROCEDURE override-add-record
:
436 /*------------------------------------------------------------------------------
438 ------------------------------------------------------------------------------*/
440 CREATE BuildingSystem.
441 BuildingSystem.PropertyCode
= INT( find-parent-key
("PropertyCode") ).
443 RUN dispatch
( 'display-fields'
:U
).
444 RUN dispatch
( 'enable-fields'
:U
).
446 CURRENT-WINDOW:TITLE = "Adding a new Building System".
450 /* _UIB-CODE-BLOCK-END
*/
454 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
455 PROCEDURE pre-destroy
:
456 /*------------------------------------------------------------------------------
460 ------------------------------------------------------------------------------*/
462 IF LAST-EVENT:FUNCTION = "WINDOW-CLOSE" THEN RUN cancel-changes.
466 /* _UIB-CODE-BLOCK-END
*/
470 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key V-table-Win adm/support/_key-snd.p
472 /*------------------------------------------------------------------------------
473 Purpose
: Sends a requested
KEY value back to the calling
475 Parameters
: <see adm
/template
/sndkytop.i
>
476 ------------------------------------------------------------------------------*/
478 /* Define variables needed by this internal procedure.
*/
479 {src
/adm
/template
/sndkytop.i
}
481 /* Return the key value associated with each key case.
*/
482 {src
/adm
/template
/sndkycas.i
"PropertyCode" "BuildingSystem" "PropertyCode"}
483 {src
/adm
/template
/sndkycas.i
"BuildingSystemType" "BuildingSystem" "BuildingSystemType"}
485 /* Close the
CASE statement and end the procedure.
*/
486 {src
/adm
/template
/sndkyend.i
}
490 /* _UIB-CODE-BLOCK-END
*/
494 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
495 PROCEDURE send-records
:
496 /*------------------------------------------------------------------------------
497 Purpose
: Send record
ROWID's for all tables used by
499 Parameters
: see template
/snd-head.i
500 ------------------------------------------------------------------------------*/
502 /* Define variables needed by this internal procedure.
*/
503 {src
/adm
/template
/snd-head.i
}
505 /* For each requested table
, put it's
ROWID in the output list.
*/
506 {src
/adm
/template
/snd-list.i
"BuildingSystem"}
508 /* Deal with any unexpected table requests before closing.
*/
509 {src
/adm
/template
/snd-end.i
}
513 /* _UIB-CODE-BLOCK-END
*/
517 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
518 PROCEDURE state-changed
:
519 /* -----------------------------------------------------------
523 -------------------------------------------------------------*/
524 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
525 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
528 /* Object instance CASEs can go here to replace standard behavior
530 {src
/adm
/template
/vstates.i
}
534 /* _UIB-CODE-BLOCK-END
*/
538 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-mode V-table-Win
540 /*------------------------------------------------------------------------------
542 ------------------------------------------------------------------------------*/
543 DEF INPUT PARAMETER new-mode
AS CHAR NO-UNDO.
549 /* _UIB-CODE-BLOCK-END
*/
553 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE verify-record V-table-Win
554 PROCEDURE verify-record
:
555 /*------------------------------------------------------------------------------
559 ------------------------------------------------------------------------------*/
561 DO WITH FRAME {&FRAME-NAME}:
567 /* _UIB-CODE-BLOCK-END
*/