1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS V-table-Win
8 /*------------------------------------------------------------------------
9 ------------------------------------------------------------------------*/
13 /* *************************** Definitions
************************** */
15 &SCOPED-DEFINE REPORT-ID "Current Printer"
17 DEF VAR user-name
AS CHAR NO-UNDO.
18 {inc
/username.i
"user-name"}
20 /* _UIB-CODE-BLOCK-END
*/
24 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
26 /* ******************** Preprocessor Definitions
******************** */
28 &Scoped-define PROCEDURE-TYPE SmartViewer
30 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
32 /* Name of first Frame and
/or Browse and
/or first Query
*/
33 &Scoped-define FRAME-NAME F-Main
36 &Scoped-define EXTERNAL-TABLES RP
37 &Scoped-define FIRST-EXTERNAL-TABLE RP
40 /* Need to scope the external tables to this procedure
*/
41 DEFINE QUERY external_tables
FOR RP.
42 /* Standard List Definitions
*/
43 &Scoped-Define ENABLED-OBJECTS RECT-4 btn-select-local btn-select-batch ~
45 &Scoped-Define DISPLAYED-FIELDS RP.Char1 RP.Char2 RP.Char3 RP.Char4
47 /* Custom List Definitions
*/
48 /* ADM-CREATE-FIELDS
,ADM-ASSIGN-FIELDS
,List-3
,List-4
,List-5
,List-6
*/
50 /* _UIB-PREPROCESSOR-BLOCK-END
*/
55 /* *********************** Control Definitions
********************** */
58 /* Definitions of the field level widgets
*/
59 DEFINE BUTTON btn-select-batch
64 DEFINE BUTTON btn-select-local
69 DEFINE BUTTON Btn_OK
AUTO-GO DEFAULT
74 DEFINE RECTANGLE RECT-4
75 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
79 /* ************************ Frame Definitions
*********************** */
82 RP.Char1
AT ROW 2.2 COL 2.15
83 LABEL "Printer" FORMAT "X(50)"
87 RP.Char2
AT ROW 3.4 COL 5.29 COLON-ALIGNED HELP
89 LABEL "On" FORMAT "X(100)"
93 btn-select-local
AT ROW 3.4 COL 49
94 RP.Char3
AT ROW 5.8 COL 2.15
95 LABEL "Printer" FORMAT "X(50)"
99 RP.Char4
AT ROW 7 COL 5.29 COLON-ALIGNED HELP
101 LABEL "On" FORMAT "X(100)"
105 btn-select-batch
AT ROW 7 COL 49
106 Btn_OK
AT ROW 9 COL 45.57
107 RECT-4
AT ROW 1 COL 1
108 "Local Printout" VIEW-AS TEXT
109 SIZE 20 BY 1 AT ROW 1.2 COL 2.14
111 "Batch Printout" VIEW-AS TEXT
112 SIZE 20 BY 1 AT ROW 4.8 COL 2.14
114 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
115 SIDE-LABELS NO-UNDERLINE THREE-D
116 AT COL 1 ROW 1 SCROLLABLE
118 DEFAULT-BUTTON Btn_OK.
121 /* *********************** Procedure Settings
************************ */
123 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
124 /* Settings for
THIS-PROCEDURE
126 External Tables
: TTPL.RP
127 Allow
: Basic
,DB-Fields
129 Add Fields to
: EXTERNAL-TABLES
130 Other Settings
: PERSISTENT-ONLY
COMPILE
133 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
134 /* then cleanup and return.
*/
135 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
136 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
137 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
141 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
143 /* ************************* Create Window
************************** */
145 &ANALYZE-SUSPEND _CREATE-WINDOW
146 /* DESIGN Window definition
(used by the UIB
)
147 CREATE WINDOW V-table-Win
ASSIGN
150 /* END WINDOW DEFINITION
*/
155 /* *************** Runtime Attributes and UIB Settings
************** */
157 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
158 /* SETTINGS
FOR WINDOW V-table-Win
159 VISIBLE,,RUN-PERSISTENT
*/
160 /* SETTINGS
FOR FRAME F-Main
161 NOT-VISIBLE Size-to-Fit
*/
163 FRAME F-Main
:SCROLLABLE = FALSE
164 FRAME F-Main
:HIDDEN = TRUE.
166 /* SETTINGS
FOR FILL-IN RP.Char1
IN FRAME F-Main
167 NO-ENABLE ALIGN-L EXP-LABEL EXP-FORMAT
*/
168 /* SETTINGS
FOR FILL-IN RP.Char2
IN FRAME F-Main
169 NO-ENABLE EXP-LABEL EXP-FORMAT EXP-HELP
*/
170 /* SETTINGS
FOR FILL-IN RP.Char3
IN FRAME F-Main
171 NO-ENABLE ALIGN-L EXP-LABEL EXP-FORMAT
*/
172 /* SETTINGS
FOR FILL-IN RP.Char4
IN FRAME F-Main
173 NO-ENABLE EXP-LABEL EXP-FORMAT EXP-HELP
*/
174 /* _RUN-TIME-ATTRIBUTES-END
*/
178 /* Setting information for Queries and Browse Widgets fields
*/
180 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
181 /* Query rebuild information for
FRAME F-Main
184 */ /* FRAME F-Main
*/
190 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
191 /* ************************* Included-Libraries
*********************** */
193 {src
/adm
/method
/viewer.i
}
194 {inc
/method
/m-mntvwr.i
}
196 /* _UIB-CODE-BLOCK-END
*/
202 /* ************************ Control Triggers
************************ */
204 &Scoped-define SELF-NAME btn-select-batch
205 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL btn-select-batch V-table-Win
206 ON CHOOSE OF btn-select-batch
IN FRAME F-Main
/* Select
*/
208 RUN configure-printer
("Batch").
211 /* _UIB-CODE-BLOCK-END
*/
215 &Scoped-define SELF-NAME btn-select-local
216 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL btn-select-local V-table-Win
217 ON CHOOSE OF btn-select-local
IN FRAME F-Main
/* Select
*/
219 RUN configure-printer
("Local").
222 /* _UIB-CODE-BLOCK-END
*/
226 &Scoped-define SELF-NAME Btn_OK
227 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK V-table-Win
228 ON CHOOSE OF Btn_OK
IN FRAME F-Main
/* OK */
231 RUN dispatch
( 'exit'
:U
).
234 /* _UIB-CODE-BLOCK-END
*/
240 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
243 /* *************************** Main Block
*************************** */
245 &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN
246 RUN dispatch
IN THIS-PROCEDURE ('initialize'
:U
).
249 /************************ INTERNAL PROCEDURES
********************/
251 /* _UIB-CODE-BLOCK-END
*/
255 /* ********************** Internal Procedures
*********************** */
257 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
258 PROCEDURE adm-row-available
:
259 /*------------------------------------------------------------------------------
260 Purpose
: Dispatched to this procedure when the Record-
261 Source has a new row available. This procedure
262 tries to get the new row
(or foriegn keys
) from
263 the Record-Source and process it.
265 ------------------------------------------------------------------------------*/
267 /* Define variables needed by this internal procedure.
*/
268 {src
/adm
/template
/row-head.i
}
270 /* Create a list of all the tables that we need to get.
*/
271 {src
/adm
/template
/row-list.i
"RP"}
273 /* Get the record
ROWID's from the RECORD-SOURCE.
*/
274 {src
/adm
/template
/row-get.i
}
276 /* FIND each record specified by the RECORD-SOURCE.
*/
277 {src
/adm
/template
/row-find.i
"RP"}
279 /* Process the newly available records
(i.e. display fields
,
280 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
281 {src
/adm
/template
/row-end.i
}
285 /* _UIB-CODE-BLOCK-END
*/
289 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE assign-printer V-table-Win
290 PROCEDURE assign-printer
:
291 /*------------------------------------------------------------------------------
293 ------------------------------------------------------------------------------*/
295 FIND RP
WHERE RP.UserName
= user-name
AND RP.ReportID
= {&REPORT-ID} EXCLUSIVE-LOCK NO-ERROR.
297 IF NOT AVAILABLE(RP
) THEN DO:
299 ASSIGN RP.ReportID
= {&REPORT-ID}
300 RP.UserName
= user-name .
302 DO WITH FRAME {&FRAME-NAME}:
303 RP.Char1
= RP.Char1
:SCREEN-VALUE.
304 RP.Char2
= RP.Char2
:SCREEN-VALUE.
305 RP.Char3
= RP.Char3
:SCREEN-VALUE.
306 RP.Char4
= RP.Char4
:SCREEN-VALUE.
309 FIND RP
WHERE RP.UserName
= user-name
AND RP.ReportID
= {&REPORT-ID} NO-LOCK.
313 /* _UIB-CODE-BLOCK-END
*/
317 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE configure-printer V-table-Win
318 PROCEDURE configure-printer
:
319 /*------------------------------------------------------------------------------
321 ------------------------------------------------------------------------------*/
322 DEF INPUT PARAMETER printer-use
AS CHAR NO-UNDO.
324 DEF VAR dlg-ok
AS LOGICAL NO-UNDO INITIAL Yes.
326 DO WITH FRAME {&FRAME-NAME}:
327 SYSTEM-DIALOG PRINTER-SETUP UPDATE dlg-ok.
328 IF printer-use
= "Local" THEN DO:
329 IF dlg-ok
THEN ASSIGN
330 RP.Char1
:SCREEN-VALUE = SESSION:PRINTER-NAME
331 RP.Char2
:SCREEN-VALUE = SESSION:PRINTER-PORT
332 RP.Char2
:SENSITIVE = Yes.
335 IF dlg-ok
THEN ASSIGN
336 RP.Char3
:SCREEN-VALUE = SESSION:PRINTER-NAME
337 RP.Char4
:SCREEN-VALUE = SESSION:PRINTER-PORT.
342 /* _UIB-CODE-BLOCK-END
*/
346 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
347 PROCEDURE disable_UI
:
348 /*------------------------------------------------------------------------------
349 Purpose
: DISABLE the User Interface
351 Notes
: Here we clean-up the user-interface by deleting
352 dynamic widgets we have created and
/or hide
353 frames. This procedure is usually called when
354 we are ready to
"clean-up" after running.
355 ------------------------------------------------------------------------------*/
356 /* Hide all frames.
*/
358 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
361 /* _UIB-CODE-BLOCK-END
*/
365 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
366 PROCEDURE inst-initialize
:
367 /*------------------------------------------------------------------------------
369 ------------------------------------------------------------------------------*/
371 FIND RP
WHERE RP.UserName
= user-name
AND RP.ReportID
= {&REPORT-ID} NO-LOCK NO-ERROR.
373 IF NOT AVAILABLE(RP
) THEN DO TRANSACTION:
375 ASSIGN RP.ReportID
= {&REPORT-ID}
376 RP.UserName
= user-name
377 RP.Char1
= SESSION:PRINTER-NAME
378 RP.Char2
= SESSION:PRINTER-PORT
379 RP.Char3
= SESSION:PRINTER-NAME
380 RP.Char4
= SESSION:PRINTER-PORT .
382 FIND RP
WHERE RP.UserName
= user-name
AND RP.ReportID
= {&REPORT-ID} NO-LOCK NO-ERROR.
384 RUN dispatch
( 'display-fields'
:U
).
386 RP.Char2
:SENSITIVE IN FRAME {&FRAME-NAME} = Yes.
387 RP.Char3
:SENSITIVE IN FRAME {&FRAME-NAME} = Yes.
388 RP.Char4
:SENSITIVE IN FRAME {&FRAME-NAME} = Yes.
389 RP.Char4
:SENSITIVE IN FRAME {&FRAME-NAME} = Yes.
393 /* _UIB-CODE-BLOCK-END
*/
397 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
398 PROCEDURE send-records
:
399 /*------------------------------------------------------------------------------
400 Purpose
: Send record
ROWID's for all tables used by
402 Parameters
: see template
/snd-head.i
403 ------------------------------------------------------------------------------*/
405 /* Define variables needed by this internal procedure.
*/
406 {src
/adm
/template
/snd-head.i
}
408 /* For each requested table
, put it's
ROWID in the output list.
*/
409 {src
/adm
/template
/snd-list.i
"RP"}
411 /* Deal with any unexpected table requests before closing.
*/
412 {src
/adm
/template
/snd-end.i
}
416 /* _UIB-CODE-BLOCK-END
*/
420 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
421 PROCEDURE state-changed
:
422 /* -----------------------------------------------------------
426 -------------------------------------------------------------*/
427 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
428 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
431 /* Object instance CASEs can go here to replace standard behavior
433 {src
/adm
/template
/vstates.i
}
437 /* _UIB-CODE-BLOCK-END
*/