Changes for Catalyst APMS. Added PDF checkboxes to screens the generate remittance...
[capital-apms-progress.git] / vwr / mnt / v-cheque-whites.w
blob9fb387f279b51f1f943e02a35352fa1f9ac806e4
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: vwr\mnt\v-cheque-whites.w
10 ------------------------------------------------------------------------*/
11 CREATE WIDGET-POOL.
12 /* *************************** Definitions ************************** */
14 &SCOP REPORT-ID "cheque-whites"
16 /* _UIB-CODE-BLOCK-END */
17 &ANALYZE-RESUME
20 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
22 /* ******************** Preprocessor Definitions ******************** */
24 &Scoped-define PROCEDURE-TYPE SmartViewer
26 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
28 /* Name of first Frame and/or Browse and/or first Query */
29 &Scoped-define FRAME-NAME F-Main
31 /* External Tables */
32 &Scoped-define EXTERNAL-TABLES RP
33 &Scoped-define FIRST-EXTERNAL-TABLE RP
36 /* Need to scope the external tables to this procedure */
37 DEFINE QUERY external_tables FOR RP.
38 /* Standard List Definitions */
39 &Scoped-Define ENABLED-FIELDS RP.Int1 RP.Int2 RP.Log2 RP.Log1
40 &Scoped-define FIELD-PAIRS~
41 ~{&FP1}Int1 ~{&FP2}Int1 ~{&FP3}~
42 ~{&FP1}Int2 ~{&FP2}Int2 ~{&FP3}
43 &Scoped-define ENABLED-TABLES RP
44 &Scoped-define FIRST-ENABLED-TABLE RP
45 &Scoped-Define ENABLED-OBJECTS RECT-22 cmb_bnkact btn_print
46 &Scoped-Define DISPLAYED-FIELDS RP.Int1 RP.Int2 RP.Log2 RP.Log1
47 &Scoped-Define DISPLAYED-OBJECTS cmb_bnkact
49 /* Custom List Definitions */
50 /* ADM-CREATE-FIELDS,ADM-ASSIGN-FIELDS,List-3,List-4,List-5,List-6 */
52 /* _UIB-PREPROCESSOR-BLOCK-END */
53 &ANALYZE-RESUME
57 /* *********************** Control Definitions ********************** */
60 /* Definitions of the field level widgets */
61 DEFINE BUTTON btn_print DEFAULT
62 LABEL "&OK"
63 SIZE 8.57 BY 1
64 FONT 9.
66 DEFINE VARIABLE cmb_bnkact AS CHARACTER FORMAT "X(256)":U
67 LABEL "Bank Account"
68 VIEW-AS COMBO-BOX INNER-LINES 15
69 LIST-ITEMS "",""
70 SIZE 52.57 BY 1 NO-UNDO.
72 DEFINE RECTANGLE RECT-22
73 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
74 SIZE 65.72 BY 6.4.
77 /* ************************ Frame Definitions *********************** */
79 DEFINE FRAME F-Main
80 cmb_bnkact AT ROW 1.2 COL 11.57 COLON-ALIGNED
81 RP.Int1 AT ROW 2.4 COL 11.57 COLON-ALIGNED HELP
83 LABEL "Cheques from" FORMAT ">999999"
84 VIEW-AS FILL-IN
85 SIZE 7.43 BY 1
86 RP.Int2 AT ROW 3.4 COL 11.57 COLON-ALIGNED HELP
88 LABEL "to" FORMAT ">999999"
89 VIEW-AS FILL-IN
90 SIZE 7.43 BY 1
91 RP.Log2 AT ROW 5.2 COL 4.43
92 LABEL "One cheque per page"
93 VIEW-AS TOGGLE-BOX
94 SIZE 20.57 BY .8
95 RP.Log1 AT ROW 6.2 COL 4.43 HELP
97 LABEL "Preview"
98 VIEW-AS TOGGLE-BOX
99 SIZE 9.14 BY .8
100 btn_print AT ROW 6.2 COL 57.57
101 RECT-22 AT ROW 1 COL 1
102 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
103 SIDE-LABELS NO-UNDERLINE THREE-D
104 AT COL 1 ROW 1 SCROLLABLE
105 FONT 10
106 DEFAULT-BUTTON btn_print.
109 /* *********************** Procedure Settings ************************ */
111 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
112 /* Settings for THIS-PROCEDURE
113 Type: SmartViewer
114 External Tables: TTPL.RP
115 Allow: Basic,DB-Fields
116 Frames: 1
117 Add Fields to: EXTERNAL-TABLES
118 Other Settings: PERSISTENT-ONLY COMPILE
121 /* This procedure should always be RUN PERSISTENT. Report the error, */
122 /* then cleanup and return. */
123 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
124 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
125 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
126 RETURN.
127 END.
129 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
131 /* ************************* Create Window ************************** */
133 &ANALYZE-SUSPEND _CREATE-WINDOW
134 /* DESIGN Window definition (used by the UIB)
135 CREATE WINDOW V-table-Win ASSIGN
136 HEIGHT = 8.9
137 WIDTH = 71.57.
138 /* END WINDOW DEFINITION */
140 &ANALYZE-RESUME
143 /* *************** Runtime Attributes and UIB Settings ************** */
145 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
146 /* SETTINGS FOR WINDOW V-table-Win
147 VISIBLE,,RUN-PERSISTENT */
148 /* SETTINGS FOR FRAME F-Main
149 NOT-VISIBLE Size-to-Fit */
150 ASSIGN
151 FRAME F-Main:SCROLLABLE = FALSE
152 FRAME F-Main:HIDDEN = TRUE.
154 /* SETTINGS FOR FILL-IN RP.Int1 IN FRAME F-Main
155 EXP-LABEL EXP-FORMAT EXP-HELP */
156 /* SETTINGS FOR FILL-IN RP.Int2 IN FRAME F-Main
157 EXP-LABEL EXP-FORMAT EXP-HELP */
158 /* SETTINGS FOR TOGGLE-BOX RP.Log1 IN FRAME F-Main
159 EXP-LABEL EXP-HELP */
160 /* SETTINGS FOR Toggle-Box RP.Log2 IN FRAME F-Main
161 EXP-LABEL */
162 /* _RUN-TIME-ATTRIBUTES-END */
163 &ANALYZE-RESUME
166 /* Setting information for Queries and Browse Widgets fields */
168 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
169 /* Query rebuild information for FRAME F-Main
170 _Options = "NO-LOCK"
171 _Query is NOT OPENED
172 */ /* FRAME F-Main */
173 &ANALYZE-RESUME
178 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
179 /* ************************* Included-Libraries *********************** */
181 {src/adm/method/viewer.i}
182 {inc/method/m-mntvwr.i}
184 /* _UIB-CODE-BLOCK-END */
185 &ANALYZE-RESUME
190 /* ************************ Control Triggers ************************ */
192 &Scoped-define SELF-NAME btn_print
193 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL btn_print V-table-Win
194 ON CHOOSE OF btn_print IN FRAME F-Main /* OK */
196 SELF:SENSITIVE = No.
197 RUN run-report.
198 SELF:SENSITIVE = Yes.
200 /* RUN dispatch( 'exit':U ). */
201 END.
203 /* _UIB-CODE-BLOCK-END */
204 &ANALYZE-RESUME
207 &Scoped-define SELF-NAME cmb_bnkact
208 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_bnkact V-table-Win
209 ON U1 OF cmb_bnkact IN FRAME F-Main /* Bank Account */
211 {inc/selcmb/scbnk1.i "RP" "Char2"}
212 END.
214 /* _UIB-CODE-BLOCK-END */
215 &ANALYZE-RESUME
218 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_bnkact V-table-Win
219 ON U2 OF cmb_bnkact IN FRAME F-Main /* Bank Account */
221 {inc/selcmb/scbnk2.i "RP" "Char2"}
222 END.
224 /* _UIB-CODE-BLOCK-END */
225 &ANALYZE-RESUME
228 &UNDEFINE SELF-NAME
230 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
233 /* *************************** Main Block *************************** */
235 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
236 RUN dispatch IN THIS-PROCEDURE ('initialize':U).
237 &ENDIF
239 /************************ INTERNAL PROCEDURES ********************/
241 /* _UIB-CODE-BLOCK-END */
242 &ANALYZE-RESUME
245 /* ********************** Internal Procedures *********************** */
247 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
248 PROCEDURE adm-row-available :
249 /*------------------------------------------------------------------------------
250 Purpose: Dispatched to this procedure when the Record-
251 Source has a new row available. This procedure
252 tries to get the new row (or foriegn keys) from
253 the Record-Source and process it.
254 Parameters: <none>
255 ------------------------------------------------------------------------------*/
257 /* Define variables needed by this internal procedure. */
258 {src/adm/template/row-head.i}
260 /* Create a list of all the tables that we need to get. */
261 {src/adm/template/row-list.i "RP"}
263 /* Get the record ROWID's from the RECORD-SOURCE. */
264 {src/adm/template/row-get.i}
266 /* FIND each record specified by the RECORD-SOURCE. */
267 {src/adm/template/row-find.i "RP"}
269 /* Process the newly available records (i.e. display fields,
270 open queries, and/or pass records on to any RECORD-TARGETS). */
271 {src/adm/template/row-end.i}
273 END PROCEDURE.
275 /* _UIB-CODE-BLOCK-END */
276 &ANALYZE-RESUME
279 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
280 PROCEDURE disable_UI :
281 /*------------------------------------------------------------------------------
282 Purpose: DISABLE the User Interface
283 Parameters: <none>
284 Notes: Here we clean-up the user-interface by deleting
285 dynamic widgets we have created and/or hide
286 frames. This procedure is usually called when
287 we are ready to "clean-up" after running.
288 ------------------------------------------------------------------------------*/
289 /* Hide all frames. */
290 HIDE FRAME F-Main.
291 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
292 END PROCEDURE.
294 /* _UIB-CODE-BLOCK-END */
295 &ANALYZE-RESUME
298 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enable-appropriate-fields V-table-Win
299 PROCEDURE enable-appropriate-fields :
300 /*------------------------------------------------------------------------------
301 Purpose:
302 ------------------------------------------------------------------------------*/
304 END PROCEDURE.
306 /* _UIB-CODE-BLOCK-END */
307 &ANALYZE-RESUME
310 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
311 PROCEDURE inst-initialize :
312 /*------------------------------------------------------------------------------
313 Purpose:
314 ------------------------------------------------------------------------------*/
315 DEF VAR user-name AS CHAR NO-UNDO.
316 {inc/username.i "user-name"}
318 FIND RP WHERE RP.ReportID = {&REPORT-ID} AND RP.UserName = user-name NO-ERROR.
320 IF NOT AVAILABLE RP THEN DO:
321 CREATE RP.
322 ASSIGN RP.ReportID = {&REPORT-ID}
323 RP.UserName = user-name .
324 END.
326 RUN dispatch( 'display-fields':U ).
327 RUN dispatch( 'enable-fields':U ).
328 RUN enable-appropriate-fields.
330 END PROCEDURE.
332 /* _UIB-CODE-BLOCK-END */
333 &ANALYZE-RESUME
336 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
337 PROCEDURE pre-destroy :
338 /*------------------------------------------------------------------------------
339 Purpose:
340 ------------------------------------------------------------------------------*/
342 RUN check-modified( "CLEAR" ).
344 END PROCEDURE.
346 /* _UIB-CODE-BLOCK-END */
347 &ANALYZE-RESUME
350 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE run-report V-table-Win
351 PROCEDURE run-report :
352 /*------------------------------------------------------------------------------
353 Purpose:
354 ------------------------------------------------------------------------------*/
355 DEF VAR report-options AS CHAR NO-UNDO.
357 RUN dispatch( 'update-record':U ).
359 DO WITH FRAME {&FRAME-NAME}:
360 report-options = "~nChequeRange," + RP.Char2 + "," + STRING(RP.Int1) + "," + STRING(RP.Int2)
361 + (IF RP.Log1 THEN "~nPreview" ELSE "")
362 + (IF RP.Log2 THEN "~nOnePerPage" ELSE "") .
364 END.
366 RUN notify( 'set-busy, CONTAINER-SOURCE':U ).
367 RUN process/report/cheque-whites.p ( report-options ).
368 RUN notify( 'set-idle, CONTAINER-SOURCE':U ).
370 END PROCEDURE.
372 /* _UIB-CODE-BLOCK-END */
373 &ANALYZE-RESUME
376 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
377 PROCEDURE send-records :
378 /*------------------------------------------------------------------------------
379 Purpose: Send record ROWID's for all tables used by
380 this file.
381 Parameters: see template/snd-head.i
382 ------------------------------------------------------------------------------*/
384 /* Define variables needed by this internal procedure. */
385 {src/adm/template/snd-head.i}
387 /* For each requested table, put it's ROWID in the output list. */
388 {src/adm/template/snd-list.i "RP"}
390 /* Deal with any unexpected table requests before closing. */
391 {src/adm/template/snd-end.i}
393 END PROCEDURE.
395 /* _UIB-CODE-BLOCK-END */
396 &ANALYZE-RESUME
399 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
400 PROCEDURE state-changed :
401 /* -----------------------------------------------------------
402 Purpose:
403 Parameters: <none>
404 Notes:
405 -------------------------------------------------------------*/
406 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
407 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
409 CASE p-state:
410 /* Object instance CASEs can go here to replace standard behavior
411 or add new cases. */
412 {src/adm/template/vstates.i}
413 END CASE.
414 END PROCEDURE.
416 /* _UIB-CODE-BLOCK-END */
417 &ANALYZE-RESUME