Really, this should be it, for the passing income.
[capital-apms-progress.git] / process / one-off / rentchrg.p
blob3c4d99ff7008fb403218e4b0bdc76b644103bf07
1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12
2 &ANALYZE-RESUME
3 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS Procedure
4 /*--------------------------------------------------------------------------
5 File :
6 Purpose :
8 Syntax :
10 Description :
12 Author(s) :
13 Created :
14 Notes :
15 ------------------------------------------------------------------------*/
17 {inc/ofc-this.i}
18 {inc/ofc-set.i "RentCharge-Type" "charge-type" "ERROR"}
19 IF LOOKUP( charge-type, "Accounts,Single" ) = 0 THEN RETURN.
21 {inc/ofc-acct.i "RENT" "rent-account"}
22 {inc/ofc-acct.i "OUTGOINGS" "outgoings-account"}
23 {inc/ofc-acct.i "DEBTORS" "sundry-debtors"}
25 DEF VAR default-last-date AS DATE NO-UNDO.
26 default-last-date = TODAY.
27 IF DAY(default-last-date) > 20 THEN /* put date into next month */
28 default-last-date = default-last-date + 15.
30 FIND LAST Month WHERE Month.StartDate <= default-last-date NO-LOCK NO-ERROR.
31 IF AVAILABLE Month THEN default-last-date = Month.StartDate - 1.
33 DEF WORK-TABLE og-acct NO-UNDO
34 FIELD AccountCode LIKE ChartOfAccount.AccountCode
35 FIELD ShortName AS CHAR FORMAT "X(9)"
36 FIELD Recovered AS DECIMAL
37 FIELD Gross AS DECIMAL
38 FIELD Vacant AS DECIMAL.
40 /* _UIB-CODE-BLOCK-END */
41 &ANALYZE-RESUME
44 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
46 /* ******************** Preprocessor Definitions ******************** */
48 &Scoped-define PROCEDURE-TYPE Procedure
49 &Scoped-define DB-AWARE no
53 /* _UIB-PREPROCESSOR-BLOCK-END */
54 &ANALYZE-RESUME
57 /* ************************ Function Prototypes ********************** */
59 &IF DEFINED(EXCLUDE-convert-from-yearly) = 0 &THEN
61 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD convert-from-yearly Procedure
62 FUNCTION convert-from-yearly RETURNS DECIMAL
63 ( INPUT amount AS DEC, INPUT freq AS CHAR ) FORWARD.
65 /* _UIB-CODE-BLOCK-END */
66 &ANALYZE-RESUME
68 &ENDIF
70 &IF DEFINED(EXCLUDE-get-prop-og) = 0 &THEN
72 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD get-prop-og Procedure
73 FUNCTION get-prop-og RETURNS DECIMAL
74 ( INPUT doit AS LOGICAL, INPUT pc AS INTEGER, INPUT ac AS DECIMAL ) FORWARD.
76 /* _UIB-CODE-BLOCK-END */
77 &ANALYZE-RESUME
79 &ENDIF
81 &IF DEFINED(EXCLUDE-last-trans-date) = 0 &THEN
83 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD last-trans-date Procedure
84 FUNCTION last-trans-date RETURNS DATE
85 ( INPUT account-code AS DEC ) FORWARD.
87 /* _UIB-CODE-BLOCK-END */
88 &ANALYZE-RESUME
90 &ENDIF
93 /* *********************** Procedure Settings ************************ */
95 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
96 /* Settings for THIS-PROCEDURE
97 Type: Procedure
98 Allow:
99 Frames: 0
100 Add Fields to: Neither
101 Other Settings: CODE-ONLY COMPILE
103 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
105 /* ************************* Create Window ************************** */
107 &ANALYZE-SUSPEND _CREATE-WINDOW
108 /* DESIGN Window definition (used by the UIB)
109 CREATE WINDOW Procedure ASSIGN
110 HEIGHT = 16.75
111 WIDTH = 39.72.
112 /* END WINDOW DEFINITION */
114 &ANALYZE-RESUME
116 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB Procedure
117 /* ************************* Included-Libraries *********************** */
119 {inc/date.i}
121 /* _UIB-CODE-BLOCK-END */
122 &ANALYZE-RESUME
128 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK Procedure
131 /* *************************** Main Block *************************** */
133 RUN convert-area-types.
134 RUN convert-rent-charges.
135 RUN convert-rent-reviews.
137 MESSAGE "Conversion of RentalSpace rents to Rent Charges completed!".
139 /* _UIB-CODE-BLOCK-END */
140 &ANALYZE-RESUME
143 /* ********************** Internal Procedures *********************** */
145 &IF DEFINED(EXCLUDE-build-property-details) = 0 &THEN
147 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE build-property-details Procedure
148 PROCEDURE build-property-details :
149 /*------------------------------------------------------------------------------
150 Purpose: Build details of property outgoings &c.
151 ------------------------------------------------------------------------------*/
152 DEF INPUT PARAMETER times-amt AS LOGICAL NO-UNDO.
154 DEF VAR out-line AS CHAR NO-UNDO.
155 DEF VAR no-accounts AS INTEGER NO-UNDO.
156 DEF VAR i AS INTEGER NO-UNDO.
157 DEF VAR percentage AS DECIMAL NO-UNDO.
158 DEF VAR acct-amnt AS DECIMAL NO-UNDO.
159 DEF VAR money-fmt AS CHAR NO-UNDO.
160 DEF VAR non-zero AS LOGICAL NO-UNDO.
162 DEF BUFFER PrimarySpace FOR RentalSpace.
164 money-fmt = IF times-amt = Yes THEN "->>>,>>9" ELSE "->>>9.99".
166 no-accounts = 0.
167 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST",
168 EACH TenancyOutgoing NO-LOCK OF TenancyLease WHERE TenancyOutgoing.Percentage > 0:
169 FIND FIRST og-acct WHERE og-acct.AccountCode = TenancyOutgoing.AccountCode NO-ERROR.
170 IF AVAILABLE(og-acct) THEN
171 og-acct.Recovered = og-acct.Recovered + TenancyOutgoing.Percentage.
172 ELSE DO:
173 no-accounts = no-accounts + 1.
174 FIND ChartOfAccount WHERE ChartOfAccount.AccountCode = TenancyOutgoing.AccountCode NO-LOCK NO-ERROR.
175 CREATE og-acct.
176 ASSIGN
177 og-acct.AccountCode = TenancyOutgoing.AccountCode
178 og-acct.ShortName = (IF AVAILABLE(ChartOfAccount) THEN STRING( (IF TRIM(ChartOfAccount.ShortName) <> "" THEN ChartOfAccount.ShortName ELSE ChartOfAccount.Name), "X(7)") ELSE "???????")
179 og-acct.Recovered = TenancyOutgoing.Percentage
180 og-acct.Vacant = 0
182 og-acct.ShortName = TRIM(og-acct.ShortName).
183 og-acct.ShortName = FILL( " ", 7 - LENGTH(og-acct.ShortName)) + og-acct.ShortName .
184 END.
185 END.
187 /* fill in those where a default percentage applies from the lease record */
188 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST",
189 EACH og-acct WHERE NOT CAN-FIND( FIRST TenancyOutgoing OF TenancyLease WHERE TenancyOutgoing.AccountCode = og-acct.AccountCode):
190 og-acct.Recovered = og-acct.Recovered + TenancyLease.OutgoingsRate .
191 END.
193 col-head1 = FILL(" ", 33).
194 col-head2 = STRING( "Tenant / Area", "X(33)").
195 FOR EACH og-acct BY og-acct.AccountCode:
196 col-head1 = col-head1 + " " + og-acct.ShortName.
197 col-head2 = col-head2 + " " + STRING( og-acct.AccountCode, "9999.99").
198 END.
200 IF print-main-schedule THEN PAGE. ELSE RUN set-headings( col-head1, col-head2).
203 /* Net Leases */
204 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST"
205 AND NOT TenancyLease.GrossLease,
206 FIRST PrimarySpace OF TenancyLease /* WHERE PrimarySpace.RentalSpaceCode = TenancyLease.PrimarySpace */
207 BY PrimarySpace.Level BY PrimarySpace.LevelSequence :
208 FIND Tenant WHERE Tenant.TenantCode = TenancyLease.TenantCode NO-LOCK NO-ERROR.
209 non-zero = No.
210 out-line = STRING( Tenant.tenantCode, "99999 ")
211 + STRING( Tenant.Name, "X(15)") + " "
212 + STRING( TenancyLease.AreaDescription, "X(11)") .
213 FOR EACH og-acct BY og-acct.AccountCode:
214 FIND TenancyOutgoing NO-LOCK OF TenancyLease WHERE TenancyOutgoing.AccountCode = og-acct.AccountCode NO-ERROR.
215 percentage = (IF AVAILABLE(TenancyOutgoing) THEN TenancyOutgoing.Percentage ELSE TenancyLease.OutgoingsRate ).
216 IF percentage = ? THEN percentage = 0. ELSE
217 percentage = percentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
218 out-line = out-line + (IF percentage <> 0 THEN STRING( percentage, money-fmt) ELSE " - ").
219 IF percentage <> 0 THEN non-zero = Yes.
220 END.
221 IF PrimarySpace.AreaType <> "C" OR non-zero THEN RUN print-line( out-line, No).
222 END.
223 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
225 out-line = STRING( "Total Recoverable", "X(33)").
226 FOR EACH og-acct BY og-acct.AccountCode:
227 out-line = out-line + STRING( og-acct.Recovered * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
228 money-fmt) .
229 END.
230 RUN print-line( out-line, No).
233 /* Gross Leases */
234 RUN print-line( " ", No ).
235 RUN print-line( " ", No ).
236 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST"
237 AND TenancyLease.GrossLease,
238 FIRST PrimarySpace OF TenancyLease /* WHERE PrimarySpace.RentalSpaceCode = TenancyLease.PrimarySpace */
239 BY PrimarySpace.Level BY PrimarySpace.LevelSequence :
240 FIND Tenant WHERE Tenant.TenantCode = TenancyLease.TenantCode NO-LOCK NO-ERROR.
241 non-zero = No.
242 out-line = STRING( Tenant.tenantCode, "99999 ")
243 + STRING( Tenant.Name, "X(15)") + " "
244 + STRING( TenancyLease.AreaDescription, "X(11)") .
245 percentage = 0.
246 FOR EACH RentalSpace OF TenancyLease:
247 percentage = percentage + RentalSpace.OutgoingsPercentage.
248 END.
249 IF percentage = 0 THEN NEXT.
251 FOR EACH og-acct BY og-acct.AccountCode:
252 acct-amnt = percentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
253 out-line = out-line + (IF acct-amnt <> 0 THEN STRING( acct-amnt, money-fmt) ELSE " - ") .
254 og-acct.Gross = og-acct.Gross + percentage.
255 END.
256 RUN print-line( out-line, No).
258 END.
259 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
261 out-line = STRING( "Total Gross Leases", "X(33)").
262 FOR EACH og-acct BY og-acct.AccountCode:
263 out-line = out-line + STRING( og-acct.Gross * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
264 money-fmt) .
265 END.
266 RUN print-line( out-line, No).
269 RUN print-line( " ", No ).
270 RUN print-line( " ", No ).
271 FOR EACH RentalSpace NO-LOCK OF Property WHERE RentalSpace.AreaStatus = "V"
272 AND RentalSpace.OutgoingsPercentage <> 0
273 BY Level BY LevelSequence:
274 out-line = STRING( TRIM( STRING( RentalSpace.Level, "->>>9/")) + TRIM( STRING( RentalSpace.LevelSequence, ">>>9 ")), "X(8)")
275 + STRING( RentalSpace.Description, "X(25)").
276 FOR EACH og-acct BY og-acct.AccountCode:
277 percentage = RentalSpace.OutgoingsPercentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
278 out-line = out-line + (IF percentage <> 0 THEN STRING( percentage, money-fmt) ELSE " - ") .
279 og-acct.Vacant = og-acct.Vacant + RentalSpace.OutgoingsPercentage.
280 END.
281 RUN print-line( out-line, No).
282 END.
284 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
285 out-line = STRING( "Total Vacant", "X(33)").
286 FOR EACH og-acct BY og-acct.AccountCode:
287 out-line = out-line + STRING( og-acct.Vacant * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
288 money-fmt) .
289 END.
290 RUN print-line( out-line, No).
293 RUN print-line( " ", No ).
294 RUN print-line( " ", No ).
295 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("=",7), no-accounts), No).
296 out-line = STRING( "Total", "X(33)").
297 FOR EACH og-acct BY og-acct.AccountCode:
298 out-line = out-line + STRING( (og-acct.Recovered + og-acct.Gross + og-acct.Vacant) * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
299 money-fmt) .
300 END.
301 RUN print-line( out-line, No).
303 END PROCEDURE.
305 /* _UIB-CODE-BLOCK-END */
306 &ANALYZE-RESUME
308 &ENDIF
310 &IF DEFINED(EXCLUDE-convert-area-types) = 0 &THEN
312 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE convert-area-types Procedure
313 PROCEDURE convert-area-types :
314 /*------------------------------------------------------------------------------
315 Purpose:
316 ------------------------------------------------------------------------------*/
318 FOR EACH RentChargeType: DELETE RentChargeType. END.
320 FOR EACH AreaType NO-LOCK:
321 CREATE RentChargeType.
322 ASSIGN
323 RentChargeType.RentchargeType = AreaType.AreaType
324 RentchargeType.Description = AreaType.Description + " Rental"
325 RentChargeType.AccountCode = AreaType.AccountCode.
326 END.
328 /* Create the default "rental" rent charge type */
329 CREATE RentChargeType.
330 ASSIGN
331 RentChargeType.RentChargeType = "RENT"
332 RentChargeType.Description = "Rental"
333 RentChargeType.AccountCode = rent-account.
335 /* Create the default "outgoings" rent charge type */
336 CREATE RentChargeType.
337 ASSIGN
338 RentChargeType.RentChargeType = "O/G"
339 RentChargeType.Description = "Outgoings"
340 RentChargeType.AccountCode = outgoings-account.
342 IF NOT CAN-FIND( RentChargeLineStatus WHERE RentChargeLineStatus.RentChargeLineStatus = "C") THEN DO:
343 /* Create the "current" rent charge line status */
344 CREATE RentChargeLineStatus.
345 ASSIGN RentChargeLineStatus.RentChargeLineStatus = "C"
346 RentChargeLineStatus.Description = "Current".
347 END.
349 IF NOT CAN-FIND( RentChargeLineStatus WHERE RentChargeLineStatus.RentChargeLineStatus = "P") THEN DO:
350 /* Create the "Past" rent charge line status */
351 CREATE RentChargeLineStatus.
352 ASSIGN RentChargeLineStatus.RentChargeLineStatus = "P"
353 RentChargeLineStatus.Description = "Past".
354 END.
356 IF NOT CAN-FIND( RentChargeLineStatus WHERE RentChargeLineStatus.RentChargeLineStatus = "I") THEN DO:
357 /* Create the "Past" rent charge line status */
358 CREATE RentChargeLineStatus.
359 ASSIGN RentChargeLineStatus.RentChargeLineStatus = "I"
360 RentChargeLineStatus.Description = "Initial".
361 END.
363 IF NOT CAN-FIND( RentChargeLineStatus WHERE RentChargeLineStatus.RentChargeLineStatus = "N") THEN DO:
364 /* Create the "Future" rent charge line status */
365 CREATE RentChargeLineStatus.
366 ASSIGN RentChargeLineStatus.RentChargeLineStatus = "N"
367 RentChargeLineStatus.Description = "Not finalised".
368 END.
370 END PROCEDURE.
372 /* _UIB-CODE-BLOCK-END */
373 &ANALYZE-RESUME
375 &ENDIF
377 &IF DEFINED(EXCLUDE-convert-og-charge) = 0 &THEN
379 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE convert-og-charge Procedure
380 PROCEDURE convert-og-charge :
381 /*------------------------------------------------------------------------------
382 Purpose:
383 ------------------------------------------------------------------------------*/
384 DEF INPUT PARAMETER seq-code AS INT NO-UNDO.
386 IF (TenancyLease.OutgoingsBudget = 0 OR TenancyLease.OutgoingsBudget = ?)
387 AND TenancyLease.RecoveryType <> "B" THEN DO:
389 END.
390 ELSE DO TRANSACTION:
391 CREATE RentCharge.
392 ASSIGN RentCharge.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
393 RentCharge.SequenceCode = seq-code
394 RentCharge.RentChargeType = "O/G"
395 RentCharge.Description = "Outgoings"
396 RentCharge.EntityType = ""
397 RentCharge.EntityCode = 0
398 RentCharge.AccountCode = outgoings-account.
400 CREATE RentChargeLine.
401 ASSIGN RentChargeLine.DateCommitted = TODAY
402 RentChargeLine.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
403 RentChargeLine.SequenceCode = RentCharge.SequenceCode
404 RentChargeLine.RentChargeLineStatus = "C"
405 RentChargeLine.EndDate = TenancyLease.RentEndDate .
407 RentChargeLine.FrequencyCode = (IF TenancyLease.PaymentFrequency <> "" THEN TenancyLease.PaymentFrequency ELSE "MNTH").
408 RentChargeLine.LastChargedDate = last-trans-date( RentCharge.AccountCode ).
409 RentChargeLine.StartDate = (IF TenancyLease.RentStartDate <> ? THEN TenancyLease.RentStartDate ELSE RentChargeLine.LastChargedDate + 1).
410 RentChargeLine.Amount = convert-from-yearly( TenancyLease.OutgoingsBudget, RentChargeLine.FrequencyCode ).
411 END. /* if TenancyLease.OutgoingsBudget <> 0 then */
414 END PROCEDURE.
416 /* _UIB-CODE-BLOCK-END */
417 &ANALYZE-RESUME
419 &ENDIF
421 &IF DEFINED(EXCLUDE-convert-rent-charges) = 0 &THEN
423 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE convert-rent-charges Procedure
424 PROCEDURE convert-rent-charges :
425 /*------------------------------------------------------------------------------
426 Purpose: Create rent charge records from the current structure
427 ------------------------------------------------------------------------------*/
429 DEF VAR rent-chg-amount AS DEC NO-UNDO.
430 DEF VAR outgoings-amount AS DEC NO-UNDO.
431 DEF VAR last-charged-date AS DATE NO-UNDO.
432 DEF VAR seq-code AS INT NO-UNDO.
434 /* Clear all rent charges */
435 FOR EACH RentChargeLine: DELETE RentChargeLine. END.
436 FOR EACH RentCharge: DELETE RentCharge. END.
438 ON WRITE OF RentCharge OVERRIDE DO: END.
440 IF charge-type = "Single" THEN DO:
442 FOR EACH Property WHERE Property.Active AND NOT Property.ExternallyManaged NO-LOCK:
443 lease-loop:
444 FOR EACH TenancyLease WHERE TenancyLease.PropertyCode = Property.PropertyCode
445 AND TenancyLease.LeaseStatus <> "PAST" NO-LOCK :
446 FIND FIRST Tenant WHERE Tenant.TenantCode = TenancyLease.TenantCode
447 AND Tenant.Active NO-LOCK NO-ERROR.
448 IF NOT AVAILABLE(Tenant) THEN NEXT lease-loop.
450 seq-code = 1.
451 rent-chg-amount = 0.
452 FOR EACH RentalSpace WHERE RentalSpace.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
453 AND RentalSpace.AreaStatus <> "V" NO-LOCK:
454 rent-chg-amount = rent-chg-amount + ( IF RentalSpace.ChargedRental <> ? THEN RentalSpace.ChargedRental ELSE 0 ).
455 END.
457 IF rent-chg-amount = 0 OR rent-chg-amount = ? THEN DO:
458 /* MESSAGE TenancyLease.TenancyLeaseCode " has zero rental value". */
460 END.
461 ELSE DO TRANSACTION:
462 CREATE RentCharge.
463 ASSIGN
464 RentCharge.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
465 RentCharge.SequenceCode = seq-code
466 RentCharge.RentChargeType = "RENT"
467 RentCharge.Description = "Rental"
468 RentCharge.EntityType = ""
469 RentCharge.EntityCode = 0
470 RentCharge.AccountCode = rent-account.
472 CREATE RentChargeLine.
473 ASSIGN
474 RentChargeLine.DateCommitted = TODAY
475 RentChargeLine.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
476 RentChargeLine.SequenceCode = RentCharge.SequenceCode
477 RentChargeLine.RentChargeLineStatus = "C"
478 RentChargeLine.EndDate = TenancyLease.RentEndDate .
480 RentChargeLine.FrequencyCode = "MNTH".
481 /* (IF TenancyLease.PaymentFrequency <> "" THEN TenancyLease.PaymentFrequency ELSE "MNTH"). */
482 RentChargeLine.LastChargedDate = last-trans-date( RentCharge.AccountCode ).
483 RentChargeLine.StartDate = TenancyLease.RentStartDate.
484 IF RentChargeLine.StartDate = ? THEN RentChargeLine.StartDate = TenancyLease.LeaseStartDate.
485 IF RentChargeLine.StartDate = ? THEN RentChargeLine.StartDate = RentChargeLine.LastChargedDate + 1.
486 IF RentChargeLine.StartDate = ? THEN RentChargeLine.StartDate = last-of-month(TODAY - 3) + 1.
487 RentChargeLine.Amount = convert-from-yearly( rent-chg-amount, RentChargeLine.FrequencyCode ).
489 seq-code = seq-code + 1.
490 END. /* if rent-chg-amount <> 0 then */
492 RUN convert-og-charge( seq-code ).
494 END. /* each lease */
495 END. /* each property */
496 END.
497 ELSE DO: /* Charge-Type = "Accounts" */
499 /* For Australia - split rent charges based on rent charge type */
500 FOR EACH Property NO-LOCK WHERE Property.Active AND NOT Property.ExternallyManaged,
501 EACH TenancyLease OF Property NO-LOCK WHERE TenancyLease.LeaseStatus <> "PAST",
502 FIRST Tenant OF TenancyLease WHERE Tenant.Active:
504 seq-code = 1.
505 FOR EACH RentalSpace OF TenancyLease WHERE RentalSpace.AreaStatus <> "V" NO-LOCK
506 BREAK BY RentalSpace.AreaType:
508 /* For area types "S" create individual charges */
509 IF FIRST-OF( RentalSpace.AreaType ) OR RentalSpace.AreaType = "S" THEN
510 rent-chg-amount = 0.
512 rent-chg-amount = rent-chg-amount + ( IF RentalSpace.ChargedRental <> ? THEN RentalSpace.ChargedRental ELSE 0 ).
514 IF LAST-OF( RentalSpace.AreaType ) OR RentalSpace.AreaType = "S" THEN DO:
515 FIND AreaType WHERE AreaType.AreaType = RentalSpace.AreaType NO-LOCK NO-ERROR.
517 CREATE RentCharge.
518 ASSIGN
519 RentCharge.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
520 RentCharge.SequenceCode = seq-code
521 seq-code = seq-code + 1
522 RentCharge.RentChargeType = RentalSpace.AreaType
523 RentCharge.Description = IF NOT AVAILABLE(AreaType) OR RentalSpace.AreaType = "S" THEN RentalSpace.Description ELSE AreaType.Description
524 RentCharge.EntityType = ""
525 RentCharge.EntityCode = 0
526 RentCharge.AccountCode = IF AVAILABLE(AreaType) THEN AreaType.AccountCode ELSE rent-account.
528 CREATE RentChargeLine.
529 ASSIGN
530 RentChargeLine.DateCommitted = TODAY
531 RentChargeLine.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
532 RentChargeLine.SequenceCode = RentCharge.SequenceCode
533 RentChargeLine.FrequencyCode = IF TenancyLease.PaymentFrequency <> "" THEN TenancyLease.PaymentFrequency ELSE "MNTH".
535 RentChargeLine.Amount = convert-from-yearly( rent-chg-amount, RentChargeLine.FrequencyCode ).
536 ASSIGN
537 RentChargeLine.RentChargeLineStatus = "C"
538 RentChargeLine.LastChargedDate = last-trans-date( RentCharge.AccountCode )
539 RentChargeLine.StartDate = IF TenancyLease.RentStartDate <> ?
540 THEN TenancyLease.RentStartDate
541 ELSE RentChargeLine.LastChargedDate + 1
542 RentChargeLine.EndDate = TenancyLease.RentEndDate .
543 END.
545 END. /* for each rental space */
547 RUN convert-og-charge( seq-code ).
549 END. /* for each lease */
551 END. /* aussie style */
553 END PROCEDURE.
555 /* _UIB-CODE-BLOCK-END */
556 &ANALYZE-RESUME
558 &ENDIF
560 &IF DEFINED(EXCLUDE-convert-rent-reviews) = 0 &THEN
562 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE convert-rent-reviews Procedure
563 PROCEDURE convert-rent-reviews :
564 /*------------------------------------------------------------------------------
565 Purpose: Create incomplete rent charge records from the
566 Parameters: <none>
567 Notes:
568 ------------------------------------------------------------------------------*/
569 RETURN.
570 MESSAGE "Converting Rent Reviews" VIEW-AS ALERT-BOX.
572 ON WRITE OF RentCharge OVERRIDE DO: END.
574 FOR EACH Property NO-LOCK WHERE Property.Active AND NOT Property.ExternallyManaged,
575 EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST",
576 FIRST Tenant NO-LOCK OF TenancyLease WHERE Tenant.Active,
577 EACH RentReview NO-LOCK OF TenancyLease:
579 /* Find the rent charge that the review should belong to */
580 IF charge-type = "Single" THEN DO:
581 FIND FIRST RentCharge WHERE RentCharge.TenancyLeaseCode = RentReview.TenancyLeaseCode
582 AND RentCharge.RentChargeType = "RENT" NO-LOCK NO-ERROR.
583 RUN create-review-change.
584 END.
585 ELSE DO:
586 FOR EACH RentCharge WHERE RentCharge.TenancyLeaseCode = RentReview.TenancyLeaseCode NO-LOCK:
587 RUN create-review-change.
588 END.
589 END.
590 END.
592 ON WRITE OF RentCharge REVERT .
594 END PROCEDURE.
596 /* _UIB-CODE-BLOCK-END */
597 &ANALYZE-RESUME
599 &ENDIF
601 &IF DEFINED(EXCLUDE-create-review-change) = 0 &THEN
603 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE create-review-change Procedure
604 PROCEDURE create-review-change :
605 /*------------------------------------------------------------------------------
606 Purpose:
607 ------------------------------------------------------------------------------*/
608 DEF BUFFER LastCharge FOR RentCharge.
610 IF NOT AVAILABLE RentCharge THEN DO:
611 FIND LAST LastCharge WHERE LastCharge.TenancyLeaseCode = RentReview.TenancyLeaseCode
612 NO-LOCK NO-ERROR.
613 CREATE RentCharge.
614 ASSIGN RentCharge.TenancyLeaseCode = TenancyLease.TenancyLeaseCode
615 RentCharge.SequenceCode = IF AVAILABLE LastCharge THEN LastCharge.SequenceCode + 1 ELSE 1
616 RentCharge.RentChargeType = "RENT"
617 RentCharge.Description = "Rental"
618 RentCharge.EntityType = ""
619 RentCharge.EntityCode = 0
620 RentCharge.AccountCode = rent-account.
621 END.
623 CREATE RentChargeLine.
624 ASSIGN RentChargeLine.TenancyLeaseCode = RentCharge.TenancyLeaseCode
625 RentChargeLine.SequenceCode = RentCharge.SequenceCode
626 RentChargeLine.RentChargeLineStatus = "R"
627 RentChargeLine.StartDate = RentReview.NewRentStart
628 RentChargeLine.EndDate = ?
629 RentChargeLine.Amount = RentReview.NewRental
630 RentChargeLine.FrequencyCode = IF TenancyLease.PaymentFrequency <> ""
631 THEN TenancyLease.PaymentFrequency ELSE "MNTH" .
633 END PROCEDURE.
635 /* _UIB-CODE-BLOCK-END */
636 &ANALYZE-RESUME
638 &ENDIF
640 /* ************************ Function Implementations ***************** */
642 &IF DEFINED(EXCLUDE-convert-from-yearly) = 0 &THEN
644 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION convert-from-yearly Procedure
645 FUNCTION convert-from-yearly RETURNS DECIMAL
646 ( INPUT amount AS DEC, INPUT freq AS CHAR ) :
647 /*------------------------------------------------------------------------------
648 Purpose:
649 Notes:
650 ------------------------------------------------------------------------------*/
652 DEF VAR n-months AS INT NO-UNDO INITIAL ?.
653 DEF VAR n-days AS INT NO-UNDO INITIAL ?.
655 /* mostly we are dealing with months, so to be slightly more efficient... */
656 IF freq = "MNTH" THEN n-months = 1. ELSE n-months = get-freq-months( freq ).
657 IF n-months <> ? THEN RETURN ROUND( amount / 12 * n-months, 2 ).
659 n-days = get-freq-days( freq ).
660 IF n-days <> ? THEN RETURN ROUND( amount / 365 * n-days, 2 ).
662 RETURN 0.00. /* Function return value. */
664 END FUNCTION.
666 /* _UIB-CODE-BLOCK-END */
667 &ANALYZE-RESUME
669 &ENDIF
671 &IF DEFINED(EXCLUDE-get-prop-og) = 0 &THEN
673 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION get-prop-og Procedure
674 FUNCTION get-prop-og RETURNS DECIMAL
675 ( INPUT doit AS LOGICAL, INPUT pc AS INTEGER, INPUT ac AS DECIMAL ) :
676 /*------------------------------------------------------------------------------
677 Purpose:
678 Notes:
679 ------------------------------------------------------------------------------*/
680 IF doit <> Yes THEN RETURN 1.0 .
681 FIND PropertyOutgoing WHERE PropertyOutgoing.PropertyCode = pc
682 AND PropertyOutgoing.AccountCode = ac NO-LOCK NO-ERROR.
683 IF AVAILABLE(PropertyOutgoing) THEN
684 RETURN PropertyOutgoing.BudgetAmount / 100 .
686 RETURN 0.00 .
688 END FUNCTION.
690 /* _UIB-CODE-BLOCK-END */
691 &ANALYZE-RESUME
693 &ENDIF
695 &IF DEFINED(EXCLUDE-last-trans-date) = 0 &THEN
697 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION last-trans-date Procedure
698 FUNCTION last-trans-date RETURNS DATE
699 ( INPUT account-code AS DEC ) :
700 /*------------------------------------------------------------------------------
701 Purpose: Return a logical last charged date for the given tenant and account
702 Notes:
703 ------------------------------------------------------------------------------*/
704 DEF VAR default-date AS DATE NO-UNDO.
706 default-date = IF TenancyLease.RentEndDate <> ?
707 THEN MINIMUM( TenancyLease.RentEndDate, default-last-date )
708 ELSE default-last-date.
710 DEF VAR charge-month LIKE Month.MonthCode INIT ? NO-UNDO.
711 FIND Tenant OF TenancyLease NO-LOCK NO-ERROR.
712 IF NOT AVAILABLE Tenant THEN RETURN default-date.
714 FIND LAST AcctTran WHERE AcctTran.EntityType = Tenant.EntityType
715 AND AcctTran.EntityCode = Tenant.EntityCode
716 AND AcctTran.AccountCode = account-code
717 AND AcctTran.Reference = "T" + STRING(Tenant.TenantCode)
718 NO-LOCK NO-ERROR.
719 IF AVAILABLE AcctTran THEN charge-month = AcctTran.MonthCode.
721 IF charge-month <> ? THEN DO:
722 FIND Month WHERE Month.MonthCode = charge-month NO-LOCK NO-ERROR.
723 IF AVAILABLE Month THEN RETURN MAX(Month.EndDate, default-date).
724 END.
726 RETURN default-date.
728 END FUNCTION.
730 /* _UIB-CODE-BLOCK-END */
731 &ANALYZE-RESUME
733 &ENDIF