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 ReplLoadRule
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 ReplLoadRule.SourceSystem ~
62 ReplLoadRule.TableToLoad ReplLoadRule.Activity ReplLoadRule.CollisionDetect
63 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table ReplLoadRule.SourceSystem ~
64 ReplLoadRule.TableToLoad ReplLoadRule.Activity ReplLoadRule.CollisionDetect
65 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table~
66 ~
{&FP1}SourceSystem ~{&FP2}SourceSystem ~{&FP3}~
67 ~
{&FP1}TableToLoad ~{&FP2}TableToLoad ~{&FP3}~
68 ~
{&FP1}Activity ~{&FP2}Activity ~{&FP3}~
69 ~
{&FP1}CollisionDetect ~{&FP2}CollisionDetect ~{&FP3}
70 &Scoped-define ENABLED-TABLES-IN-QUERY-br_table ReplLoadRule
71 &Scoped-define FIRST-ENABLED-TABLE-IN-QUERY-br_table ReplLoadRule
72 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH ReplLoadRule WHERE ~{&KEY-PHRASE} NO-LOCK ~
74 &Scoped-define TABLES-IN-QUERY-br_table ReplLoadRule
75 &Scoped-define FIRST-TABLE-IN-QUERY-br_table ReplLoadRule
78 /* Definitions for
FRAME F-Main
*/
80 /* Standard List Definitions
*/
81 &Scoped-Define ENABLED-OBJECTS br_table cmb_office cmb_table RECT-1 ~
82 tgl_create tgl_modify tgl_delete tgl_rollback
83 &Scoped-Define DISPLAYED-OBJECTS cmb_office cmb_table tgl_create tgl_modify ~
84 tgl_delete tgl_rollback
86 /* Custom List Definitions
*/
87 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
89 /* _UIB-PREPROCESSOR-BLOCK-END
*/
93 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
94 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
100 OfficeCode|y|y|ttpl.ReplLog.OfficeCode
103 **************************
104 * Set attributes related to FOREIGN
KEYS
106 RUN set-attribute-list
(
107 'Keys-Accepted
= "OfficeCode",
108 Keys-Supplied
= "OfficeCode"'
:U
).
110 /* Tell the ADM to use the OPEN-QUERY-CASES.
*/
111 &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
112 /**************************
114 /* _UIB-CODE-BLOCK-END
*/
117 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
118 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
126 ************************
127 * Set attributes related to SORTBY-OPTIONS
*/
128 RUN set-attribute-list
(
129 'SortBy-Options
= ""'
:U
).
130 /************************
133 </FILTER-ATTRIBUTES
> */
135 /* _UIB-CODE-BLOCK-END
*/
139 /* *********************** Control Definitions
********************** */
142 /* Definitions of the field level widgets
*/
143 DEFINE VARIABLE cmb_office
AS CHARACTER FORMAT "X(256)":U
144 VIEW-AS COMBO-BOX INNER-LINES 5
146 SIZE 17.14 BY 1 NO-UNDO.
148 DEFINE VARIABLE cmb_table
AS CHARACTER FORMAT "X(256)"
149 VIEW-AS COMBO-BOX INNER-LINES 15
151 SIZE 17.14 BY 1 NO-UNDO.
153 DEFINE RECTANGLE RECT-1
154 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
157 DEFINE VARIABLE tgl_create
AS LOGICAL INITIAL no
162 DEFINE VARIABLE tgl_delete
AS LOGICAL INITIAL no
167 DEFINE VARIABLE tgl_modify
AS LOGICAL INITIAL no
172 DEFINE VARIABLE tgl_rollback
AS LOGICAL INITIAL no
173 LABEL "Rollback on collisions?"
175 SIZE 18.86 BY 1 NO-UNDO.
177 /* Query definitions
*/
179 DEFINE QUERY br_table
FOR
180 ReplLoadRule
SCROLLING.
183 /* Browse definitions
*/
184 DEFINE BROWSE br_table
185 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
186 QUERY br_table
NO-LOCK DISPLAY
187 ReplLoadRule.SourceSystem
FORMAT "X(4)"
188 ReplLoadRule.TableToLoad
189 ReplLoadRule.Activity
190 ReplLoadRule.CollisionDetect
COLUMN-LABEL "Rollback On?" FORMAT "Yes/No"
192 ReplLoadRule.SourceSystem
193 ReplLoadRule.TableToLoad
194 ReplLoadRule.Activity
195 ReplLoadRule.CollisionDetect
196 /* _UIB-CODE-BLOCK-END
*/
198 WITH NO-ASSIGN NO-ROW-MARKERS SEPARATORS SIZE 48.57 BY 13.6
202 /* ************************ Frame Definitions
*********************** */
205 br_table
AT ROW 1 COL 1
206 cmb_office
AT ROW 2 COL 48.14 COLON-ALIGNED NO-LABEL
207 cmb_table
AT ROW 4.4 COL 48.14 COLON-ALIGNED HELP
208 "Enter the name of the replicated table to load" NO-LABEL
209 tgl_create
AT ROW 6.8 COL 53
210 tgl_modify
AT ROW 7.8 COL 53
211 tgl_delete
AT ROW 8.8 COL 53
212 tgl_rollback
AT ROW 10.8 COL 50.14
213 "Source:" VIEW-AS TEXT
214 SIZE 8 BY 1 AT ROW 1 COL 50.14
215 "Table:" VIEW-AS TEXT
216 SIZE 8 BY 1 AT ROW 3.4 COL 50.14
217 "Load Changes on:" VIEW-AS TEXT
218 SIZE 15.43 BY 1 AT ROW 5.8 COL 50.72
219 RECT-1
AT ROW 6.2 COL 50.14
220 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
221 SIDE-LABELS NO-UNDERLINE THREE-D
222 AT COL 1 ROW 1 SCROLLABLE
226 /* *********************** Procedure Settings
************************ */
228 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
229 /* Settings for
THIS-PROCEDURE
233 Add Fields to
: EXTERNAL-TABLES
234 Other Settings
: PERSISTENT-ONLY
COMPILE
237 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
238 /* then cleanup and return.
*/
239 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
240 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
241 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
245 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
247 /* ************************* Create Window
************************** */
249 &ANALYZE-SUSPEND _CREATE-WINDOW
250 /* DESIGN Window definition
(used by the UIB
)
251 CREATE WINDOW B-table-Win
ASSIGN
254 /* END WINDOW DEFINITION
*/
259 /* *************** Runtime Attributes and UIB Settings
************** */
261 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
262 /* SETTINGS
FOR WINDOW B-table-Win
263 NOT-VISIBLE
,,RUN-PERSISTENT
*/
264 /* SETTINGS
FOR FRAME F-Main
265 NOT-VISIBLE Size-to-Fit
*/
266 /* BROWSE-TAB br_table
1 F-Main
*/
268 FRAME F-Main
:SCROLLABLE = FALSE
269 FRAME F-Main
:HIDDEN = TRUE.
271 /* _RUN-TIME-ATTRIBUTES-END
*/
275 /* Setting information for Queries and Browse Widgets fields
*/
277 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
278 /* Query rebuild information for
BROWSE br_table
279 _TblList
= "ttpl.ReplLoadRule"
280 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
281 _FldNameList
[1] > ttpl.ReplLoadRule.SourceSystem
282 "ReplLoadRule.SourceSystem" ?
"X(4)" "character" ? ? ? ? ? ? yes ?
283 _FldNameList
[2] > ttpl.ReplLoadRule.TableToLoad
284 "ReplLoadRule.TableToLoad" ? ?
"character" ? ? ? ? ? ? yes ?
285 _FldNameList
[3] > ttpl.ReplLoadRule.Activity
286 "ReplLoadRule.Activity" ? ?
"character" ? ? ? ? ? ? yes ?
287 _FldNameList
[4] > ttpl.ReplLoadRule.CollisionDetect
288 "ReplLoadRule.CollisionDetect" "Rollback On?" "Yes/No" "logical" ? ? ? ? ? ? yes ?
290 */ /* BROWSE br_table
*/
293 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
294 /* Query rebuild information for
FRAME F-Main
297 */ /* FRAME F-Main
*/
303 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
304 /* ************************* Included-Libraries
*********************** */
306 {src
/adm
/method
/browser.i
}
307 {inc
/method
/m-drlvwr.i
}
309 /* _UIB-CODE-BLOCK-END
*/
315 /* ************************ Control Triggers
************************ */
317 &Scoped-define BROWSE-NAME br_table
318 &Scoped-define SELF-NAME br_table
319 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
320 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
322 /* This code displays initial values for newly added or copied rows.
*/
323 {src
/adm
/template
/brsentry.i
}
326 /* _UIB-CODE-BLOCK-END
*/
330 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
331 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
333 /* Do not disable this code or no updates will take place except
334 by pressing the Save button on an Update SmartPanel.
*/
335 {src
/adm
/template
/brsleave.i
}
338 /* _UIB-CODE-BLOCK-END
*/
342 &Scoped-define SELF-NAME cmb_office
343 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_office B-table-Win
344 ON VALUE-CHANGED
OF cmb_office
IN FRAME F-Main
349 /* _UIB-CODE-BLOCK-END
*/
353 &Scoped-define SELF-NAME cmb_table
354 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_table B-table-Win
355 ON VALUE-CHANGED
OF cmb_table
IN FRAME F-Main
360 /* _UIB-CODE-BLOCK-END
*/
364 &Scoped-define SELF-NAME tgl_create
365 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL tgl_create B-table-Win
366 ON VALUE-CHANGED
OF tgl_create
IN FRAME F-Main
/* Create
*/
371 /* _UIB-CODE-BLOCK-END
*/
375 &Scoped-define SELF-NAME tgl_delete
376 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL tgl_delete B-table-Win
377 ON VALUE-CHANGED
OF tgl_delete
IN FRAME F-Main
/* Delete
*/
382 /* _UIB-CODE-BLOCK-END
*/
386 &Scoped-define SELF-NAME tgl_modify
387 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL tgl_modify B-table-Win
388 ON VALUE-CHANGED
OF tgl_modify
IN FRAME F-Main
/* Modify
*/
393 /* _UIB-CODE-BLOCK-END
*/
397 &Scoped-define SELF-NAME tgl_rollback
398 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL tgl_rollback B-table-Win
399 ON VALUE-CHANGED
OF tgl_rollback
IN FRAME F-Main
/* Rollback on collisions?
*/
401 RUN rollback-changed.
404 /* _UIB-CODE-BLOCK-END
*/
410 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
413 /* *************************** Main Block
*************************** */
415 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
416 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
419 ReplLoadRule.Source
:READ-ONLY IN BROWSE {&BROWSE-NAME} = Yes.
420 ReplLoadRule.Activity
:READ-ONLY IN BROWSE {&BROWSE-NAME} = Yes.
421 ReplLoadRule.CollisionDetect
:READ-ONLY IN BROWSE {&BROWSE-NAME} = Yes.
422 ReplLoadRule.TableToLoad
:READ-ONLY IN BROWSE {&BROWSE-NAME} = Yes.
424 /* _UIB-CODE-BLOCK-END
*/
428 /* ********************** Internal Procedures
*********************** */
430 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-open-query-cases B-table-Win adm/support/_adm-opn.p
431 PROCEDURE adm-open-query-cases
:
432 /*------------------------------------------------------------------------------
433 Purpose
: Opens different cases of the query based on attributes
434 such as the 'Key-Name'
, or 'SortBy-Case'
436 ------------------------------------------------------------------------------*/
437 DEF VAR key-value
AS CHAR NO-UNDO.
439 /* Look up the current key-value.
*/
440 RUN get-attribute
('Key-Value'
:U
).
441 key-value
= RETURN-VALUE.
443 /* Find the current record using the current Key-Name.
*/
444 RUN get-attribute
('Key-Name'
:U
).
446 WHEN 'OfficeCode'
:U
THEN DO:
447 &Scope KEY-PHRASE ReplLog.OfficeCode eq key-value
448 {&OPEN-QUERY-{&BROWSE-NAME}}
449 END.
/* OfficeCode
*/
451 &Scope KEY-PHRASE TRUE
452 {&OPEN-QUERY-{&BROWSE-NAME}}
453 END.
/* OTHERWISE...
*/
458 /* _UIB-CODE-BLOCK-END
*/
462 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
463 PROCEDURE adm-row-available
:
464 /*------------------------------------------------------------------------------
465 Purpose
: Dispatched to this procedure when the Record-
466 Source has a new row available. This procedure
467 tries to get the new row
(or foriegn keys
) from
468 the Record-Source and process it.
470 ------------------------------------------------------------------------------*/
472 /* Define variables needed by this internal procedure.
*/
473 {src
/adm
/template
/row-head.i
}
475 /* Process the newly available records
(i.e. display fields
,
476 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
477 {src
/adm
/template
/row-end.i
}
481 /* _UIB-CODE-BLOCK-END
*/
485 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
486 PROCEDURE disable_UI
:
487 /*------------------------------------------------------------------------------
488 Purpose
: DISABLE the User Interface
490 Notes
: Here we clean-up the user-interface by deleting
491 dynamic widgets we have created and
/or hide
492 frames. This procedure is usually called when
493 we are ready to
"clean-up" after running.
494 ------------------------------------------------------------------------------*/
495 /* Hide all frames.
*/
497 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
500 /* _UIB-CODE-BLOCK-END
*/
504 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-value-changed B-table-Win
505 PROCEDURE inst-value-changed
:
506 /*------------------------------------------------------------------------------
510 ------------------------------------------------------------------------------*/
512 RUN set-link-attributes
IN sys-mgr
( THIS-PROCEDURE, "delete-record",
513 "SENSITIVE = " + IF AVAILABLE ReplLoadRule
THEN "Yes" ELSE "No" ).
518 /* _UIB-CODE-BLOCK-END
*/
522 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE load-changes B-table-Win
523 PROCEDURE load-changes
:
524 /*------------------------------------------------------------------------------
528 ------------------------------------------------------------------------------*/
531 "Are you sure you want to load all" SKIP
532 "outstanding replication changes ?" SKIP
533 VIEW-AS ALERT-BOX QUESTION BUTTONS YES-NO
534 TITLE "Proceed ?" UPDATE reload-it
AS LOGI.
536 IF NOT reload-it
THEN RETURN.
538 RUN rplctn\replload.p.
540 MESSAGE "Replication Load complete"
541 VIEW-AS ALERT-BOX INFORMATION TITLE "Done".
545 /* _UIB-CODE-BLOCK-END
*/
549 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-add-record B-table-Win
550 PROCEDURE local-add-record
:
551 /*------------------------------------------------------------------------------
552 Purpose
: Override standard ADM method
554 ------------------------------------------------------------------------------*/
556 /* Code placed here will execute PRIOR to standard behavior.
*/
558 /* Dispatch standard ADM method.
*/
559 RUN dispatch
IN THIS-PROCEDURE ( INPUT 'add-record'
:U
) .
561 /* Code placed here will execute AFTER standard behavior.
*/
562 RUN sensitise-fields
( Yes
).
566 /* _UIB-CODE-BLOCK-END
*/
570 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-delete-record B-table-Win
571 PROCEDURE local-delete-record
:
572 /*------------------------------------------------------------------------------
573 Purpose
: Override standard ADM method
575 ------------------------------------------------------------------------------*/
577 /* Code placed here will execute PRIOR to standard behavior.
*/
579 /* Dispatch standard ADM method.
*/
580 RUN dispatch
IN THIS-PROCEDURE ( INPUT 'delete-record'
:U
) .
582 /* Code placed here will execute AFTER standard behavior.
*/
587 /* _UIB-CODE-BLOCK-END
*/
591 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE office-changed B-table-Win
592 PROCEDURE office-changed
:
593 /*------------------------------------------------------------------------------
597 ------------------------------------------------------------------------------*/
599 DO WITH FRAME {&FRAME-NAME}:
600 ReplLoadRule.Source
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} = INPUT cmb_office.
601 /* Ensure that the record gets updated
*/
602 RUN dispatch
( 'update-record'
:U
).
607 /* _UIB-CODE-BLOCK-END
*/
611 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE options-changed B-table-Win
612 PROCEDURE options-changed
:
613 /*------------------------------------------------------------------------------
617 ------------------------------------------------------------------------------*/
619 DO WITH FRAME {&FRAME-NAME}:
620 IF NOT AVAILABLE ReplLoadRule
THEN RETURN.
621 DEF VAR act
AS CHAR NO-UNDO.
622 ASSIGN FRAME {&FRAME-NAME} tgl_create tgl_modify tgl_delete.
623 act
= ( IF tgl_create
THEN "C" ELSE "" ) +
624 ( IF tgl_modify
THEN "M" ELSE "" ) +
625 ( IF tgl_delete
THEN "D" ELSE "" ).
626 ReplLoadRule.Activity
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} = act.
627 /* Ensure that the record gets updated
*/
628 RUN dispatch
( 'update-record'
:U
).
633 /* _UIB-CODE-BLOCK-END
*/
637 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-initialize B-table-Win
638 PROCEDURE pre-initialize
:
639 /*------------------------------------------------------------------------------
643 ------------------------------------------------------------------------------*/
645 /* Populate the table name combo
*/
647 FOR EACH _File
WHERE NOT _File._File-Name
BEGINS "_" NO-LOCK:
648 IF cmb_table
:ADD-LAST( _File._File-Name
) IN FRAME {&FRAME-NAME} THEN.
651 /* Populate the office combo
*/
653 FOR EACH Office
NO-LOCK WHERE NOT ThisOffice
:
654 IF cmb_office
:ADD-LAST( Office.OfficeCode
) IN FRAME {&FRAME-NAME} THEN.
659 /* _UIB-CODE-BLOCK-END
*/
663 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE rollback-changed B-table-Win
664 PROCEDURE rollback-changed
:
665 /*------------------------------------------------------------------------------
669 ------------------------------------------------------------------------------*/
671 DO WITH FRAME {&FRAME-NAME}:
672 ReplLoadRule.CollisionDetect
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} =
673 tgl_rollback
:SCREEN-VALUE.
674 /* Ensure that the record gets updated
*/
675 RUN dispatch
( 'update-record'
:U
).
680 /* _UIB-CODE-BLOCK-END
*/
684 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE rule-changed B-table-Win
685 PROCEDURE rule-changed
:
686 /*------------------------------------------------------------------------------
690 ------------------------------------------------------------------------------*/
692 DO WITH FRAME {&FRAME-NAME}:
693 DEF VAR act
AS CHAR NO-UNDO.
694 CLEAR FRAME {&FRAME-NAME} ALL.
695 act
= INPUT BROWSE {&BROWSE-NAME} ReplLoadRule.Activity.
696 tgl_create
= INDEX( act
, "C" ) <> 0.
697 tgl_modify
= INDEX( act
, "M" ) <> 0.
698 tgl_delete
= INDEX( act
, "D" ) <> 0.
699 cmb_table
:SCREEN-VALUE = INPUT BROWSE {&BROWSE-NAME} ReplLoadRule.TableToLoad.
700 ASSIGN cmb_office
:SCREEN-VALUE = INPUT BROWSE {&BROWSE-NAME} ReplLoadRule.Source NO-ERROR.
701 tgl_rollback
= ReplLoadRule.CollisionDetect
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} = "Yes".
702 IF tgl_rollback
= ?
THEN tgl_rollback
= No.
708 WITH FRAME {&FRAME-NAME}.
709 RUN sensitise-fields
( AVAILABLE ReplLoadRule
).
714 /* _UIB-CODE-BLOCK-END
*/
718 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
720 /*------------------------------------------------------------------------------
721 Purpose
: Sends a requested
KEY value back to the calling
723 Parameters
: <see adm
/template
/sndkytop.i
>
724 ------------------------------------------------------------------------------*/
726 /* Define variables needed by this internal procedure.
*/
727 {src
/adm
/template
/sndkytop.i
}
729 /* Return the key value associated with each key case.
*/
730 {src
/adm
/template
/sndkycas.i
"OfficeCode" "ReplLog" "OfficeCode"}
732 /* Close the
CASE statement and end the procedure.
*/
733 {src
/adm
/template
/sndkyend.i
}
737 /* _UIB-CODE-BLOCK-END
*/
741 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
742 PROCEDURE send-records
:
743 /*------------------------------------------------------------------------------
744 Purpose
: Send record
ROWID's for all tables used by
746 Parameters
: see template
/snd-head.i
747 ------------------------------------------------------------------------------*/
749 /* Define variables needed by this internal procedure.
*/
750 {src
/adm
/template
/snd-head.i
}
752 /* For each requested table
, put it's
ROWID in the output list.
*/
753 {src
/adm
/template
/snd-list.i
"ReplLoadRule"}
755 /* Deal with any unexpected table requests before closing.
*/
756 {src
/adm
/template
/snd-end.i
}
760 /* _UIB-CODE-BLOCK-END
*/
764 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE sensitise-fields B-table-Win
765 PROCEDURE sensitise-fields
:
766 /*------------------------------------------------------------------------------
770 ------------------------------------------------------------------------------*/
772 DO WITH FRAME {&FRAME-NAME}:
773 DEF INPUT PARAMETER sens
AS LOGI
NO-UNDO.
775 cmb_office
:SENSITIVE = sens.
776 cmb_table
:SENSITIVE = sens.
777 tgl_create
:SENSITIVE = sens.
778 tgl_modify
:SENSITIVE = sens.
779 tgl_delete
:SENSITIVE = sens.
780 tgl_rollback
:SENSITIVE = sens.
785 /* _UIB-CODE-BLOCK-END
*/
789 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
790 PROCEDURE state-changed
:
791 /* -----------------------------------------------------------
795 -------------------------------------------------------------*/
796 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
797 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
800 /* Object instance CASEs can go here to replace standard behavior
802 {src
/adm
/template
/bstates.i
}
806 /* _UIB-CODE-BLOCK-END
*/
810 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE table-changed B-table-Win
811 PROCEDURE table-changed
:
812 /*------------------------------------------------------------------------------
816 ------------------------------------------------------------------------------*/
818 DO WITH FRAME {&FRAME-NAME}:
819 ReplLoadRule.TableToLoad
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} = INPUT cmb_table.
820 /* Ensure that the record gets updated
*/
821 RUN dispatch
( 'update-record'
:U
).
826 /* _UIB-CODE-BLOCK-END
*/