Added capital works blank section. Synced calling screen.
[capital-apms-progress.git] / vwr / sel / b-selfyr.w
blob5f4f911b4fdc59c7b4c757e37e4dd120060e795f
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 B-table-Win
8 /*------------------------------------------------------------------------
9 ------------------------------------------------------------------------*/
10 CREATE WIDGET-POOL.
11 /* *************************** Definitions ************************** */
13 /* _UIB-CODE-BLOCK-END */
14 &ANALYZE-RESUME
17 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
19 /* ******************** Preprocessor Definitions ******************** */
21 &Scoped-define PROCEDURE-TYPE SmartBrowser
23 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
25 /* Name of first Frame and/or Browse and/or first Query */
26 &Scoped-define FRAME-NAME F-Main
27 &Scoped-define BROWSE-NAME br_table
29 /* Internal Tables (found by Frame, Query & Browse Queries) */
30 &Scoped-define INTERNAL-TABLES FinancialYear
32 /* Define KEY-PHRASE in case it is used by any query. */
33 &Scoped-define KEY-PHRASE TRUE
35 /* Definitions for BROWSE br_table */
36 &Scoped-define FIELDS-IN-QUERY-br_table FinancialYear.FinancialYearCode ~
37 FinancialYear.Description
38 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table
39 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table
40 &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH FinancialYear WHERE ~{&KEY-PHRASE} NO-LOCK ~
41 ~{&SORTBY-PHRASE}.
42 &Scoped-define TABLES-IN-QUERY-br_table FinancialYear
43 &Scoped-define FIRST-TABLE-IN-QUERY-br_table FinancialYear
46 /* Definitions for FRAME F-Main */
48 /* Standard List Definitions */
49 &Scoped-Define ENABLED-OBJECTS br_table
51 /* Custom List Definitions */
52 /* List-1,List-2,List-3,List-4,List-5,List-6 */
54 /* _UIB-PREPROCESSOR-BLOCK-END */
55 &ANALYZE-RESUME
58 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
59 /* Actions: ? adm/support/keyedit.w ? ? ? */
60 /* STRUCTURED-DATA
61 <KEY-OBJECT>
62 &BROWSE-NAME
63 </KEY-OBJECT>
64 <FOREIGN-KEYS>
65 </FOREIGN-KEYS>
66 <EXECUTING-CODE>
67 **************************
68 * Set attributes related to FOREIGN KEYS
70 RUN set-attribute-list (
71 'Keys-Accepted = "",
72 Keys-Supplied = ""':U).
73 /**************************
74 </EXECUTING-CODE> */
76 /* _UIB-CODE-BLOCK-END */
77 &ANALYZE-RESUME
79 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
80 /* Actions: ? adm/support/advqedit.w ? ? ? */
81 /* STRUCTURED-DATA
82 <KEY-OBJECT>
83 &BROWSE-NAME
84 </KEY-OBJECT>
85 <SORTBY-OPTIONS>
86 </SORTBY-OPTIONS>
87 <SORTBY-RUN-CODE>
88 ************************
89 * Set attributes related to SORTBY-OPTIONS */
90 RUN set-attribute-list (
91 'SortBy-Options = ""':U).
92 /************************
93 </SORTBY-RUN-CODE>
94 <FILTER-ATTRIBUTES>
95 </FILTER-ATTRIBUTES> */
97 /* _UIB-CODE-BLOCK-END */
98 &ANALYZE-RESUME
101 /* *********************** Control Definitions ********************** */
104 /* Definitions of the field level widgets */
105 /* Query definitions */
106 &ANALYZE-SUSPEND
107 DEFINE QUERY br_table FOR
108 FinancialYear SCROLLING.
109 &ANALYZE-RESUME
111 /* Browse definitions */
112 DEFINE BROWSE br_table
113 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED
114 QUERY br_table NO-LOCK DISPLAY
115 FinancialYear.FinancialYearCode COLUMN-LABEL "- Year -"
116 FinancialYear.Description FORMAT "X(70)"
117 /* _UIB-CODE-BLOCK-END */
118 &ANALYZE-RESUME
119 WITH NO-ASSIGN SEPARATORS SIZE 60 BY 15.78
120 BGCOLOR 16 .
123 /* ************************ Frame Definitions *********************** */
125 DEFINE FRAME F-Main
126 br_table AT ROW 1 COL 1
127 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
128 SIDE-LABELS NO-UNDERLINE THREE-D
129 AT COL 1 ROW 1 SCROLLABLE
130 BGCOLOR 8 FGCOLOR 0 .
133 /* *********************** Procedure Settings ************************ */
135 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
136 /* Settings for THIS-PROCEDURE
137 Type: SmartBrowser
138 Allow: Basic,Browse
139 Frames: 1
140 Add Fields to: EXTERNAL-TABLES
141 Other Settings: PERSISTENT-ONLY COMPILE
144 /* This procedure should always be RUN PERSISTENT. Report the error, */
145 /* then cleanup and return. */
146 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
147 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
148 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
149 RETURN.
150 END.
152 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
154 /* ************************* Create Window ************************** */
156 &ANALYZE-SUSPEND _CREATE-WINDOW
157 /* DESIGN Window definition (used by the UIB)
158 CREATE WINDOW B-table-Win ASSIGN
159 HEIGHT = 16.17
160 WIDTH = 93.
161 /* END WINDOW DEFINITION */
163 &ANALYZE-RESUME
166 /* *************** Runtime Attributes and UIB Settings ************** */
168 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
169 /* SETTINGS FOR WINDOW B-table-Win
170 NOT-VISIBLE,,RUN-PERSISTENT */
171 /* SETTINGS FOR FRAME F-Main
172 NOT-VISIBLE Size-to-Fit */
173 /* BROWSE-TAB br_table 1 F-Main */
174 ASSIGN
175 FRAME F-Main:SCROLLABLE = FALSE
176 FRAME F-Main:HIDDEN = TRUE.
178 /* _RUN-TIME-ATTRIBUTES-END */
179 &ANALYZE-RESUME
182 /* Setting information for Queries and Browse Widgets fields */
184 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
185 /* Query rebuild information for BROWSE br_table
186 _TblList = "ttpl.FinancialYear"
187 _Options = "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
188 _FldNameList[1] > ttpl.FinancialYear.FinancialYearCode
189 "FinancialYearCode" "- Year -" ? "integer" ? ? ? ? ? ? no ?
190 _FldNameList[2] > ttpl.FinancialYear.Description
191 "Description" ? "X(70)" "character" ? ? ? ? ? ? no ?
192 _Query is NOT OPENED
193 */ /* BROWSE br_table */
194 &ANALYZE-RESUME
196 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
197 /* Query rebuild information for FRAME F-Main
198 _Options = "NO-LOCK"
199 _Query is NOT OPENED
200 */ /* FRAME F-Main */
201 &ANALYZE-RESUME
205 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "SmartBrowserCues" B-table-Win _INLINE
206 /* Actions: adecomm/_so-cue.w ? adecomm/_so-cued.p ? adecomm/_so-cuew.p */
207 /* SmartBrowser,uib,49266
208 Destroy on next read */
209 /* _UIB-CODE-BLOCK-END */
210 &ANALYZE-RESUME
213 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
214 /* ************************* Included-Libraries *********************** */
216 {src/adm/method/browser.i}
217 {inc/method/m-selvwr.i}
219 /* _UIB-CODE-BLOCK-END */
220 &ANALYZE-RESUME
225 /* ************************ Control Triggers ************************ */
227 &Scoped-define BROWSE-NAME br_table
228 &Scoped-define SELF-NAME br_table
229 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
230 ON ROW-ENTRY OF br_table IN FRAME F-Main
232 /* This code displays initial values for newly added or copied rows. */
233 {src/adm/template/brsentry.i}
234 END.
236 /* _UIB-CODE-BLOCK-END */
237 &ANALYZE-RESUME
240 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
241 ON ROW-LEAVE OF br_table IN FRAME F-Main
243 /* Do not disable this code or no updates will take place except
244 by pressing the Save button on an Update SmartPanel. */
245 {src/adm/template/brsleave.i}
246 END.
248 /* _UIB-CODE-BLOCK-END */
249 &ANALYZE-RESUME
252 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
253 ON VALUE-CHANGED OF br_table IN FRAME F-Main
255 /* This ADM trigger code must be preserved in order to notify other
256 objects when the browser's current row changes. */
257 {src/adm/template/brschnge.i}
258 END.
260 /* _UIB-CODE-BLOCK-END */
261 &ANALYZE-RESUME
264 &UNDEFINE SELF-NAME
266 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
269 /* *************************** Main Block *************************** */
271 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
272 RUN dispatch IN THIS-PROCEDURE ('initialize':U).
273 &ENDIF
275 /* _UIB-CODE-BLOCK-END */
276 &ANALYZE-RESUME
279 /* ********************** Internal Procedures *********************** */
281 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
282 PROCEDURE adm-row-available :
283 /*------------------------------------------------------------------------------
284 Purpose: Dispatched to this procedure when the Record-
285 Source has a new row available. This procedure
286 tries to get the new row (or foriegn keys) from
287 the Record-Source and process it.
288 Parameters: <none>
289 ------------------------------------------------------------------------------*/
291 /* Define variables needed by this internal procedure. */
292 {src/adm/template/row-head.i}
294 /* Process the newly available records (i.e. display fields,
295 open queries, and/or pass records on to any RECORD-TARGETS). */
296 {src/adm/template/row-end.i}
298 END PROCEDURE.
300 /* _UIB-CODE-BLOCK-END */
301 &ANALYZE-RESUME
304 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
305 PROCEDURE disable_UI :
306 /*------------------------------------------------------------------------------
307 Purpose: DISABLE the User Interface
308 Parameters: <none>
309 Notes: Here we clean-up the user-interface by deleting
310 dynamic widgets we have created and/or hide
311 frames. This procedure is usually called when
312 we are ready to "clean-up" after running.
313 ------------------------------------------------------------------------------*/
314 /* Hide all frames. */
315 HIDE FRAME F-Main.
316 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
317 END PROCEDURE.
319 /* _UIB-CODE-BLOCK-END */
320 &ANALYZE-RESUME
323 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
324 PROCEDURE send-records :
325 /*------------------------------------------------------------------------------
326 Purpose: Send record ROWID's for all tables used by
327 this file.
328 Parameters: see template/snd-head.i
329 ------------------------------------------------------------------------------*/
331 /* Define variables needed by this internal procedure. */
332 {src/adm/template/snd-head.i}
334 /* For each requested table, put it's ROWID in the output list. */
335 {src/adm/template/snd-list.i "FinancialYear"}
337 /* Deal with any unexpected table requests before closing. */
338 {src/adm/template/snd-end.i}
340 END PROCEDURE.
342 /* _UIB-CODE-BLOCK-END */
343 &ANALYZE-RESUME
346 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
347 PROCEDURE state-changed :
348 /* -----------------------------------------------------------
349 Purpose:
350 Parameters: <none>
351 Notes:
352 -------------------------------------------------------------*/
353 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
354 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
356 CASE p-state:
357 /* Object instance CASEs can go here to replace standard behavior
358 or add new cases. */
359 {src/adm/template/bstates.i}
360 END CASE.
361 END PROCEDURE.
363 /* _UIB-CODE-BLOCK-END */
364 &ANALYZE-RESUME