Really, this should be it, for the passing income.
[capital-apms-progress.git] / vwr / mnt / v-selscn.w
blob38c392d583b2366bc9ca9327090099817f8937bf
1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
2 &ANALYZE-RESUME
3 /* Connected Databases
4 ttpl PROGRESS
5 */
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS V-table-Win
8 /*------------------------------------------------------------------------
9 File:
10 Description:
11 ------------------------------------------------------------------------*/
12 CREATE WIDGET-POOL.
13 /* *************************** Definitions ************************** */
15 DEF VAR user-name AS CHAR NO-UNDO.
16 {inc/username.i "user-name"}
18 /* _UIB-CODE-BLOCK-END */
19 &ANALYZE-RESUME
22 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
24 /* ******************** Preprocessor Definitions ******************** */
26 &Scoped-define PROCEDURE-TYPE SmartViewer
28 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
30 /* Name of first Frame and/or Browse and/or first Query */
31 &Scoped-define FRAME-NAME F-Main
33 /* External Tables */
34 &Scoped-define EXTERNAL-TABLES RP
35 &Scoped-define FIRST-EXTERNAL-TABLE RP
38 /* Need to scope the external tables to this procedure */
39 DEFINE QUERY external_tables FOR RP.
40 /* Standard List Definitions */
41 &Scoped-Define ENABLED-FIELDS RP.Int1
42 &Scoped-define FIELD-PAIRS~
43 ~{&FP1}Int1 ~{&FP2}Int1 ~{&FP3}
44 &Scoped-define ENABLED-TABLES RP
45 &Scoped-define FIRST-ENABLED-TABLE RP
46 &Scoped-Define ENABLED-OBJECTS RECT-27 btn_ok
47 &Scoped-Define DISPLAYED-FIELDS RP.Int1
48 &Scoped-Define DISPLAYED-OBJECTS fil_Scenario
50 /* Custom List Definitions */
51 /* ADM-CREATE-FIELDS,ADM-ASSIGN-FIELDS,List-3,List-4,List-5,List-6 */
53 /* _UIB-PREPROCESSOR-BLOCK-END */
54 &ANALYZE-RESUME
58 /* *********************** Control Definitions ********************** */
61 /* Definitions of the field level widgets */
62 DEFINE BUTTON btn_ok
63 LABEL "&OK"
64 SIZE 10.29 BY 1.1.
66 DEFINE VARIABLE fil_Scenario AS CHARACTER FORMAT "X(256)":U
67 VIEW-AS FILL-IN
68 SIZE 35 BY 1.05 NO-UNDO.
70 DEFINE RECTANGLE RECT-27
71 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
72 SIZE 53.14 BY 3.
75 /* ************************ Frame Definitions *********************** */
77 DEFINE FRAME F-Main
78 RP.Int1 AT ROW 1.4 COL 2.14
79 LABEL "Scenario"
80 VIEW-AS FILL-IN
81 SIZE 6.29 BY 1.05
82 fil_Scenario AT ROW 1.4 COL 16.14 COLON-ALIGNED NO-LABEL
83 btn_ok AT ROW 2.6 COL 42.72
84 RECT-27 AT ROW 1 COL 1
85 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
86 SIDE-LABELS NO-UNDERLINE THREE-D
87 AT COL 1 ROW 1 SCROLLABLE
88 FONT 10.
91 /* *********************** Procedure Settings ************************ */
93 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
94 /* Settings for THIS-PROCEDURE
95 Type: SmartViewer
96 External Tables: TTPL.RP
97 Allow: Basic,DB-Fields
98 Frames: 1
99 Add Fields to: EXTERNAL-TABLES
100 Other Settings: PERSISTENT-ONLY COMPILE
103 /* This procedure should always be RUN PERSISTENT. Report the error, */
104 /* then cleanup and return. */
105 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
106 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
107 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
108 RETURN.
109 END.
111 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
113 /* ************************* Create Window ************************** */
115 &ANALYZE-SUSPEND _CREATE-WINDOW
116 /* DESIGN Window definition (used by the UIB)
117 CREATE WINDOW V-table-Win ASSIGN
118 HEIGHT = 3.1
119 WIDTH = 53.14.
120 /* END WINDOW DEFINITION */
122 &ANALYZE-RESUME
125 /* *************** Runtime Attributes and UIB Settings ************** */
127 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
128 /* SETTINGS FOR WINDOW V-table-Win
129 VISIBLE,,RUN-PERSISTENT */
130 /* SETTINGS FOR FRAME F-Main
131 NOT-VISIBLE Size-to-Fit */
132 ASSIGN
133 FRAME F-Main:SCROLLABLE = FALSE
134 FRAME F-Main:HIDDEN = TRUE.
136 /* SETTINGS FOR FILL-IN fil_Scenario IN FRAME F-Main
137 NO-ENABLE */
138 /* SETTINGS FOR FILL-IN RP.Int1 IN FRAME F-Main
139 ALIGN-L EXP-LABEL */
140 /* _RUN-TIME-ATTRIBUTES-END */
141 &ANALYZE-RESUME
144 /* Setting information for Queries and Browse Widgets fields */
146 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
147 /* Query rebuild information for FRAME F-Main
148 _Options = "NO-LOCK"
149 _Query is NOT OPENED
150 */ /* FRAME F-Main */
151 &ANALYZE-RESUME
156 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
157 /* ************************* Included-Libraries *********************** */
159 {src/adm/method/viewer.i}
160 {inc/method/m-mntvwr.i}
162 /* _UIB-CODE-BLOCK-END */
163 &ANALYZE-RESUME
168 /* ************************ Control Triggers ************************ */
170 &Scoped-define SELF-NAME btn_ok
171 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL btn_ok V-table-Win
172 ON CHOOSE OF btn_ok IN FRAME F-Main /* OK */
174 RUN dispatch( 'update-record':U ).
175 RUN dispatch( 'exit':U ).
176 END.
178 /* _UIB-CODE-BLOCK-END */
179 &ANALYZE-RESUME
182 &Scoped-define SELF-NAME fil_Scenario
183 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL fil_Scenario V-table-Win
184 ON U1 OF fil_Scenario IN FRAME F-Main
186 {inc/selfil/sfscn1.i "RP" "Int1"}
187 END.
189 /* _UIB-CODE-BLOCK-END */
190 &ANALYZE-RESUME
193 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL fil_Scenario V-table-Win
194 ON U2 OF fil_Scenario IN FRAME F-Main
196 {inc/selfil/sfscn2.i "RP" "Int1"}
197 END.
199 /* _UIB-CODE-BLOCK-END */
200 &ANALYZE-RESUME
203 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL fil_Scenario V-table-Win
204 ON U3 OF fil_Scenario IN FRAME F-Main
206 {inc/selfil/sfscn3.i "RP" "Int1"}
207 END.
209 /* _UIB-CODE-BLOCK-END */
210 &ANALYZE-RESUME
213 &Scoped-define SELF-NAME RP.Int1
214 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL RP.Int1 V-table-Win
215 ON LEAVE OF RP.Int1 IN FRAME F-Main /* Scenario */
217 {inc/selcde/cdscn.i "fil_Scenario"}
218 END.
220 /* _UIB-CODE-BLOCK-END */
221 &ANALYZE-RESUME
224 &UNDEFINE SELF-NAME
226 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
229 /* *************************** Main Block *************************** */
231 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
232 RUN dispatch IN THIS-PROCEDURE ('initialize':U).
233 &ENDIF
235 /************************ INTERNAL PROCEDURES ********************/
237 /* _UIB-CODE-BLOCK-END */
238 &ANALYZE-RESUME
241 /* ********************** Internal Procedures *********************** */
243 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
244 PROCEDURE adm-row-available :
245 /*------------------------------------------------------------------------------
246 Purpose: Dispatched to this procedure when the Record-
247 Source has a new row available. This procedure
248 tries to get the new row (or foriegn keys) from
249 the Record-Source and process it.
250 Parameters: <none>
251 ------------------------------------------------------------------------------*/
253 /* Define variables needed by this internal procedure. */
254 {src/adm/template/row-head.i}
256 /* Create a list of all the tables that we need to get. */
257 {src/adm/template/row-list.i "RP"}
259 /* Get the record ROWID's from the RECORD-SOURCE. */
260 {src/adm/template/row-get.i}
262 /* FIND each record specified by the RECORD-SOURCE. */
263 {src/adm/template/row-find.i "RP"}
265 /* Process the newly available records (i.e. display fields,
266 open queries, and/or pass records on to any RECORD-TARGETS). */
267 {src/adm/template/row-end.i}
269 END PROCEDURE.
271 /* _UIB-CODE-BLOCK-END */
272 &ANALYZE-RESUME
275 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
276 PROCEDURE disable_UI :
277 /*------------------------------------------------------------------------------
278 Purpose: DISABLE the User Interface
279 Parameters: <none>
280 Notes: Here we clean-up the user-interface by deleting
281 dynamic widgets we have created and/or hide
282 frames. This procedure is usually called when
283 we are ready to "clean-up" after running.
284 ------------------------------------------------------------------------------*/
285 /* Hide all frames. */
286 HIDE FRAME F-Main.
287 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
288 END PROCEDURE.
290 /* _UIB-CODE-BLOCK-END */
291 &ANALYZE-RESUME
294 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
295 PROCEDURE inst-initialize :
296 /*------------------------------------------------------------------------------
297 Purpose:
298 Parameters: <none>
299 Notes:
300 ------------------------------------------------------------------------------*/
302 &SCOP REPORT-ID "Current Scenario"
304 FIND RP WHERE
305 RP.UserName = user-name AND
306 RP.ReportID = {&REPORT-ID} NO-ERROR.
308 IF NOT AVAILABLE RP THEN
309 DO WITH FRAME {&FRAME-NAME}:
311 CREATE RP.
312 ASSIGN
313 RP.ReportID = {&REPORT-ID}
314 RP.UserName = user-name.
315 END.
317 RUN dispatch( 'enable-fields':U ).
318 RUN dispatch( 'display-fields':U ).
320 END PROCEDURE.
322 /* _UIB-CODE-BLOCK-END */
323 &ANALYZE-RESUME
326 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
327 PROCEDURE pre-destroy :
328 /*------------------------------------------------------------------------------
329 Purpose:
330 Parameters: <none>
331 Notes:
332 ------------------------------------------------------------------------------*/
334 RUN check-modified( "CLEAR" ).
336 END PROCEDURE.
338 /* _UIB-CODE-BLOCK-END */
339 &ANALYZE-RESUME
342 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
343 PROCEDURE send-records :
344 /*------------------------------------------------------------------------------
345 Purpose: Send record ROWID's for all tables used by
346 this file.
347 Parameters: see template/snd-head.i
348 ------------------------------------------------------------------------------*/
350 /* Define variables needed by this internal procedure. */
351 {src/adm/template/snd-head.i}
353 /* For each requested table, put it's ROWID in the output list. */
354 {src/adm/template/snd-list.i "RP"}
356 /* Deal with any unexpected table requests before closing. */
357 {src/adm/template/snd-end.i}
359 END PROCEDURE.
361 /* _UIB-CODE-BLOCK-END */
362 &ANALYZE-RESUME
365 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
366 PROCEDURE state-changed :
367 /* -----------------------------------------------------------
368 Purpose:
369 Parameters: <none>
370 Notes:
371 -------------------------------------------------------------*/
372 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
373 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
375 CASE p-state:
376 /* Object instance CASEs can go here to replace standard behavior
377 or add new cases. */
378 {src/adm/template/vstates.i}
379 END CASE.
380 END PROCEDURE.
382 /* _UIB-CODE-BLOCK-END */
383 &ANALYZE-RESUME