1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
8 /* Temp-Table and Buffer definitions
*/
9 DEFINE TEMP-TABLE Forecast
NO-UNDO LIKE TTPL.CashFlow
10 FIELD FromDate
AS DATE
11 FIELD Periods
AS DEC EXTENT 12.
14 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS B-table-Win
15 /*------------------------------------------------------------------------
19 ------------------------------------------------------------------------*/
23 /* *************************** Definitions
************************** */
26 DEF VAR forecast-start
AS DATE NO-UNDO.
27 DEF VAR period-size
AS CHAR NO-UNDO.
28 DEF VAR parent-type
AS CHAR NO-UNDO INITIAL "".
29 DEF VAR parent-code
AS INT NO-UNDO INITIAL 0.
30 DEF VAR parent-property
AS INT NO-UNDO INITIAL 0.
32 /* _UIB-CODE-BLOCK-END
*/
36 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
38 /* ******************** Preprocessor Definitions
******************** */
40 &Scoped-define PROCEDURE-TYPE SmartBrowser
42 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
44 /* Name of first Frame and
/or Browse and
/or first Query
*/
45 &Scoped-define FRAME-NAME F-Main
46 &Scoped-define BROWSE-NAME br_table
48 /* Internal Tables
(found by Frame
, Query
& Browse Queries) */
49 &Scoped-define INTERNAL-TABLES Forecast
51 /* Define KEY-PHRASE in case it is used by any query.
*/
52 &Scoped-define KEY-PHRASE TRUE
54 /* Definitions for
BROWSE br_table
*/
55 &Scoped-define FIELDS-IN-QUERY-br_table Forecast.Description Forecast.Periods[1] Forecast.Periods[2] Forecast.Periods[3] Forecast.Periods[4] Forecast.Periods[5] Forecast.Periods[6] Forecast.Periods[7] Forecast.Periods[8] Forecast.Periods[9] Forecast.Periods[10] Forecast.Periods[11] Forecast.Periods[12]
56 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table Forecast.Periods[1] Forecast.Periods[2] Forecast.Periods[3] Forecast.Periods[4] Forecast.Periods[5] Forecast.Periods[6] Forecast.Periods[7] Forecast.Periods[8] Forecast.Periods[9] Forecast.Periods[10] Forecast.Periods[11] Forecast.Periods[12]
57 &Scoped-define FIELD-PAIRS-IN-QUERY-br_table~
58 ~
{&FP1}Periods[1] ~{&FP2}Periods[1] ~{&FP3}~
59 ~
{&FP1}Periods[2] ~{&FP2}Periods[2] ~{&FP3}~
60 ~
{&FP1}Periods[3] ~{&FP2}Periods[3] ~{&FP3}~
61 ~
{&FP1}Periods[4] ~{&FP2}Periods[4] ~{&FP3}~
62 ~
{&FP1}Periods[5] ~{&FP2}Periods[5] ~{&FP3}~
63 ~
{&FP1}Periods[6] ~{&FP2}Periods[6] ~{&FP3}~
64 ~
{&FP1}Periods[7] ~{&FP2}Periods[7] ~{&FP3}~
65 ~
{&FP1}Periods[8] ~{&FP2}Periods[8] ~{&FP3}~
66 ~
{&FP1}Periods[9] ~{&FP2}Periods[9] ~{&FP3}~
67 ~
{&FP1}Periods[10] ~{&FP2}Periods[10] ~{&FP3}~
68 ~
{&FP1}Periods[11] ~{&FP2}Periods[11] ~{&FP3}~
69 ~
{&FP1}Periods[12] ~{&FP2}Periods[12] ~{&FP3}
70 &Scoped-define ENABLED-TABLES-IN-QUERY-br_table Forecast
71 &Scoped-define FIRST-ENABLED-TABLE-IN-QUERY-br_table Forecast
72 &Scoped-define SELF-NAME br_table
73 &Scoped-define OPEN-QUERY-br_table OPEN QUERY {&SELF-NAME} FOR EACH Forecast WHERE ~{&KEY-PHRASE} NO-LOCK ~{&SORTBY-PHRASE}.
74 &Scoped-define TABLES-IN-QUERY-br_table Forecast
75 &Scoped-define FIRST-TABLE-IN-QUERY-br_table Forecast
78 /* Definitions for
FRAME F-Main
*/
80 /* Standard List Definitions
*/
81 &Scoped-Define ENABLED-OBJECTS br_table
83 /* Custom List Definitions
*/
84 /* List-1
,List-2
,List-3
,List-4
,List-5
,List-6
*/
86 /* _UIB-PREPROCESSOR-BLOCK-END
*/
90 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE
91 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
99 **************************
100 * Set attributes related to FOREIGN
KEYS
102 RUN set-attribute-list
(
104 Keys-Supplied
= ""'
:U
).
105 /**************************
108 /* _UIB-CODE-BLOCK-END
*/
111 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE
112 /* Actions
: ? adm
/support
/advqedit.w ? ? ?
*/
120 ************************
121 * Set attributes related to SORTBY-OPTIONS
*/
122 RUN set-attribute-list
(
123 'SortBy-Options
= ""'
:U
).
124 /************************
127 </FILTER-ATTRIBUTES
> */
129 /* _UIB-CODE-BLOCK-END
*/
133 /* *********************** Control Definitions
********************** */
136 /* Definitions of the field level widgets
*/
137 /* Query definitions
*/
139 DEFINE QUERY br_table
FOR
143 /* Browse definitions
*/
144 DEFINE BROWSE br_table
145 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _FREEFORM
146 QUERY br_table
NO-LOCK DISPLAY
173 /* _UIB-CODE-BLOCK-END
*/
175 WITH NO-ASSIGN SEPARATORS SIZE 73.14 BY 14.8
179 /* ************************ Frame Definitions
*********************** */
182 br_table
AT ROW 1 COL 1
183 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
184 SIDE-LABELS NO-UNDERLINE THREE-D
185 AT COL 1 ROW 1 SCROLLABLE
186 BGCOLOR 16 FGCOLOR 0 FONT 10.
189 /* *********************** Procedure Settings
************************ */
191 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
192 /* Settings for
THIS-PROCEDURE
196 Add Fields to
: EXTERNAL-TABLES
197 Other Settings
: PERSISTENT-ONLY
COMPILE
198 Temp-Tables and Buffers
:
199 TABLE: Forecast T
"?" NO-UNDO TTPL CashFlow
201 FIELD FromDate
AS DATE
202 FIELD Periods
AS DEC EXTENT 12
207 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
208 /* then cleanup and return.
*/
209 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
210 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT."
211 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
215 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
217 /* ************************* Create Window
************************** */
219 &ANALYZE-SUSPEND _CREATE-WINDOW
220 /* DESIGN Window definition
(used by the UIB
)
221 CREATE WINDOW B-table-Win
ASSIGN
224 /* END WINDOW DEFINITION
*/
229 /* *************** Runtime Attributes and UIB Settings
************** */
231 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
232 /* SETTINGS
FOR WINDOW B-table-Win
233 NOT-VISIBLE
,,RUN-PERSISTENT
*/
234 /* SETTINGS
FOR FRAME F-Main
235 NOT-VISIBLE Size-to-Fit
*/
236 /* BROWSE-TAB br_table
1 F-Main
*/
238 FRAME F-Main
:SCROLLABLE = FALSE
239 FRAME F-Main
:HIDDEN = TRUE.
242 br_table
:NUM-LOCKED-COLUMNS IN FRAME F-Main
= 1.
244 /* _RUN-TIME-ATTRIBUTES-END
*/
248 /* Setting information for Queries and Browse Widgets fields
*/
250 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table
251 /* Query rebuild information for
BROWSE br_table
253 OPEN QUERY {&SELF-NAME} FOR EACH Forecast WHERE ~{&KEY-PHRASE} NO-LOCK
256 _Options
= "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
258 */ /* BROWSE br_table
*/
261 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
262 /* Query rebuild information for
FRAME F-Main
265 */ /* FRAME F-Main
*/
271 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win
272 /* ************************* Included-Libraries
*********************** */
274 {src
/adm
/method
/browser.i
}
275 {inc
/method
/m-drlvwr.i
}
277 /* _UIB-CODE-BLOCK-END
*/
283 /* ************************ Control Triggers
************************ */
285 &Scoped-define BROWSE-NAME br_table
286 &Scoped-define SELF-NAME br_table
287 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
288 ON ROW-ENTRY
OF br_table
IN FRAME F-Main
290 /* This code displays initial values for newly added or copied rows.
*/
291 {src
/adm
/template
/brsentry.i
}
294 /* _UIB-CODE-BLOCK-END
*/
298 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
299 ON ROW-LEAVE
OF br_table
IN FRAME F-Main
301 /* Do not disable this code or no updates will take place except
302 by pressing the Save button on an Update SmartPanel.
*/
303 {src
/adm
/template
/brsleave.i
}
306 /* _UIB-CODE-BLOCK-END
*/
310 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win
311 ON VALUE-CHANGED
OF br_table
IN FRAME F-Main
313 /* This ADM trigger code must be preserved in order to notify other
314 objects when the browser's current row changes.
*/
315 {src
/adm
/template
/brschnge.i
}
318 /* _UIB-CODE-BLOCK-END
*/
324 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win
327 /* *************************** Main Block
*************************** */
329 /* _UIB-CODE-BLOCK-END
*/
333 /* ********************** Internal Procedures
*********************** */
335 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _ADM-ROW-AVAILABLE
336 PROCEDURE adm-row-available
:
337 /*------------------------------------------------------------------------------
338 Purpose
: Dispatched to this procedure when the Record-
339 Source has a new row available. This procedure
340 tries to get the new row
(or foriegn keys
) from
341 the Record-Source and process it.
343 ------------------------------------------------------------------------------*/
345 /* Define variables needed by this internal procedure.
*/
346 {src
/adm
/template
/row-head.i
}
348 /* Process the newly available records
(i.e. display fields
,
349 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
350 {src
/adm
/template
/row-end.i
}
354 /* _UIB-CODE-BLOCK-END
*/
358 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE clear-current-forecast B-table-Win
359 PROCEDURE clear-current-forecast
:
360 /*------------------------------------------------------------------------------
362 ------------------------------------------------------------------------------*/
363 FOR EACH Forecast
: DELETE Forecast.
END.
366 /* _UIB-CODE-BLOCK-END
*/
370 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI B-table-Win _DEFAULT-DISABLE
371 PROCEDURE disable_UI
:
372 /*------------------------------------------------------------------------------
373 Purpose
: DISABLE the User Interface
375 Notes
: Here we clean-up the user-interface by deleting
376 dynamic widgets we have created and
/or hide
377 frames. This procedure is usually called when
378 we are ready to
"clean-up" after running.
379 ------------------------------------------------------------------------------*/
380 /* Hide all frames.
*/
382 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
385 /* _UIB-CODE-BLOCK-END
*/
389 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE forecast-for-area B-table-Win
390 PROCEDURE forecast-for-area
:
391 /*------------------------------------------------------------------------------
393 ------------------------------------------------------------------------------*/
394 DEF INPUT PARAMETER new-records
AS LOGI
NO-UNDO.
395 DEF INPUT PARAMETER property-code
AS INT NO-UNDO.
396 DEF INPUT PARAMETER fc-for
AS INT NO-UNDO.
398 IF NOT AVAILABLE(Property
) THEN
399 FIND Property
WHERE Property.PropertyCode
= property-code
NO-LOCK NO-ERROR.
400 IF NOT AVAILABLE(Property
) THEN RETURN.
402 FIND RentalSpace
OF Property
WHERE RentalSpace.RentalSpaceCode
= fc-for
NO-LOCK.
403 IF NOT AVAILABLE(RentalSpace
) THEN RETURN.
405 IF new-records
THEN CREATE Forecast.
406 Forecast.Description
= RentalSpace.Description .
408 /* now we're fucked
, aren't we?
! */
412 /* _UIB-CODE-BLOCK-END
*/
416 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE forecast-for-lease B-table-Win
417 PROCEDURE forecast-for-lease
:
418 /*------------------------------------------------------------------------------
420 ------------------------------------------------------------------------------*/
421 DEF INPUT PARAMETER new-records
AS LOGI
NO-UNDO.
422 DEF INPUT PARAMETER fc-for
AS INT NO-UNDO.
424 FIND TenancyLease
WHERE TenancyLease.TenancyLeaseCode
= fc-for
NO-LOCK NO-ERROR.
425 IF NOT AVAILABLE(TenancyLease
) THEN RETURN.
426 FIND Tenant
WHERE Tenant.TenantCode
= TenancyLease.TenantCode
NO-LOCK NO-ERROR.
427 IF NOT AVAILABLE(Tenant
) THEN RETURN.
429 IF NOT AVAILABLE(Property
) THEN
430 FIND Property
WHERE Property.PropertyCode
= TenancyLease.PropertyCode
NO-LOCK NO-ERROR.
431 IF NOT AVAILABLE(Property
) THEN RETURN.
433 DEF BUFFER tmp_Space
FOR RentalSpace.
434 FOR EACH tmp_Space
NO-LOCK OF TenancyLease
WHERE tmp_Space.AreaStatus
<> "X":
435 IF new-records
THEN CREATE Forecast.
436 Forecast.Description
= RentalSpace.Description .
437 RUN forecast-for-area
( no
, tmp_Space.PropertyCode
, tmp_Space.RentalSpaceCode
).
442 /* _UIB-CODE-BLOCK-END
*/
446 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE forecast-for-property B-table-Win
447 PROCEDURE forecast-for-property
:
448 /*------------------------------------------------------------------------------
450 ------------------------------------------------------------------------------*/
451 DEF INPUT PARAMETER new-records
AS LOGI
NO-UNDO.
452 DEF INPUT PARAMETER fc-for
AS INT NO-UNDO.
454 FIND Property
WHERE Property.PropertyCode
= fc-for
NO-LOCK NO-ERROR.
455 IF NOT AVAILABLE(Property
) THEN RETURN.
457 DEF BUFFER tmp_Lease
FOR TenancyLease.
458 FOR EACH tmp_Lease
NO-LOCK OF Property
WHERE tmp_Lease.LeaseStatus
<> "PAST":
460 Forecast.Description
= TenancyLease.AreaDescription.
461 RUN forecast-for-lease
( no
, tmp_Lease.TenancyLeaseCode
).
464 DEF BUFFER tmp_Space
FOR RentalSpace.
465 FOR EACH tmp_Space
NO-LOCK OF Property
WHERE tmp_Space.AreaStatus
= "V":
467 Forecast.Description
= "Vacant: " + RentalSpace.Description.
468 RUN forecast-for-area
( no
, tmp_Space.PropertyCode
, tmp_Space.RentalSpaceCode
).
473 /* _UIB-CODE-BLOCK-END
*/
477 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE forecast-for-tenant B-table-Win
478 PROCEDURE forecast-for-tenant
:
479 /*------------------------------------------------------------------------------
481 ------------------------------------------------------------------------------*/
482 DEF INPUT PARAMETER new-records
AS LOGI
NO-UNDO.
483 DEF INPUT PARAMETER fc-for
AS INT NO-UNDO.
485 FIND Tenant
WHERE Tenant.TenantCode
= fc-for
NO-LOCK NO-ERROR.
486 IF NOT AVAILABLE(Tenant
) OR Tenant.EntityType
<> "P" THEN RETURN.
488 IF NOT AVAILABLE(Property
) THEN
489 FIND Property
WHERE Property.PropertyCode
= Tenant.EntityCode
NO-LOCK NO-ERROR.
490 IF NOT AVAILABLE(Property
) THEN RETURN.
492 DEF BUFFER tmp_Space
FOR RentalSpace.
493 FOR EACH TenancyLease
NO-LOCK OF Tenant
,
494 EACH tmp_Space
NO-LOCK OF TenancyLease
WHERE tmp_Space.AreaStatus
<> "X":
495 IF new-records
THEN CREATE Forecast.
496 Forecast.Description
= RentalSpace.Description .
497 RUN forecast-for-area
( no
, tmp_Space.PropertyCode
, tmp_Space.RentalSpaceCode
).
502 /* _UIB-CODE-BLOCK-END
*/
506 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-open-query B-table-Win
507 PROCEDURE pre-open-query
:
508 /*------------------------------------------------------------------------------
510 ------------------------------------------------------------------------------*/
511 RUN rebuild-forecast.
514 /* _UIB-CODE-BLOCK-END
*/
518 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE rebuild-forecast B-table-Win
519 PROCEDURE rebuild-forecast
:
520 /*------------------------------------------------------------------------------
522 ------------------------------------------------------------------------------*/
523 RUN clear-current-forecast.
525 WHEN "Property" THEN RUN forecast-for-property
( yes
, parent-code
).
526 WHEN "Lease" THEN RUN forecast-for-lease
( yes
, parent-code
).
527 WHEN "Tenant" THEN RUN forecast-for-tenant
( yes
, parent-code
).
528 WHEN "RentalSpace" THEN RUN forecast-for-area
( yes
, parent-property
, parent-code
).
529 OTHERWISE MESSAGE parent-type
"not implemented yet.".
534 /* _UIB-CODE-BLOCK-END
*/
538 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _ADM-SEND-RECORDS
539 PROCEDURE send-records
:
540 /*------------------------------------------------------------------------------
541 Purpose
: Send record
ROWID's for all tables used by
543 Parameters
: see template
/snd-head.i
544 ------------------------------------------------------------------------------*/
546 /* Define variables needed by this internal procedure.
*/
547 {src
/adm
/template
/snd-head.i
}
549 /* For each requested table
, put it's
ROWID in the output list.
*/
550 {src
/adm
/template
/snd-list.i
"Forecast"}
552 /* Deal with any unexpected table requests before closing.
*/
553 {src
/adm
/template
/snd-end.i
}
557 /* _UIB-CODE-BLOCK-END
*/
561 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed B-table-Win
562 PROCEDURE state-changed
:
563 /* -----------------------------------------------------------
567 -------------------------------------------------------------*/
568 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
569 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
572 /* Object instance CASEs can go here to replace standard behavior
574 {src
/adm
/template
/bstates.i
}
578 /* _UIB-CODE-BLOCK-END
*/
582 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-forecast-start B-table-Win
583 PROCEDURE use-forecast-start
:
584 /*------------------------------------------------------------------------------
586 ------------------------------------------------------------------------------*/
587 DEF VAR new-start
AS CHAR NO-UNDO.
588 forecast-start
= DATE(new-start
).
591 /* _UIB-CODE-BLOCK-END
*/
595 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-Key-Name B-table-Win
596 PROCEDURE use-Key-Name
:
597 /*------------------------------------------------------------------------------
599 ------------------------------------------------------------------------------*/
600 DEF INPUT PARAMETER new-key-name
AS CHAR NO-UNDO.
601 parent-type
= new-key-name.
604 /* _UIB-CODE-BLOCK-END
*/
608 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-parent-code B-table-Win
609 PROCEDURE use-parent-code
:
610 /*------------------------------------------------------------------------------
612 ------------------------------------------------------------------------------*/
613 DEF VAR new-code
AS CHAR NO-UNDO.
614 parent-code
= INT(new-code
).
617 /* _UIB-CODE-BLOCK-END
*/
621 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-parent-property B-table-Win
622 PROCEDURE use-parent-property
:
623 /*------------------------------------------------------------------------------
625 ------------------------------------------------------------------------------*/
626 DEF VAR new-property
AS CHAR NO-UNDO.
627 parent-property
= INT(new-property
).
630 /* _UIB-CODE-BLOCK-END
*/
634 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-Parent-Type B-table-Win
635 PROCEDURE use-Parent-Type
:
636 /*------------------------------------------------------------------------------
638 ------------------------------------------------------------------------------*/
639 DEF VAR new-type
AS CHAR NO-UNDO.
640 parent-type
= new-type.
643 /* _UIB-CODE-BLOCK-END
*/
647 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE use-period-size B-table-Win
648 PROCEDURE use-period-size
:
649 /*------------------------------------------------------------------------------
651 ------------------------------------------------------------------------------*/
652 DEF VAR new-size
AS CHAR NO-UNDO.
653 period-size
= new-size.
656 /* _UIB-CODE-BLOCK-END
*/