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 ------------------------------------------------------------------------*/
16 /* *************************** Definitions
************************** */
19 DEF VAR insp-iqp
AS CHAR NO-UNDO FORMAT "X(50)" LABEL "IQP Inspector".
20 DEF VAR insp-owner
AS CHAR NO-UNDO FORMAT "X(50)" LABEL "Owner Inspector".
22 DEF BUFFER Insp
FOR Inspector.
23 DEF BUFFER Pers
FOR Person.
25 /* _UIB-CODE-BLOCK-END
*/
29 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
31 /* ******************** Preprocessor Definitions
******************** */
33 &Scoped-define PROCEDURE-TYPE SmartBrowser
35 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
37 /* Name of first Frame and
/or Browse and
/or first Query
*/
38 &Scoped-define FRAME-NAME F-Main
39 &Scoped-define BROWSE-NAME br_table
41 /* Internal Tables
(found by Frame
, Query
& Browse Queries) */
42 &Scoped-define INTERNAL-TABLES BuildingSystem
44 /* Define KEY-PHRASE in case it is used by any query.
*/
45 &Scoped-define KEY-PHRASE TRUE
47 /* Definitions for
BROWSE br_table
*/
48 &Scoped-define FIELDS-IN-QUERY-br_table BuildingSystem.PropertyCode ~
49 BuildingSystem.BuildingSystemType BuildingSystem.InspectorIQP ~
50 BuildingSystem.InspectorOwner BuildingSystem.IQPCertificate ~
51 get-inspector-name
(BuildingSystem.InspectorIQP
) @ insp-iqp ~
52 get-inspector-name
(BuildingSystem.InspectorOwner
) @ insp-owner
53 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table
54 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table
55 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH BuildingSystem WHERE ~{&KEY-PHRASE} NO-LOCK ~
57 &Scoped-define TABLES-IN-QUERY-br_table BuildingSystem
58 &Scoped-define FIRST-TABLE-IN-QUERY-br_table BuildingSystem
61 /* Definitions for
FRAME F-Main
*/
63 /* Standard List Definitions
*/
64 &Scoped-Define ENABLED-OBJECTS br_table
66 /* Custom List Definitions
*/
67 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
69 /* _UIB-PREPROCESSOR-BLOCK-END
*/
73 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
74 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
80 PropertyCode|y|y|TTPL.BuildingSystem.PropertyCode
81 InspectorIQP|y|y|TTPL.BuildingSystem.InspectorIQP
82 InspectorOwner|y|y|TTPL.BuildingSystem.InspectorOwner
85 **************************
86 * Set attributes related to FOREIGN
KEYS
88 RUN set-attribute-list
(
89 'Keys-Accepted
= "PropertyCode,InspectorIQP,InspectorOwner",
90 Keys-Supplied
= "PropertyCode,InspectorIQP,InspectorOwner"'
:U
).
92 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
93 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
94 /**************************
96 /* _UIB-CODE-BLOCK-END
*/
99 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
100 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
108 ************************
109 * Set attributes related to SORTBY-OPTIONS
*/
110 RUN set-attribute-list
(
111 'SortBy-Options
= ""'
:U
).
112 /************************
115 </FILTER-ATTRIBUTES
> */
117 /* _UIB-CODE-BLOCK-END
*/
120 /* ************************ Function Prototypes
********************** */
122 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD get-inspector-name B-table-Win
123 FUNCTION get-inspector-name
RETURNS CHARACTER
124 ( INPUT inspector-code
AS INT ) FORWARD.
126 /* _UIB-CODE-BLOCK-END
*/
130 /* *********************** Control Definitions
********************** */
133 /* Definitions of the field level widgets
*/
134 /* Query definitions
*/
136 DEFINE QUERY br_table
FOR
137 BuildingSystem
SCROLLING.
140 /* Browse definitions
*/
141 DEFINE BROWSE br_table
142 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
143 QUERY br_table
NO-LOCK DISPLAY
144 BuildingSystem.PropertyCode
145 BuildingSystem.BuildingSystemType
146 BuildingSystem.InspectorIQP
COLUMN-LABEL "Insp.IQP"
147 BuildingSystem.InspectorOwner
COLUMN-LABEL "Insp.Owner"
148 BuildingSystem.IQPCertificate
COLUMN-LABEL "IQPCert"
149 get-inspector-name
(BuildingSystem.InspectorIQP
) @ insp-iqp
150 get-inspector-name
(BuildingSystem.InspectorOwner
) @ insp-owner
151 /* _UIB-CODE-BLOCK-END
*/
153 WITH NO-ASSIGN SEPARATORS SIZE 94.86 BY 14.2
157 /* ************************ Frame Definitions
*********************** */
160 br_table
AT ROW 1 COL 1
161 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
162 SIDE-LABELS NO-UNDERLINE THREE-D
163 AT COL 1 ROW 1 SCROLLABLE
164 BGCOLOR 16 FGCOLOR 0 FONT 10.
167 /* *********************** Procedure Settings
************************ */
169 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
170 /* Settings for
THIS-PROCEDURE
174 Add Fields to
: EXTERNAL-TABLES
175 Other Settings
: PERSISTENT-ONLY
COMPILE
178 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
179 /* then cleanup and return.
*/
180 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
181 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
182 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
186 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
188 /* ************************* Create Window
************************** */
190 &ANALYZE-SUSPEND _CREATE-WINDOW
191 /* DESIGN Window definition
(used by the UIB
)
192 CREATE WINDOW B-table-Win
ASSIGN
195 /* END WINDOW DEFINITION
*/
200 /* *************** Runtime Attributes and UIB Settings
************** */
202 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
203 /* SETTINGS
FOR WINDOW B-table-Win
204 NOT-VISIBLE
,,RUN-PERSISTENT
*/
205 /* SETTINGS
FOR FRAME F-Main
206 NOT-VISIBLE Size-to-Fit
*/
207 /* BROWSE-TAB br_table
1 F-Main
*/
209 FRAME F-Main
:SCROLLABLE = FALSE
210 FRAME F-Main
:HIDDEN = TRUE.
212 /* _RUN-TIME-ATTRIBUTES-END
*/
216 /* Setting information for Queries and Browse Widgets fields
*/
218 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
219 /* Query rebuild information for
BROWSE br_table
220 _TblList
= "TTPL.BuildingSystem"
221 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
223 _FldNameList
[1] = TTPL.BuildingSystem.PropertyCode
224 _FldNameList
[2] = TTPL.BuildingSystem.BuildingSystemType
225 _FldNameList
[3] > TTPL.BuildingSystem.InspectorIQP
226 "BuildingSystem.InspectorIQP" "Insp.IQP" ?
"integer" ? ? ? ? ? ? no ?
227 _FldNameList
[4] > TTPL.BuildingSystem.InspectorOwner
228 "BuildingSystem.InspectorOwner" "Insp.Owner" ?
"integer" ? ? ? ? ? ? no ?
229 _FldNameList
[5] > TTPL.BuildingSystem.IQPCertificate
230 "BuildingSystem.IQPCertificate" "IQPCert" ?
"logical" ? ? ? ? ? ? no ?
231 _FldNameList
[6] > "_<CALC>"
232 "get-inspector-name(BuildingSystem.InspectorIQP) @ insp-iqp" ? ? ? ? ? ? ? ? ? no ?
233 _FldNameList
[7] > "_<CALC>"
234 "get-inspector-name(BuildingSystem.InspectorOwner) @ insp-owner" ? ? ? ? ? ? ? ? ? no ?
236 */ /* BROWSE br_table
*/
239 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
240 /* Query rebuild information for
FRAME F-Main
243 */ /* FRAME F-Main
*/
249 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
250 /* ************************* Included-Libraries
*********************** */
252 {src
/adm
/method
/browser.i
}
253 {inc
/method
/m-drlvwr.i
}
255 /* _UIB-CODE-BLOCK-END
*/
261 /* ************************ Control Triggers
************************ */
263 &Scoped-define BROWSE-NAME br_table
264 &Scoped-define SELF-NAME br_table
265 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
266 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
268 /* This code displays initial values for newly added or copied rows.
*/
269 {src
/adm
/template
/brsentry.i
}
272 /* _UIB-CODE-BLOCK-END
*/
276 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
277 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
279 /* Do not disable this code or no updates will take place except
280 by pressing the Save button on an Update SmartPanel.
*/
281 {src
/adm
/template
/brsleave.i
}
284 /* _UIB-CODE-BLOCK-END
*/
288 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
289 ON VALUE-CHANGED
OF br_table
IN FRAME F-Main
291 /* This ADM trigger code must be preserved in order to notify other
292 objects when the browser's current row changes.
*/
293 {src
/adm
/template
/brschnge.i
}
296 /* _UIB-CODE-BLOCK-END
*/
302 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
305 /* *************************** Main Block
*************************** */
307 /* _UIB-CODE-BLOCK-END
*/
311 /* ********************** Internal Procedures
*********************** */
313 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-open-query-cases B-table-Win adm/support/_adm-opn.p
314 PROCEDURE adm-open-query-cases
:
315 /*------------------------------------------------------------------------------
316 Purpose
: Opens different cases of the query based on attributes
317 such as the 'Key-Name'
, or 'SortBy-Case'
319 ------------------------------------------------------------------------------*/
320 DEF VAR key-value
AS CHAR NO-UNDO.
322 /* Look up the current key-value.
*/
323 RUN get-attribute
('Key-Value'
:U
).
324 key-value
= RETURN-VALUE.
326 /* Find the current record using the current Key-Name.
*/
327 RUN get-attribute
('Key-Name'
:U
).
329 WHEN 'PropertyCode'
:U
THEN DO:
330 &Scope KEY-PHRASE BuildingSystem.PropertyCode eq INTEGER(key-value)
331 {&OPEN-QUERY-{&BROWSE-NAME}}
332 END.
/* PropertyCode
*/
333 WHEN 'InspectorIQP'
:U
THEN DO:
334 &Scope KEY-PHRASE BuildingSystem.InspectorIQP eq INTEGER(key-value)
335 {&OPEN-QUERY-{&BROWSE-NAME}}
336 END.
/* InspectorIQP
*/
337 WHEN 'InspectorOwner'
:U
THEN DO:
338 &Scope KEY-PHRASE BuildingSystem.InspectorOwner eq INTEGER(key-value)
339 {&OPEN-QUERY-{&BROWSE-NAME}}
340 END.
/* InspectorOwner
*/
342 &Scope KEY-PHRASE TRUE
343 {&OPEN-QUERY-{&BROWSE-NAME}}
344 END.
/* OTHERWISE...
*/
349 /* _UIB-CODE-BLOCK-END
*/
353 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
354 PROCEDURE adm-row-available
:
355 /*------------------------------------------------------------------------------
356 Purpose
: Dispatched to this procedure when the Record-
357 Source has a new row available. This procedure
358 tries to get the new row
(or foriegn keys
) from
359 the Record-Source and process it.
361 ------------------------------------------------------------------------------*/
363 /* Define variables needed by this internal procedure.
*/
364 {src
/adm
/template
/row-head.i
}
366 /* Process the newly available records
(i.e. display fields
,
367 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
368 {src
/adm
/template
/row-end.i
}
372 /* _UIB-CODE-BLOCK-END
*/
376 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
377 PROCEDURE disable_UI
:
378 /*------------------------------------------------------------------------------
379 Purpose
: DISABLE the User Interface
381 Notes
: Here we clean-up the user-interface by deleting
382 dynamic widgets we have created and
/or hide
383 frames. This procedure is usually called when
384 we are ready to
"clean-up" after running.
385 ------------------------------------------------------------------------------*/
386 /* Hide all frames.
*/
388 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
391 /* _UIB-CODE-BLOCK-END
*/
395 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-delete-record B-table-Win
396 PROCEDURE local-delete-record
:
397 /*------------------------------------------------------------------------------
398 Purpose
: Override standard ADM method
400 ------------------------------------------------------------------------------*/
401 DEF VAR do-it
AS LOGI
NO-UNDO INITIAL No.
403 IF NOT AVAILABLE(BuildingSystem
) THEN RETURN.
405 /* Code placed here will execute PRIOR to standard behavior.
*/
406 MESSAGE "Are you sure you want to delete the current record?"
407 VIEW-AS ALERT-BOX QUESTION BUTTONS YES-NO
408 TITLE "Confirm Deletion"
412 FIND CURRENT BuildingSystem
EXCLUSIVE-LOCK.
413 DELETE BuildingSystem.
414 RUN dispatch
( 'open-query'
:U
).
419 /* _UIB-CODE-BLOCK-END
*/
423 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
425 /*------------------------------------------------------------------------------
426 Purpose
: Sends a requested
KEY value back to the calling
428 Parameters
: <see adm
/template
/sndkytop.i
>
429 ------------------------------------------------------------------------------*/
431 /* Define variables needed by this internal procedure.
*/
432 {src
/adm
/template
/sndkytop.i
}
434 /* Return the key value associated with each key case.
*/
435 {src
/adm
/template
/sndkycas.i
"PropertyCode" "BuildingSystem" "PropertyCode"}
436 {src
/adm
/template
/sndkycas.i
"InspectorIQP" "BuildingSystem" "InspectorIQP"}
437 {src
/adm
/template
/sndkycas.i
"InspectorOwner" "BuildingSystem" "InspectorOwner"}
439 /* Close the
CASE statement and end the procedure.
*/
440 {src
/adm
/template
/sndkyend.i
}
444 /* _UIB-CODE-BLOCK-END
*/
448 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
449 PROCEDURE send-records
:
450 /*------------------------------------------------------------------------------
451 Purpose
: Send record
ROWID's for all tables used by
453 Parameters
: see template
/snd-head.i
454 ------------------------------------------------------------------------------*/
456 /* Define variables needed by this internal procedure.
*/
457 {src
/adm
/template
/snd-head.i
}
459 /* For each requested table
, put it's
ROWID in the output list.
*/
460 {src
/adm
/template
/snd-list.i
"BuildingSystem"}
462 /* Deal with any unexpected table requests before closing.
*/
463 {src
/adm
/template
/snd-end.i
}
467 /* _UIB-CODE-BLOCK-END
*/
471 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
472 PROCEDURE state-changed
:
473 /* -----------------------------------------------------------
477 -------------------------------------------------------------*/
478 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
479 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
482 /* Object instance CASEs can go here to replace standard behavior
484 {src
/adm
/template
/bstates.i
}
488 /* _UIB-CODE-BLOCK-END
*/
492 /* ************************ Function Implementations
***************** */
494 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION get-inspector-name B-table-Win
495 FUNCTION get-inspector-name
RETURNS CHARACTER
496 ( INPUT inspector-code
AS INT ) :
497 /*------------------------------------------------------------------------------
498 Purpose
: Return the name of the inspector
500 ------------------------------------------------------------------------------*/
502 FIND Insp
WHERE Insp.InspectorCode
= inspector-code
NO-LOCK NO-ERROR.
503 IF AVAILABLE(Insp
) THEN FIND Pers
OF Insp
NO-LOCK NO-ERROR.
504 IF AVAILABLE(Pers
) THEN
505 RETURN Pers.FirstName
+ " " + Pers.LastName
+ ", " + Pers.Company .
507 IF AVAILABLE(Insp
) THEN
508 RETURN "No contact assigned to inspector".
510 RETURN "Inspector " + STRING(inspector-code
) + " not on file".
514 /* _UIB-CODE-BLOCK-END
*/