Really, this should be it, for the passing income.
[capital-apms-progress.git] / vwr / mnt / v-impctc.w
bloba01f82c5d86af496cd8178dd775786041d172c3e
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 INITIAL "Andrew" NO-UNDO.
17 &GLOB REPORT-ID "impctc"
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 EXTERNAL-TABLES RP
36 &Scoped-define FIRST-EXTERNAL-TABLE RP
39 /* Need to scope the external tables to this procedure */
40 DEFINE QUERY external_tables FOR RP.
41 /* Standard List Definitions */
42 &Scoped-Define ENABLED-FIELDS RP.Char1
43 &Scoped-define FIELD-PAIRS~
44 ~{&FP1}Char1 ~{&FP2}Char1 ~{&FP3}
45 &Scoped-define ENABLED-TABLES RP
46 &Scoped-define FIRST-ENABLED-TABLE RP
47 &Scoped-Define ENABLED-OBJECTS Btn_Browse Btn_OK
48 &Scoped-Define DISPLAYED-FIELDS RP.Char1
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_Browse
63 LABEL "Browse"
64 SIZE 10 BY 1.05.
66 DEFINE BUTTON Btn_OK AUTO-GO DEFAULT
67 LABEL "OK"
68 SIZE 13.14 BY 1.2
69 BGCOLOR 8 .
72 /* ************************ Frame Definitions *********************** */
74 DEFINE FRAME F-Main
75 RP.Char1 AT ROW 2.6 COL 9.29 COLON-ALIGNED HELP
77 LABEL "Filename" FORMAT "X(100)"
78 VIEW-AS FILL-IN
79 SIZE 49.72 BY 1
80 Btn_Browse AT ROW 2.6 COL 61.57
81 Btn_OK AT ROW 6 COL 58.14
82 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
83 SIDE-LABELS NO-UNDERLINE THREE-D
84 AT COL 1 ROW 1 SCROLLABLE
85 FONT 10
86 DEFAULT-BUTTON Btn_OK.
89 /* *********************** Procedure Settings ************************ */
91 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
92 /* Settings for THIS-PROCEDURE
93 Type: SmartViewer
94 External Tables: ttpl.RP
95 Allow: Basic,DB-Fields
96 Frames: 1
97 Add Fields to: EXTERNAL-TABLES
98 Other Settings: PERSISTENT-ONLY COMPILE
101 /* This procedure should always be RUN PERSISTENT. Report the error, */
102 /* then cleanup and return. */
103 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
104 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
105 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
106 RETURN.
107 END.
109 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
111 /* ************************* Create Window ************************** */
113 &ANALYZE-SUSPEND _CREATE-WINDOW
114 /* DESIGN Window definition (used by the UIB)
115 CREATE WINDOW V-table-Win ASSIGN
116 HEIGHT = 6.3
117 WIDTH = 70.86.
118 /* END WINDOW DEFINITION */
120 &ANALYZE-RESUME
123 /* *************** Runtime Attributes and UIB Settings ************** */
125 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
126 /* SETTINGS FOR WINDOW V-table-Win
127 VISIBLE,,RUN-PERSISTENT */
128 /* SETTINGS FOR FRAME F-Main
129 NOT-VISIBLE Size-to-Fit */
130 ASSIGN
131 FRAME F-Main:SCROLLABLE = FALSE
132 FRAME F-Main:HIDDEN = TRUE.
134 /* _RUN-TIME-ATTRIBUTES-END */
135 &ANALYZE-RESUME
138 /* Setting information for Queries and Browse Widgets fields */
140 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
141 /* Query rebuild information for FRAME F-Main
142 _Options = "NO-LOCK"
143 _Query is NOT OPENED
144 */ /* FRAME F-Main */
145 &ANALYZE-RESUME
150 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
151 /* ************************* Included-Libraries *********************** */
153 {src/adm/method/viewer.i}
154 {inc/method/m-mntvwr.i}
156 /* _UIB-CODE-BLOCK-END */
157 &ANALYZE-RESUME
162 /* ************************ Control Triggers ************************ */
164 &Scoped-define SELF-NAME Btn_Browse
165 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_Browse V-table-Win
166 ON CHOOSE OF Btn_Browse IN FRAME F-Main /* Browse */
168 RUN choose-filename.
169 END.
171 /* _UIB-CODE-BLOCK-END */
172 &ANALYZE-RESUME
175 &Scoped-define SELF-NAME Btn_OK
176 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK V-table-Win
177 ON CHOOSE OF Btn_OK IN FRAME F-Main /* OK */
179 SELF:SENSITIVE = No.
180 RUN run-report.
181 SELF:SENSITIVE = Yes.
183 RUN dispatch ( 'exit':U ).
185 END.
187 /* _UIB-CODE-BLOCK-END */
188 &ANALYZE-RESUME
191 &UNDEFINE SELF-NAME
193 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
196 /* *************************** Main Block *************************** */
198 /* _UIB-CODE-BLOCK-END */
199 &ANALYZE-RESUME
202 /* ********************** Internal Procedures *********************** */
204 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
205 PROCEDURE adm-row-available :
206 /*------------------------------------------------------------------------------
207 Purpose: Dispatched to this procedure when the Record-
208 Source has a new row available. This procedure
209 tries to get the new row (or foriegn keys) from
210 the Record-Source and process it.
211 Parameters: <none>
212 ------------------------------------------------------------------------------*/
214 /* Define variables needed by this internal procedure. */
215 {src/adm/template/row-head.i}
217 /* Create a list of all the tables that we need to get. */
218 {src/adm/template/row-list.i "RP"}
220 /* Get the record ROWID's from the RECORD-SOURCE. */
221 {src/adm/template/row-get.i}
223 /* FIND each record specified by the RECORD-SOURCE. */
224 {src/adm/template/row-find.i "RP"}
226 /* Process the newly available records (i.e. display fields,
227 open queries, and/or pass records on to any RECORD-TARGETS). */
228 {src/adm/template/row-end.i}
230 END PROCEDURE.
232 /* _UIB-CODE-BLOCK-END */
233 &ANALYZE-RESUME
236 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE choose-filename V-table-Win
237 PROCEDURE choose-filename :
238 /*------------------------------------------------------------------------------
239 Purpose:
240 ------------------------------------------------------------------------------*/
241 DEF VAR file-chosen AS LOGICAL INITIAL Yes NO-UNDO.
242 DEF VAR temp-filename AS CHAR NO-UNDO FORMAT "X(200)".
243 DEF VAR directory-string AS CHAR NO-UNDO.
245 temp-filename = INPUT FRAME {&FRAME-NAME} RP.Char1 .
246 directory-string = SUBSTRING( temp-filename, 1, R-INDEX( temp-filename, "\") ).
247 SYSTEM-DIALOG GET-FILE temp-filename
248 FILTERS "Capital APMS import files" "*.TXT", "All files" "*.*"
249 INITIAL-FILTER 1
250 DEFAULT-EXTENSION "*.TXT"
251 INITIAL-DIR directory-string MUST-EXIST
252 RETURN-TO-START-DIR
253 TITLE "Select Contacts Import File" USE-FILENAME
254 UPDATE file-chosen.
256 IF file-chosen THEN DO:
257 RP.Char1:SCREEN-VALUE = temp-filename.
258 END.
260 END PROCEDURE.
262 /* _UIB-CODE-BLOCK-END */
263 &ANALYZE-RESUME
266 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
267 PROCEDURE disable_UI :
268 /*------------------------------------------------------------------------------
269 Purpose: DISABLE the User Interface
270 Parameters: <none>
271 Notes: Here we clean-up the user-interface by deleting
272 dynamic widgets we have created and/or hide
273 frames. This procedure is usually called when
274 we are ready to "clean-up" after running.
275 ------------------------------------------------------------------------------*/
276 /* Hide all frames. */
277 HIDE FRAME F-Main.
278 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
279 END PROCEDURE.
281 /* _UIB-CODE-BLOCK-END */
282 &ANALYZE-RESUME
285 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
286 PROCEDURE inst-initialize :
287 /*------------------------------------------------------------------------------
288 Purpose: Initialise the necessary bits and pieces
289 ------------------------------------------------------------------------------*/
291 RUN get-username IN sec-mgr ( OUTPUT user-name ).
292 FIND RP WHERE RP.ReportID = {&REPORT-ID}
293 AND RP.UserName = user-name
294 NO-ERROR.
296 IF NOT AVAILABLE( RP ) THEN DO:
297 CREATE RP.
298 ASSIGN
299 RP.ReportID = {&REPORT-ID}
300 RP.UserName = user-name
302 END.
304 RUN dispatch ( 'display-fields':U ).
305 RUN dispatch ( 'enable-fields':U ).
307 END PROCEDURE.
309 /* _UIB-CODE-BLOCK-END */
310 &ANALYZE-RESUME
313 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
314 PROCEDURE pre-destroy :
315 /*------------------------------------------------------------------------------
316 Purpose:
317 ------------------------------------------------------------------------------*/
318 RUN check-modified( 'clear':U ).
319 END PROCEDURE.
321 /* _UIB-CODE-BLOCK-END */
322 &ANALYZE-RESUME
325 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE run-report V-table-Win
326 PROCEDURE run-report :
327 /*------------------------------------------------------------------------------
328 Purpose: Actually run the report program.
329 ------------------------------------------------------------------------------*/
330 DEF VAR report-options AS CHAR NO-UNDO.
332 RUN dispatch IN THIS-PROCEDURE ('update-record':U).
334 report-options = "FileName," + RP.Char1 .
336 RUN notify( 'set-busy,container-source':U ).
337 RUN process/import/load-contacts.p ( report-options ).
338 RUN notify( 'set-idle,container-source':U ).
340 END PROCEDURE.
342 /* _UIB-CODE-BLOCK-END */
343 &ANALYZE-RESUME
346 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
347 PROCEDURE send-records :
348 /*------------------------------------------------------------------------------
349 Purpose: Send record ROWID's for all tables used by
350 this file.
351 Parameters: see template/snd-head.i
352 ------------------------------------------------------------------------------*/
354 /* Define variables needed by this internal procedure. */
355 {src/adm/template/snd-head.i}
357 /* For each requested table, put it's ROWID in the output list. */
358 {src/adm/template/snd-list.i "RP"}
360 /* Deal with any unexpected table requests before closing. */
361 {src/adm/template/snd-end.i}
363 END PROCEDURE.
365 /* _UIB-CODE-BLOCK-END */
366 &ANALYZE-RESUME
369 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
370 PROCEDURE state-changed :
371 /* -----------------------------------------------------------
372 Purpose:
373 Parameters: <none>
374 Notes:
375 -------------------------------------------------------------*/
376 DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
377 DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
379 CASE p-state:
380 /* Object instance CASEs can go here to replace standard behavior
381 or add new cases. */
382 {src/adm/template/vstates.i}
383 END CASE.
384 END PROCEDURE.
386 /* _UIB-CODE-BLOCK-END */
387 &ANALYZE-RESUME