1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI ADM1
6 &Scoped-define WINDOW-NAME CURRENT-WINDOW
7 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS V-table-Win
8 /*------------------------------------------------------------------------
12 Description
: from VIEWER.W
- Template for SmartViewer Objects
20 ------------------------------------------------------------------------*/
21 /* This .W file was created with the Progress UIB.
*/
22 /*----------------------------------------------------------------------*/
24 /* Create an unnamed pool to store all the widgets created
25 by this procedure. This is a good default which assures
26 that this procedure's triggers and internal procedures
27 will execute in this procedure's storage
, and that proper
28 cleanup will occur on deletion of the procedure.
*/
32 /* *************************** Definitions
************************** */
34 /* Parameters Definitions
--- */
36 /* Local Variable Definitions
--- */
38 DEF TEMP-TABLE PrjCashFlow
NO-UNDO
39 FIELD YearCode
LIKE FinancialYear.FinancialYearCode
40 FIELD MonthCode
LIKE Month.MonthCode
41 FIELD MonthEnd
LIKE Month.EndDate
42 FIELD MonthName
LIKE Month.MonthName
43 FIELD Balance
LIKE AccountBalance.Balance
44 FIELD Budget
LIKE AccountBalance.Budget
45 FIELD Revised
LIKE AccountBalance.Revised
47 INDEX Month
IS UNIQUE PRIMARY
54 DEF VAR this-win
AS HANDLE NO-UNDO.
55 DEF VAR very-first-month
LIKE Month.MonthCode
NO-UNDO.
56 DEF VAR very-first-year
LIKE FinancialYear.FinancialYearCode
NO-UNDO.
58 /* _UIB-CODE-BLOCK-END
*/
62 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
64 /* ******************** Preprocessor Definitions
******************** */
66 &Scoped-define PROCEDURE-TYPE SmartViewer
67 &Scoped-define DB-AWARE no
69 &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target
71 /* Name of first Frame and
/or Browse and
/or first Query
*/
72 &Scoped-define FRAME-NAME F-Main
73 &Scoped-define BROWSE-NAME BROWSE-1
76 &Scoped-define EXTERNAL-TABLES ProjectBudget
77 &Scoped-define FIRST-EXTERNAL-TABLE ProjectBudget
80 /* Need to scope the external tables to this procedure
*/
81 DEFINE QUERY external_tables
FOR ProjectBudget.
82 /* Internal Tables
(found by Frame
, Query
& Browse Queries) */
83 &Scoped-define INTERNAL-TABLES PrjCashFlow
85 /* Definitions for
BROWSE BROWSE-1
*/
86 &Scoped-define FIELDS-IN-QUERY-BROWSE-1 PrjCashFlow.MonthName PrjCashFlow.Balance PrjCashFlow.Budget PrjCashFlow.Revised
87 &Scoped-define ENABLED-FIELDS-IN-QUERY-BROWSE-1 PrjCashFlow.Revised
88 &Scoped-define ENABLED-TABLES-IN-QUERY-BROWSE-1 PrjCashFlow
89 &Scoped-define FIRST-ENABLED-TABLE-IN-QUERY-BROWSE-1 PrjCashFlow
90 &Scoped-define SELF-NAME BROWSE-1
91 &Scoped-define OPEN-QUERY-BROWSE-1 OPEN QUERY {&SELF-NAME} FOR EACH PrjCashFlow NO-LOCK.
92 &Scoped-define TABLES-IN-QUERY-BROWSE-1 PrjCashFlow
93 &Scoped-define FIRST-TABLE-IN-QUERY-BROWSE-1 PrjCashFlow
96 /* Definitions for
FRAME F-Main
*/
98 /* Standard List Definitions
*/
99 &Scoped-Define ENABLED-OBJECTS cmb_Years tgl_topmost BROWSE-1 RECT-1
100 &Scoped-Define DISPLAYED-OBJECTS cmb_Years tgl_topmost
102 /* Custom List Definitions
*/
103 /* ADM-CREATE-FIELDS
,ADM-ASSIGN-FIELDS
,List-3
,List-4
,List-5
,List-6
*/
105 /* _UIB-PREPROCESSOR-BLOCK-END
*/
109 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" V-table-Win _INLINE
110 /* Actions
: ? adm
/support
/keyedit.w ? ? ?
*/
116 AccountCode|y|y|TTPL.ProjectBudget.AccountCode
117 EntityCode|y|y|TTPL.ProjectBudget.EntityCode
118 EntityType|y|y|TTPL.ProjectBudget.EntityType
121 **************************
122 * Set attributes related to FOREIGN
KEYS
124 RUN set-attribute-list
(
125 'Keys-Accepted
= "AccountCode,EntityCode,EntityType",
126 Keys-Supplied
= "AccountCode,EntityCode,EntityType"'
:U
).
127 /**************************
129 /* _UIB-CODE-BLOCK-END
*/
133 /* *********************** Control Definitions
********************** */
136 /* Definitions of the field level widgets
*/
137 DEFINE VARIABLE cmb_Years
AS CHARACTER FORMAT "X(256)":U
138 VIEW-AS COMBO-BOX INNER-LINES 10
143 DEFINE RECTANGLE RECT-1
144 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
147 DEFINE VARIABLE tgl_topmost
AS LOGICAL INITIAL no
153 /* Query definitions
*/
155 DEFINE QUERY BROWSE-1
FOR
156 PrjCashFlow
SCROLLING.
159 /* Browse definitions
*/
160 DEFINE BROWSE BROWSE-1
161 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS BROWSE-1 V-table-Win _FREEFORM
162 QUERY BROWSE-1
NO-LOCK DISPLAY
163 PrjCashFlow.MonthName
FORMAT "X(3)" LABEL "Mth"
169 /* _UIB-CODE-BLOCK-END
*/
171 WITH NO-ROW-MARKERS SEPARATORS SIZE 64.14 BY 10
172 BGCOLOR 15 FGCOLOR 1 FONT 8.
175 /* ************************ Frame Definitions
*********************** */
178 cmb_Years
AT ROW 1.35 COL 4.72 COLON-ALIGNED NO-LABEL
179 tgl_topmost
AT ROW 1.5 COL 56
180 BROWSE-1
AT ROW 2.65 COL 1.86
181 RECT-1
AT ROW 1 COL 1
183 SIZE 4 BY 1 AT ROW 1.35 COL 2.14
185 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
186 SIDE-LABELS NO-UNDERLINE THREE-D
187 AT COL 1 ROW 1 SCROLLABLE .
190 /* *********************** Procedure Settings
************************ */
192 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
193 /* Settings for
THIS-PROCEDURE
195 External Tables
: TTPL.ProjectBudget
196 Allow
: Basic
,DB-Fields
198 Add Fields to
: EXTERNAL-TABLES
199 Other Settings
: PERSISTENT-ONLY
COMPILE
202 /* This procedure should always be
RUN PERSISTENT. Report the error
, */
203 /* then cleanup and return.
*/
204 IF NOT THIS-PROCEDURE:PERSISTENT THEN DO:
205 MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT.":U
206 VIEW-AS ALERT-BOX ERROR BUTTONS OK.
210 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
212 /* ************************* Create Window
************************** */
214 &ANALYZE-SUSPEND _CREATE-WINDOW
215 /* DESIGN Window definition
(used by the UIB
)
216 CREATE WINDOW V-table-Win
ASSIGN
219 /* END WINDOW DEFINITION
*/
223 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB V-table-Win
224 /* ************************* Included-Libraries
*********************** */
226 {src
/adm
/method
/viewer.i
}
227 {inc
/method
/m-mntvwr.i
}
229 /* _UIB-CODE-BLOCK-END
*/
235 /* *********** Runtime Attributes and AppBuilder Settings
*********** */
237 &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
238 /* SETTINGS
FOR WINDOW V-table-Win
239 VISIBLE,,RUN-PERSISTENT
*/
240 /* SETTINGS
FOR FRAME F-Main
241 NOT-VISIBLE Size-to-Fit
*/
242 /* BROWSE-TAB BROWSE-1 tgl_topmost F-Main
*/
244 FRAME F-Main
:SCROLLABLE = FALSE
245 FRAME F-Main
:HIDDEN = TRUE.
247 /* _RUN-TIME-ATTRIBUTES-END
*/
251 /* Setting information for Queries and Browse Widgets fields
*/
253 &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE BROWSE-1
254 /* Query rebuild information for
BROWSE BROWSE-1
256 OPEN QUERY {&SELF-NAME} FOR EACH PrjCashFlow NO-LOCK.
260 */ /* BROWSE BROWSE-1
*/
263 &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main
264 /* Query rebuild information for
FRAME F-Main
267 */ /* FRAME F-Main
*/
274 /* ************************ Control Triggers
************************ */
276 &Scoped-define SELF-NAME cmb_Years
277 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL cmb_Years V-table-Win
278 ON VALUE-CHANGED
OF cmb_Years
IN FRAME F-Main
280 RUN assign-cash-flows.
284 /* _UIB-CODE-BLOCK-END
*/
288 &Scoped-define SELF-NAME tgl_topmost
289 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL tgl_topmost V-table-Win
290 ON VALUE-CHANGED
OF tgl_topmost
IN FRAME F-Main
/* On Top?
*/
295 /* _UIB-CODE-BLOCK-END
*/
299 &Scoped-define BROWSE-NAME BROWSE-1
302 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK V-table-Win
305 /* *************************** Main Block
*************************** */
308 /* Triggers for cash flows
*/
310 ON '
LEAVE'
:U
OF PrjCashFlow.Revised
315 /* _UIB-CODE-BLOCK-END
*/
319 /* ********************** Internal Procedures
*********************** */
321 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-find-using-key V-table-Win adm/support/_key-fnd.p
322 PROCEDURE adm-find-using-key
:
323 /*------------------------------------------------------------------------------
324 Purpose
: Finds the current record using the contents of
325 the 'Key-Name' and 'Key-Value' attributes.
327 ------------------------------------------------------------------------------*/
328 DEF VAR key-value
AS CHAR NO-UNDO.
329 DEF VAR row-avail-enabled
AS LOGICAL NO-UNDO.
331 /* LOCK status on the find depends on FIELDS-ENABLED.
*/
332 RUN get-attribute
('FIELDS-ENABLED'
:U
).
333 row-avail-enabled
= (RETURN-VALUE eq 'yes'
:U
).
334 /* Look up the current key-value.
*/
335 RUN get-attribute
('Key-Value'
:U
).
336 key-value
= RETURN-VALUE.
338 /* Find the current record using the current Key-Name.
*/
339 RUN get-attribute
('Key-Name'
:U
).
341 WHEN 'AccountCode'
:U
THEN
342 {src
/adm
/template
/find-tbl.i
343 &TABLE = ProjectBudget
344 &WHERE = "WHERE ProjectBudget.AccountCode eq DECIMAL(key-value)"
346 WHEN 'EntityCode'
:U
THEN
347 {src
/adm
/template
/find-tbl.i
348 &TABLE = ProjectBudget
349 &WHERE = "WHERE ProjectBudget.EntityCode eq INTEGER(key-value)"
351 WHEN 'EntityType'
:U
THEN
352 {src
/adm
/template
/find-tbl.i
353 &TABLE = ProjectBudget
354 &WHERE = "WHERE ProjectBudget.EntityType eq key-value"
360 /* _UIB-CODE-BLOCK-END
*/
363 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available V-table-Win _ADM-ROW-AVAILABLE
364 PROCEDURE adm-row-available
:
365 /*------------------------------------------------------------------------------
366 Purpose
: Dispatched to this procedure when the Record-
367 Source has a new row available. This procedure
368 tries to get the new row
(or foriegn keys
) from
369 the Record-Source and process it.
371 ------------------------------------------------------------------------------*/
373 /* Define variables needed by this internal procedure.
*/
374 {src
/adm
/template
/row-head.i
}
376 /* Create a list of all the tables that we need to get.
*/
377 {src
/adm
/template
/row-list.i
"ProjectBudget"}
379 /* Get the record
ROWID's from the RECORD-SOURCE.
*/
380 {src
/adm
/template
/row-get.i
}
382 /* FIND each record specified by the RECORD-SOURCE.
*/
383 {src
/adm
/template
/row-find.i
"ProjectBudget"}
385 /* Process the newly available records
(i.e. display fields
,
386 open queries
, and
/or pass records on to any RECORD-TARGETS
).
*/
387 {src
/adm
/template
/row-end.i
}
391 /* _UIB-CODE-BLOCK-END
*/
394 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE assign-cash-flows V-table-Win
395 PROCEDURE assign-cash-flows
:
396 /*------------------------------------------------------------------------------
398 ------------------------------------------------------------------------------*/
399 IF NOT AVAILABLE FinancialYear
400 OR NOT AVAILABLE ProjectBudget
401 OR NOT AVAILABLE PrjCashFlow
404 ASSIGN BROWSE {&BROWSE-NAME}
405 /* PrjCashFlow.MonthName
407 */ PrjCashFlow.Revised.
409 FOR EACH PrjCashFlow
:
411 FIND AccountBalance
WHERE
412 AccountBalance.EntityType
= "J" AND
413 AccountBalance.EntityCode
= Project.ProjectCode
AND
414 AccountBalance.AccountCode
= ProjectBudget.AccountCode
AND
415 AccountBalance.MonthCode
= PrjCashFlow.MonthCode
416 EXCLUSIVE-LOCK NO-ERROR.
418 IF NOT AVAILABLE AccountBalance
AND
419 ( PrjCashFlow.Budget
<> 0.00 OR PrjCashFlow.Revised
<> 0.00 ) THEN
421 CREATE AccountBalance.
423 AccountBalance.EntityType
= "J"
424 AccountBalance.EntityCode
= Project.ProjectCode
425 AccountBalance.AccountCode
= ProjectBudget.AccountCode
426 AccountBalance.MonthCode
= PrjCashFlow.MonthCode.
429 IF AVAILABLE AccountBalance
THEN
431 AccountBalance.Budget
= PrjCashFlow.Budget
432 AccountBalance.Revised
= PrjCashFlow.Revised.
438 /* _UIB-CODE-BLOCK-END
*/
441 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE budget-changed V-table-Win
442 PROCEDURE budget-changed
:
443 /*------------------------------------------------------------------------------
444 Purpose
: 1. Reflect changes in the revised budget
445 2. Apply the difference between new and old to
:
446 If the previous cash flow is the first for the budget then
447 a newly created one for that month
449 the first cash flow for this budget
450 ------------------------------------------------------------------------------*/
452 DO WITH FRAME {&FRAME-NAME}:
454 DEF VAR change
AS DEC NO-UNDO.
458 change
= DEC( PrjCashFlow.Revised
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} )
459 - PrjCashFlow.Revised.
461 IF change
= 0 THEN RETURN.
462 PrjCashFlow.Revised
= INPUT PrjCashFlow.Revised.
464 IF NOT Project.BudgetsFrozen
THEN DO:
465 PrjCashFlow.Budget
= PrjCashFlow.Budget
+ change .
468 DEF BUFFER FirstBalance
FOR AccountBalance.
469 DEF BUFFER FirstFlow
FOR PrjCashFlow.
470 DEF BUFFER ChangeMonth
FOR Month.
471 DEF VAR first-month
LIKE Month.MonthCode
NO-UNDO.
472 DEF VAR change-month
LIKE Month.MonthCode
NO-UNDO.
474 FIND FIRST FirstBalance
WHERE
475 FirstBalance.EntityType
= "J" AND
476 FirstBalance.EntityCode
= ProjectBudget.ProjectCode
AND
477 FirstBalance.AccountCode
= ProjectBudget.AccountCode
AND
478 FirstBalance.MonthCode
<= PrjCashFlow.MonthCode
AND
479 FirstBalance.Revised
<> 0
482 FIND FIRST FirstFlow
WHERE FirstFlow.MonthCode
< PrjCashFlow.MonthCode
483 AND FirstFlow.Revised
<> 0 NO-LOCK NO-ERROR.
485 IF AVAILABLE FirstBalance
AND AVAILABLE FirstFlow
THEN
486 first-month
= MIN( FirstBalance.MonthCode
, FirstFlow.MonthCode
).
487 ELSE IF AVAILABLE FirstBalance
THEN
488 first-month
= FirstBalance.MonthCode.
489 ELSE IF AVAILABLE FirstFlow
THEN
490 first-month
= FirstFlow.MonthCode.
492 first-month
= PrjCashFlow.MonthCode.
494 /* Apply changes to the appropriate month
*/
495 IF first-month
= PrjCashFlow.MonthCode
THEN DO:
496 IF DEC( PrjCashFlow.Revised
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} ) = 0.00
497 AND first-month
> very-first-month
THEN
498 FIND FIRST ChangeMonth
WHERE ChangeMonth.MonthCode
> first-month
NO-LOCK NO-ERROR.
500 FIND FIRST ChangeMonth
WHERE ChangeMonth.MonthCode
> first-month
NO-LOCK NO-ERROR.
501 change-month
= IF AVAILABLE ChangeMonth
THEN ChangeMonth.MonthCode
ELSE ?.
504 change-month
= first-month.
506 IF change-month
= ?
THEN DO:
507 MESSAGE "Error adjusting cash flows" SKIP "they may need to be reset".
511 FIND ChangeMonth
WHERE ChangeMonth.MonthCode
= change-month
NO-LOCK.
513 FIND AccountBalance
WHERE
514 AccountBalance.EntityType
= "J" AND
515 AccountBalance.EntityCode
= ProjectBudget.ProjectCode
AND
516 AccountBalance.AccountCode
= ProjectBudget.AccountCode
AND
517 AccountBalance.MonthCode
= ChangeMonth.MonthCode
520 IF NOT AVAILABLE AccountBalance
THEN DO:
521 CREATE AccountBalance.
522 ASSIGN AccountBalance.EntityType
= "J"
523 AccountBalance.EntityCode
= ProjectBudget.ProjectCode
524 AccountBalance.AccountCode
= ProjectBudget.AccountCode
525 AccountBalance.MonthCode
= ChangeMonth.MonthCode.
528 ASSIGN AccountBalance.Revised
= AccountBalance.Revised
- change.
529 IF NOT Project.BudgetsFrozen
THEN DO:
530 AccountBalance.Budget
= AccountBalance.Budget
- change .
533 IF ChangeMonth.FinancialYearCode
= FinancialYear.FinancialYearCode
THEN DO:
534 DEF BUFFER TheFlow
FOR PrjCashFlow.
535 FIND TheFlow
WHERE TheFlow.MonthCode
= change-month.
536 TheFlow.Revised
= TheFlow.Revised
- change.
537 IF NOT Project.BudgetsFrozen
THEN DO:
538 TheFlow.Budget
= TheFlow.Budget
- change.
540 IF {&BROWSE-NAME}:REFRESH() IN FRAME {&FRAME-NAME} THEN.
543 PrjCashFlow.Budget
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} =
544 STRING( PrjCashFlow.Budget
, PrjCashFlow.Budget
:FORMAT IN BROWSE {&BROWSE-NAME}).
550 /* _UIB-CODE-BLOCK-END
*/
553 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE budget-source-changed V-table-Win
554 PROCEDURE budget-source-changed
:
555 /*------------------------------------------------------------------------------
559 ------------------------------------------------------------------------------*/
561 /* Called when the source record for the cash flow information
564 IF NOT AVAILABLE ProjectBudget
THEN RETURN.
565 FIND Project
OF ProjectBudget
NO-LOCK NO-ERROR.
566 IF NOT AVAILABLE Project
THEN RETURN.
568 RUN sensitise-budgets.
573 /* _UIB-CODE-BLOCK-END
*/
576 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE close-cash-flow-query V-table-Win
577 PROCEDURE close-cash-flow-query
:
578 /*------------------------------------------------------------------------------
582 ------------------------------------------------------------------------------*/
584 CLOSE QUERY {&BROWSE-NAME}.
588 /* _UIB-CODE-BLOCK-END
*/
591 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI V-table-Win _DEFAULT-DISABLE
592 PROCEDURE disable_UI
:
593 /*------------------------------------------------------------------------------
594 Purpose
: DISABLE the User Interface
596 Notes
: Here we clean-up the user-interface by deleting
597 dynamic widgets we have created and
/or hide
598 frames. This procedure is usually called when
599 we are ready to
"clean-up" after running.
600 ------------------------------------------------------------------------------*/
601 /* Hide all frames.
*/
603 IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE.
606 /* _UIB-CODE-BLOCK-END
*/
609 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-current-cash-flows V-table-Win
610 PROCEDURE get-current-cash-flows
:
611 /*------------------------------------------------------------------------------
615 ------------------------------------------------------------------------------*/
617 FOR EACH PrjCashFlow
: DELETE PrjCashFlow.
END.
619 IF NOT AVAILABLE FinancialYear
OR
620 NOT AVAILABLE ProjectBudget
OR
621 NOT AVAILABLE Project
THEN RETURN.
623 very-first-month
= ?.
625 FOR EACH Month
OF FinancialYear
NO-LOCK:
627 IF very-first-month
= ?
AND FinancialYear.FinancialYearCode
= very-first-year
THEN
628 very-first-month
= Month.MonthCode.
632 PrjCashFlow.YearCode
= FinancialYear.FinancialYearCode
633 PrjCashFlow.MonthCode
= Month.MonthCode
634 PrjCashFlow.MonthName
= Month.MonthName.
636 FIND AccountBalance
WHERE
637 AccountBalance.EntityType
= "J" AND
638 AccountBalance.EntityCode
= Project.ProjectCode
AND
639 AccountBalance.AccountCode
= ProjectBudget.AccountCode
AND
640 AccountBalance.MonthCode
= Month.MonthCode
643 IF AVAILABLE AccountBalance
THEN
645 PrjCashFlow.Balance
= AccountBalance.Balance
646 PrjCashFlow.Budget
= AccountBalance.Budget
647 PrjCashFlow.Revised
= AccountBalance.Revised.
653 /* _UIB-CODE-BLOCK-END
*/
656 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-initialize V-table-Win
657 PROCEDURE inst-initialize
:
658 /*------------------------------------------------------------------------------
662 ------------------------------------------------------------------------------*/
664 this-win
= CURRENT-WINDOW.
669 /* _UIB-CODE-BLOCK-END
*/
672 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE inst-row-available V-table-Win
673 PROCEDURE inst-row-available
:
674 /*------------------------------------------------------------------------------
676 ------------------------------------------------------------------------------*/
678 RUN budget-source-changed.
679 RUN refresh-window-title
IN sys-mgr
( THIS-PROCEDURE ).
683 /* _UIB-CODE-BLOCK-END
*/
686 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE open-cash-flow-query V-table-Win
687 PROCEDURE open-cash-flow-query
:
688 /*------------------------------------------------------------------------------
692 ------------------------------------------------------------------------------*/
694 RUN close-cash-flow-query.
695 RUN get-current-cash-flows.
697 OPEN QUERY {&BROWSE-NAME} FOR EACH PrjCashFlow.
701 /* _UIB-CODE-BLOCK-END
*/
704 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-destroy V-table-Win
705 PROCEDURE pre-destroy
:
706 /*------------------------------------------------------------------------------
710 ------------------------------------------------------------------------------*/
712 RUN assign-cash-flows.
716 /* _UIB-CODE-BLOCK-END
*/
719 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE pre-row-available V-table-Win
720 PROCEDURE pre-row-available
:
721 /*------------------------------------------------------------------------------
725 ------------------------------------------------------------------------------*/
728 /* If the row has changed and there is already a
729 project budget available then svae the current ones
*/
730 IF AVAILABLE ProjectBudget
THEN RUN assign-cash-flows.
734 /* _UIB-CODE-BLOCK-END
*/
737 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE refresh-years V-table-Win
738 PROCEDURE refresh-years
:
739 /*------------------------------------------------------------------------------
743 ------------------------------------------------------------------------------*/
745 DO WITH FRAME {&FRAME-NAME}:
747 ASSIGN cmb_Years
:LIST-ITEMS = "".
749 DEF VAR years-from
AS INT NO-UNDO.
750 DEF VAR item
AS CHAR NO-UNDO.
752 years-from
= IF Project.StartDate
<> ?
753 THEN YEAR( Project.StartDate
)
755 very-first-year
= years-from.
757 FOR EACH FinancialYear
WHERE
758 FinancialYear.FinancialYearCode
>= years-from
NO-LOCK:
759 item
= STRING( FinancialYear.FinancialYearCode
) + " - " + FinancialYear.Description.
760 IF cmb_Years
:ADD-LAST( item
) THEN.
763 cmb_Years
:SCREEN-VALUE = cmb_Years
:ENTRY(1).
770 /* _UIB-CODE-BLOCK-END
*/
773 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key V-table-Win adm/support/_key-snd.p
775 /*------------------------------------------------------------------------------
776 Purpose
: Sends a requested
KEY value back to the calling
778 Parameters
: <see adm
/template
/sndkytop.i
>
779 ------------------------------------------------------------------------------*/
781 /* Define variables needed by this internal procedure.
*/
782 {src
/adm
/template
/sndkytop.i
}
784 /* Return the key value associated with each key case.
*/
785 {src
/adm
/template
/sndkycas.i
"AccountCode" "ProjectBudget" "AccountCode"}
786 {src
/adm
/template
/sndkycas.i
"EntityCode" "ProjectBudget" "EntityCode"}
787 {src
/adm
/template
/sndkycas.i
"EntityType" "ProjectBudget" "EntityType"}
789 /* Close the
CASE statement and end the procedure.
*/
790 {src
/adm
/template
/sndkyend.i
}
794 /* _UIB-CODE-BLOCK-END
*/
797 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records V-table-Win _ADM-SEND-RECORDS
798 PROCEDURE send-records
:
799 /*------------------------------------------------------------------------------
800 Purpose
: Send record
ROWID's for all tables used by
802 Parameters
: see template
/snd-head.i
803 ------------------------------------------------------------------------------*/
805 /* Define variables needed by this internal procedure.
*/
806 {src
/adm
/template
/snd-head.i
}
808 /* For each requested table
, put it's
ROWID in the output list.
*/
809 {src
/adm
/template
/snd-list.i
"ProjectBudget"}
810 {src
/adm
/template
/snd-list.i
"PrjCashFlow"}
812 /* Deal with any unexpected table requests before closing.
*/
813 {src
/adm
/template
/snd-end.i
}
817 /* _UIB-CODE-BLOCK-END
*/
820 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE sensitise-budgets V-table-Win
821 PROCEDURE sensitise-budgets
:
822 /*------------------------------------------------------------------------------
826 ------------------------------------------------------------------------------*/
828 PrjCashFlow.Budget
:READ-ONLY IN BROWSE {&BROWSE-NAME} = Project.BudgetsFrozen.
829 PrjCashFlow.Revised
:READ-ONLY IN BROWSE {&BROWSE-NAME} = NOT Project.BudgetsFrozen.
833 /* _UIB-CODE-BLOCK-END
*/
836 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed V-table-Win
837 PROCEDURE state-changed
:
838 /* -----------------------------------------------------------
842 -------------------------------------------------------------*/
843 DEFINE INPUT PARAMETER p-issuer-hdl
AS HANDLE NO-UNDO.
844 DEFINE INPUT PARAMETER p-state
AS CHARACTER NO-UNDO.
847 /* Object instance CASEs can go here to replace standard behavior
849 {src
/adm
/template
/vstates.i
}
853 /* _UIB-CODE-BLOCK-END
*/
856 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE top-changed V-table-Win
857 PROCEDURE top-changed
:
858 /*------------------------------------------------------------------------------
860 ------------------------------------------------------------------------------*/
862 IF INPUT FRAME {&FRAME-NAME} tgl_topmost THEN
863 RUN notify
( 'set-topmost
,container-source'
:U
).
865 RUN notify
( 'reset-topmost
,container-source'
:U
).
869 /* _UIB-CODE-BLOCK-END
*/
872 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE verify-budget V-table-Win
873 PROCEDURE verify-budget
:
874 /*------------------------------------------------------------------------------
878 ------------------------------------------------------------------------------*/
880 DO WITH FRAME {&FRAME-NAME}:
882 /* Test to see if we need to delete the budget
*/
884 IF DEC( PrjCashFlow.Budget
:SCREEN-VALUE IN BROWSE {&BROWSE-NAME} ) = 0.00 THEN
886 FIND AccountBalance
WHERE
887 AccountBalance.EntityType
= "J" AND
888 AccountBalance.EntityCode
= ProjectBudget.ProjectCode
AND
889 AccountBalance.AccountCode
= ProjectBudget.AccountCode
AND
890 AccountBalance.MonthCode
= PrjCashFlow.MonthCode
893 IF AVAILABLE AccountBalance
AND
894 NOT CAN-FIND( FIRST AcctTran
OF AccountBalance
) THEN
895 DELETE AccountBalance.
903 /* _UIB-CODE-BLOCK-END
*/
906 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE year-changed V-table-Win
907 PROCEDURE year-changed
:
908 /*------------------------------------------------------------------------------
912 ------------------------------------------------------------------------------*/
914 DO WITH FRAME {&FRAME-NAME}:
916 FIND FinancialYear
WHERE
917 FinancialYear.FinancialYearCode
= INT( TRIM( ENTRY( 1, INPUT cmb_Years
, "-" ) ) )
919 RUN open-cash-flow-query.
925 /* _UIB-CODE-BLOCK-END
*/