Changes for Catalyst APMS. Added PDF checkboxes to screens the generate remittance...
[capital-apms-progress.git] / vwr / mnt / v-rntsum.w
blob1b1a3fd0631a65934ae26d276f1b300450306be9
1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r2 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 INITIAL "Andrew" NO-UNDO.
17 &GLOB REPORT-ID "rntsum"
19 /* _UIB-CODE-BLOCK-END */
20 &ANALYZE-RESUME
23 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
25 /* ******************** Preprocessor Definitions ******************** */
27 &Scoped-define PROCEDURE-TYPE SmartViewer
29 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
31 /* Name of first Frame and/or Browse and/or first Query */
32 &Scoped-define FRAME-NAME F-Main
34 /* External Tables */
35 &Scoped-define FIRST-EXTERNAL-TABLE RP
36 &Scoped-define EXTERNAL-TABLES RP
37 /* Need to scope the external tables to this procedure */
38 DEFINE QUERY external_tables FOR RP.
40 /* Standard List Definitions */
41 &Scoped-Define ENABLED-FIELDS RP.Char1 RP.Char2 RP.Char3 RP.Log1
42 &Scoped-define FIELD-PAIRS
43 &Scoped-Define ENABLED-TABLES RP
44 &Scoped-Define ENABLED-OBJECTS RECT-1 Btn_OK
45 &Scoped-Define DISPLAYED-FIELDS RP.Char1 RP.Char2 RP.Char3 RP.Log1
47 /* Custom List Definitions */
48 /* ADM-CREATE-FIELDS,ADM-ASSIGN-FIELDS,List-3,List-4,List-5,List-6 */
50 /* _UIB-PREPROCESSOR-BLOCK-END */
51 &ANALYZE-RESUME
55 /* *********************** Control Definitions ********************** */
58 /* Definitions of the field level widgets */
59 DEFINE BUTTON Btn_OK AUTO-GO DEFAULT
60 LABEL "OK"
61 SIZE 12 BY 1.2
62 BGCOLOR 8 .
64 DEFINE RECTANGLE RECT-1
65 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
66 SIZE 46.29 BY 10.4.
69 /* ************************ Frame Definitions *********************** */
71 DEFINE FRAME F-Main
72 RP.Char1 AT ROW 1.2 COL 5 HELP
73 "" NO-LABEL
74 VIEW-AS RADIO-SET VERTICAL
75 RADIO-BUTTONS
76 "Rental", "R",
77 "Outgoings", "O"
78 SIZE 13.14 BY 1.8
79 FONT 10
80 RP.Char2 AT ROW 3.8 COL 5 HELP
81 "" NO-LABEL
82 VIEW-AS RADIO-SET VERTICAL
83 RADIO-BUTTONS
84 "Summary", "S",
85 "Detail", "D"
86 SIZE 12 BY 1.8
87 FONT 10
88 RP.Char3 AT ROW 6.4 COL 5 HELP
89 "" NO-LABEL
90 VIEW-AS RADIO-SET VERTICAL
91 RADIO-BUTTONS
92 "Include externally managed properties", "I",
93 "Exclude externally managed properties", "X"
94 SIZE 33.72 BY 1.8
95 FONT 10
96 RP.Log1 AT ROW 10 COL 10.14
97 LABEL "Preview"
98 VIEW-AS TOGGLE-BOX
99 SIZE 17.72 BY 1
100 FONT 10
101 Btn_OK AT ROW 10 COL 34.86
102 RECT-1 AT ROW 1 COL 1
103 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
104 SIDE-LABELS NO-UNDERLINE THREE-D
105 AT COL 1 ROW 1 SCROLLABLE
106 DEFAULT-BUTTON Btn_OK.
110 /* *********************** Procedure Settings ************************ */
112 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
113 /* Settings for THIS-PROCEDURE
114 Type: SmartViewer
115 External Tables: ttpl.RP
116 Allow: Basic,DB-Fields
117 Frames: 1
118 Add Fields to: EXTERNAL-TABLES
119 Other Settings: PERSISTENT-ONLY COMPILE
122 /* This procedure should always be RUN PERSISTENT. Report the error, */
123 /* then cleanup and return. */
124 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
125 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
126 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
127 RETURN.
128 END.
130 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
132 /* ************************* Create Window ************************** */
134 &ANALYZE-SUSPEND _CREATE-WINDOW
135 /* DESIGN Window definition (used by the UIB)
136 CREATE WINDOW V-table-Win ASSIGN
137 HEIGHT = 12.75
138 WIDTH = 55.57.
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 RADIO-SET RP.Char1 IN FRAME F-Main
155 EXP-HELP */
156 /* SETTINGS FOR RADIO-SET RP.Char2 IN FRAME F-Main
157 EXP-HELP */
158 /* SETTINGS FOR RADIO-SET RP.Char3 IN FRAME F-Main
159 EXP-HELP */
160 /* SETTINGS FOR TOGGLE-BOX RP.Log1 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_OK
193 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK V-table-Win
194 ON CHOOSE OF Btn_OK IN FRAME F-Main /* OK */
196 RUN run-report.
197 END.
199 /* _UIB-CODE-BLOCK-END */
200 &ANALYZE-RESUME
203 &UNDEFINE SELF-NAME
205 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
208 /* *************************** Main Block *************************** */
210 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
211 RUN dispatch IN THIS-PROCEDURE ('initialize':U).
212 &ENDIF
214 /************************ INTERNAL PROCEDURES ********************/
216 /* _UIB-CODE-BLOCK-END */
217 &ANALYZE-RESUME
220 /* ********************** Internal Procedures *********************** */
222 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
223 PROCEDURE adm-row-available :
224 /*------------------------------------------------------------------------------
225 Purpose: Dispatched to this procedure when the record-
226 source has a new row available. This procedure
227 tries to get the new row and display it.
228 Parameters: <none>
229 ------------------------------------------------------------------------------*/
231 /* Define variables needed by this internal procedure. */
232 {src/adm/template/row-head.i}
234 /* Create a list of all the tables that we need to get. */
235 {src/adm/template/row-list.i "RP"}
237 /* Get the record ROWID's from the RECORD-SOURCE. */
238 {src/adm/template/row-get.i}
240 /* FIND each record specified by the RECORD-SOURCE. */
241 {src/adm/template/row-find.i "RP"}
243 /* Process the newly available records (i.e. display fields,
244 open queries, and/or pass records on to any RECORD-TARGETS). */
245 {src/adm/template/row-end.i}
247 END PROCEDURE.
249 /* _UIB-CODE-BLOCK-END */
250 &ANALYZE-RESUME
253 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
254 PROCEDURE disable_UI :
255 /*------------------------------------------------------------------------------
256 Purpose: DISABLE the User Interface
257 Parameters: <none>
258 Notes: Here we clean-up the user-interface by deleting
259 dynamic widgets we have created and/or hide
260 frames. This procedure is usually called when
261 we are ready to "clean-up" after running.
262 ------------------------------------------------------------------------------*/
263 /* Hide all frames. */
264 HIDE FRAME F-Main.
265 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
266 END PROCEDURE.
268 /* _UIB-CODE-BLOCK-END */
269 &ANALYZE-RESUME
272 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enable-appropriate-fields V-table-Win
273 PROCEDURE enable-appropriate-fields :
274 /*------------------------------------------------------------------------------
275 Purpose: As its name!
276 ------------------------------------------------------------------------------*/
278 DO WITH FRAME {&FRAME-NAME}:
279 /* not required */
280 END.
282 END PROCEDURE.
284 /* _UIB-CODE-BLOCK-END */
285 &ANALYZE-RESUME
288 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
289 PROCEDURE inst-initialize :
290 /*------------------------------------------------------------------------------
291 Purpose: Initialise the necessary bits and pieces
292 ------------------------------------------------------------------------------*/
294 RUN get-username IN sec-mgr ( OUTPUT user-name ).
295 FIND RP WHERE RP.ReportID = {&REPORT-ID}
296 AND RP.UserName = user-name
297 NO-ERROR.
299 IF NOT AVAILABLE( RP ) THEN DO:
300 CREATE RP.
301 ASSIGN
302 RP.ReportID = {&REPORT-ID}
303 RP.UserName = user-name
305 END.
307 RUN dispatch ( 'display-fields':U ).
308 RUN dispatch ( 'enable-fields':U ).
309 RUN enable-appropriate-fields.
311 END PROCEDURE.
313 /* _UIB-CODE-BLOCK-END */
314 &ANALYZE-RESUME
317 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
318 PROCEDURE pre-destroy :
319 /*------------------------------------------------------------------------------
320 Purpose:
321 ------------------------------------------------------------------------------*/
322 RUN check-modified( 'clear':U ).
323 END PROCEDURE.
325 /* _UIB-CODE-BLOCK-END */
326 &ANALYZE-RESUME
329 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE run-report V-table-Win
330 PROCEDURE run-report :
331 /*------------------------------------------------------------------------------
332 Purpose: Actually run the report program.
333 ------------------------------------------------------------------------------*/
334 DEF VAR c-win AS HANDLE NO-UNDO.
335 DEF VAR report-options AS CHAR NO-UNDO.
337 c-win = CURRENT-WINDOW.
338 IF c-win:LOAD-MOUSE-POINTER("WAIT":U ) THEN .
339 DISABLE Btn_OK WITH FRAME {&FRAME-NAME}.
340 DO TRANSACTION:
341 RUN dispatch IN THIS-PROCEDURE ('update-record':U).
342 END.
344 report-options = RP.Char1 + RP.Char2 + RP.Char3.
345 RUN process/report/rentsum.p ( report-options,
346 RP.Log1 /* preview */
348 ENABLE Btn_OK WITH FRAME {&FRAME-NAME}.
349 IF c-win:LOAD-MOUSE-POINTER("ARROW":U ) THEN .
351 END PROCEDURE.
353 /* _UIB-CODE-BLOCK-END */
354 &ANALYZE-RESUME
357 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
358 PROCEDURE send-records :
359 /*------------------------------------------------------------------------------
360 Purpose: Send record ROWID's for all tables used by
361 this file.
362 Parameters: see template/snd-head.i
363 ------------------------------------------------------------------------------*/
365 /* Define variables needed by this internal procedure. */
366 {src/adm/template/snd-head.i}
368 /* For each requested table, put it's ROWID in the output list. */
369 {src/adm/template/snd-list.i "RP"}
371 /* Deal with any unexpected table requests before closing. */
372 {src/adm/template/snd-end.i}
374 END PROCEDURE.
376 /* _UIB-CODE-BLOCK-END */
377 &ANALYZE-RESUME
380 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
381 PROCEDURE state-changed :
382 /* -----------------------------------------------------------
383 Purpose:
384 Parameters: <none>
385 Notes:
386 -------------------------------------------------------------*/
387 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
388 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
390 CASE p-state:
391 /* Object instance CASEs can go here to replace standard behavior
392 or add new cases. */
393 {src/adm/template/vstates.i}
394 END CASE.
395 END PROCEDURE.
397 /* _UIB-CODE-BLOCK-END */
398 &ANALYZE-RESUME