Add blank column, rename column.
[capital-apms-progress.git] / process / report / schdakld.p
blob11a3550e883ee004be08feb62d7509017fa653a2
1 &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12
2 &ANALYZE-RESUME
3 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS Procedure
4 /*--------------------------------------------------------------------------
5 ------------------------------------------------------------------------*/
6 DEF INPUT PARAMETER report-options AS CHAR NO-UNDO.
8 DEF VAR preview AS LOGICAL NO-UNDO.
9 DEF VAR property-1 AS INTEGER NO-UNDO.
10 DEF VAR property-n AS INTEGER NO-UNDO.
11 DEF VAR print-main-schedule AS LOGICAL INITIAL Yes NO-UNDO.
12 DEF VAR print-outgoing-page AS LOGICAL INITIAL ? NO-UNDO.
13 DEF VAR outgoings-amounts AS LOGICAL INITIAL No NO-UNDO.
14 DEF VAR contract-rents AS LOGICAL INITIAL No NO-UNDO.
15 DEF VAR no-notes AS LOGICAL INITIAL No NO-UNDO.
16 DEF VAR selection-style AS CHAR NO-UNDO.
17 DEF VAR test-client-code AS CHAR NO-UNDO INITIAL ?.
18 DEF VAR company-list AS CHAR NO-UNDO INITIAL ?.
19 DEF VAR show-warnings AS LOGI NO-UNDO INITIAL ?.
20 RUN parse-parameters.
22 /* for accumulating outgoing details over a property */
23 DEF WORK-TABLE bldg-sublease NO-UNDO LIKE SubLease.
24 DEF WORK-TABLE og-acct NO-UNDO
25 FIELD AccountCode LIKE ChartOfAccount.AccountCode
26 FIELD ShortName AS CHAR FORMAT "X(9)"
27 FIELD Recovered AS DECIMAL
28 FIELD Gross AS DECIMAL
29 FIELD Vacant AS DECIMAL.
30 DEFINE WORKFILE og-desc NO-UNDO
31 FIELD percent AS DEC
32 FIELD accounts AS CHAR
33 FIELD description AS CHAR
34 FIELD count AS INT.
36 /* page control */
37 DEF VAR prt-ctrl AS CHAR NO-UNDO.
38 DEF VAR cols AS INT NO-UNDO.
39 DEF VAR rows AS INT NO-UNDO.
40 DEF VAR first-building AS LOGICAL INITIAL yes NO-UNDO.
41 DEF VAR user-name AS CHAR NO-UNDO.
42 {inc/username.i "user-name"}
44 {inc/ofc-this.i}
45 {inc/ofc-set-l.i "Use-Rent-Charges" "use-rent-charges"}
46 {inc/ofc-set.i "RentCharge-Outgoings" "og-rentcharge-type"}
47 IF NOT AVAILABLE(OfficeSetting) THEN og-rentcharge-type = "".
49 /* page header */
50 &SCOPED-DEFINE page-width 205
51 &SCOPED-DEFINE with-clause NO-BOX USE-TEXT NO-LABELS WIDTH {&page-width}
53 DEF VAR timeStamp AS CHAR FORMAT "X(40)" NO-UNDO.
54 timeStamp = STRING( TODAY, "99/99/9999") + ", " + STRING( TIME, "HH:MM:SS") + " for " + user-name.
55 DEF VAR hline2 AS CHAR FORMAT "X({&page-width})" NO-UNDO.
56 DEF VAR hline3 AS CHAR FORMAT "X({&page-width})" NO-UNDO.
57 DEF VAR hline4 AS CHAR FORMAT "X({&page-width})" NO-UNDO.
58 DEF VAR col-head1-base AS CHAR FORMAT "X({&page-width})" NO-UNDO.
59 DEF VAR col-head2-base AS CHAR FORMAT "X({&page-width})" NO-UNDO.
60 DEF VAR col-head1 AS CHAR FORMAT "X({&page-width})" NO-UNDO.
61 DEF VAR col-head2 AS CHAR FORMAT "X({&page-width})" NO-UNDO.
62 DEF VAR u-line AS CHAR NO-UNDO.
63 u-line = FILL("-",{&page-width}).
64 DEF VAR e-line AS CHAR NO-UNDO.
65 e-line = FILL("=",{&page-width}).
67 /* SUBSTRING(u-line,vert-pos) = "+". */
68 DEFINE FRAME heading-frame WITH 1 DOWN {&with-clause} PAGE-TOP.
69 FORM HEADER
70 timeStamp "Page " + STRING( PAGE-NUMBER ) TO {&page-width} SKIP (1)
71 hline2 SKIP hline3 SKIP (1) hline4 SKIP (1)
72 col-head1 SKIP col-head2 SKIP (1) u-line FORMAT "X({&page-width})"
73 WITH FRAME heading-frame.
75 DEF VAR vert-pos AS INT NO-UNDO INITIAL 88.
77 col-head1-base = "Rental Space | Tenant Lease | | |Renew rights | Rent Reviews | Outgoings".
78 col-head2-base = "Description Area Rate Contracted Charged | Name | %age Outgoing | Term | Expires |Notice Term |Status Notice Date | Contributions".
79 IF contract-rents THEN DO:
80 col-head1-base = "Rental Space | Tenant Lease | | |Renew rights | Rent Reviews | Outgoings".
81 col-head2-base = "Description Area Rate Contracted | Name | %age Outgoing | Term | Expires |Notice Term |Status Notice Date | Contributions".
82 vert-pos = vert-pos - 15.
83 END.
85 /* Formats */
86 DEF VAR area-format AS CHAR NO-UNDO.
87 DEF VAR unit-format AS CHAR NO-UNDO.
88 DEF VAR money-format AS CHAR NO-UNDO.
89 area-format = "->>>,>>9.99".
90 unit-format = "->>>,>>9".
91 money-format = "->>,>>>,>>9.99".
93 &GLOB FIELD-COUNT 20
94 DEF VAR f AS CHAR EXTENT {&FIELD-COUNT} NO-UNDO. /* an array of the fields we will print */
95 DEF VAR f-fmt AS CHAR EXTENT {&FIELD-COUNT} NO-UNDO.
96 ASSIGN
97 f-fmt[1] = "X(24)" f-fmt[2] = "X(16)" /* description, units */
98 f-fmt[3] = "X(14)" f-fmt[4] = "X(14)" /* rate, contracted */
99 f-fmt[5] = "X(14)" f-fmt[6] = "X(1)" /* charged, filler */
100 f-fmt[7] = "X(24)" f-fmt[8] = "X(8)" /* name, og percent */
101 f-fmt[9] = "X(12)" f-fmt[10] = "X(8)" /* og-desc, term */
102 f-fmt[11] = "X(10)" f-fmt[12] = "X(4)" /* expiry, renew notice */
103 f-fmt[13] = "X(8)" f-fmt[14] = "X(4)" /* renew term, rr freq */
104 f-fmt[15] = "X(4)" f-fmt[16] = "X(10)" /* rr notice, rr due */
105 f-fmt[17] = "X(13)" f-fmt[18] = "X(8)" /* og contrib */
106 f-fmt[19] = "X(8)" f-fmt[20] = "X(8)"
109 /* Accumulators */
110 DEF VAR level-lines AS INT NO-UNDO.
111 DEF VAR level-area AS DECIMAL NO-UNDO.
112 DEF VAR level-parks AS DECIMAL NO-UNDO.
113 DEF VAR level-contract AS DECIMAL NO-UNDO.
114 DEF VAR level-charged AS DECIMAL NO-UNDO.
116 DEF VAR bldg-area AS DECIMAL NO-UNDO.
117 DEF VAR bldg-contract AS DECIMAL NO-UNDO.
118 DEF VAR bldg-charged AS DECIMAL NO-UNDO.
119 DEF VAR bldg-outgoings AS DECIMAL NO-UNDO.
120 DEF VAR total-break AS INTEGER NO-UNDO.
122 DEF VAR grand-area AS DECIMAL NO-UNDO.
123 DEF VAR grand-contract AS DECIMAL NO-UNDO.
124 DEF VAR grand-charged AS DECIMAL NO-UNDO.
126 DEF VAR space-notes AS CHAR NO-UNDO.
127 DEF VAR lease-notes AS CHAR NO-UNDO.
128 DEF VAR various-notes AS CHAR NO-UNDO.
129 DEF VAR bldg-notes AS CHAR NO-UNDO.
130 DEF VAR notes-list AS CHAR NO-UNDO.
131 DEF VAR rs-notes AS CHAR NO-UNDO.
132 DEF VAR rs-codes AS CHAR NO-UNDO.
133 DEF VAR tl-notes AS CHAR NO-UNDO.
134 DEF VAR tl-codes AS CHAR NO-UNDO.
136 DEF VAR lease-list AS CHAR NO-UNDO.
137 DEF VAR first-appearance AS LOGICAL NO-UNDO.
139 DEF VAR out-line AS CHAR NO-UNDO.
141 /* _UIB-CODE-BLOCK-END */
142 &ANALYZE-RESUME
145 &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
147 /* ******************** Preprocessor Definitions ******************** */
149 &Scoped-define PROCEDURE-TYPE Procedure
150 &Scoped-define DB-AWARE no
154 /* _UIB-PREPROCESSOR-BLOCK-END */
155 &ANALYZE-RESUME
158 /* ************************ Function Prototypes ********************** */
160 &IF DEFINED(EXCLUDE-get-prop-og) = 0 &THEN
162 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD get-prop-og Procedure
163 FUNCTION get-prop-og RETURNS DECIMAL
164 ( INPUT doit AS LOGICAL, INPUT pc AS INTEGER, INPUT ac AS DECIMAL ) FORWARD.
166 /* _UIB-CODE-BLOCK-END */
167 &ANALYZE-RESUME
169 &ENDIF
171 &IF DEFINED(EXCLUDE-test-floor-space) = 0 &THEN
173 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD test-floor-space Procedure
174 FUNCTION test-floor-space RETURNS CHARACTER
175 ( INPUT type AS CHAR, INPUT area AS DECIMAL ) FORWARD.
177 /* _UIB-CODE-BLOCK-END */
178 &ANALYZE-RESUME
180 &ENDIF
183 /* *********************** Procedure Settings ************************ */
185 &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
186 /* Settings for THIS-PROCEDURE
187 Type: Procedure
188 Allow:
189 Frames: 0
190 Add Fields to: Neither
191 Other Settings: CODE-ONLY COMPILE
193 &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
195 /* ************************* Create Window ************************** */
197 &ANALYZE-SUSPEND _CREATE-WINDOW
198 /* DESIGN Window definition (used by the UIB)
199 CREATE WINDOW Procedure ASSIGN
200 HEIGHT = .35
201 WIDTH = 34.86.
202 /* END WINDOW DEFINITION */
204 &ANALYZE-RESUME
206 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB Procedure
207 /* ************************* Included-Libraries *********************** */
209 {inc/method/m-txtrep.i}
210 {inc/method/m-charged-rent.i}
212 /* _UIB-CODE-BLOCK-END */
213 &ANALYZE-RESUME
219 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK Procedure
222 /* *************************** Main Block *************************** */
224 RUN make-control-string ( "PCL", "reset,landscape,tm,4,a4,lm,5,courier,cpi,20,lpi,9.5",
225 OUTPUT prt-ctrl, OUTPUT rows, OUTPUT cols ).
226 /* MESSAGE "Apparently" cols "by" rows VIEW-AS ALERT-BOX INFORMATION. */
228 RUN output-control-file ( prt-ctrl ).
229 OUTPUT TO VALUE(txtrep-print-file) KEEP-MESSAGES PAGE-SIZE VALUE(rows).
231 IF selection-style = "OneClient" THEN RUN for-one-client.
232 ELSE IF selection-style = "CompanyList" THEN RUN for-company-list.
233 ELSE
234 RUN for-each-property.
236 OUTPUT CLOSE.
237 RUN view-output-file ( preview ).
239 /* _UIB-CODE-BLOCK-END */
240 &ANALYZE-RESUME
243 /* ********************** Internal Procedures *********************** */
245 &IF DEFINED(EXCLUDE-building-notes) = 0 &THEN
247 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE building-notes Procedure
248 PROCEDURE building-notes :
249 /*------------------------------------------------------------------------------
250 Purpose:
251 Parameters: <none>
252 Notes:
253 ------------------------------------------------------------------------------*/
255 END PROCEDURE.
257 /* _UIB-CODE-BLOCK-END */
258 &ANALYZE-RESUME
260 &ENDIF
262 &IF DEFINED(EXCLUDE-clear-property) = 0 &THEN
264 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE clear-property Procedure
265 PROCEDURE clear-property :
266 /*------------------------------------------------------------------------------
267 Purpose: Clear the work-tables we are using for each property
268 ------------------------------------------------------------------------------*/
269 FOR EACH bldg-sublease: DELETE bldg-sublease. END.
270 FOR EACH og-acct: DELETE og-acct. END.
271 ASSIGN bldg-area = 0 bldg-contract = 0 bldg-charged = 0 bldg-outgoings = 0
272 total-break = 90 notes-list = "" lease-list = "|"
273 rs-notes = "" rs-codes = ""
274 tl-notes = "" tl-codes = "".
275 END PROCEDURE.
277 /* _UIB-CODE-BLOCK-END */
278 &ANALYZE-RESUME
280 &ENDIF
282 &IF DEFINED(EXCLUDE-each-rental-space) = 0 &THEN
284 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE each-rental-space Procedure
285 PROCEDURE each-rental-space :
286 /*------------------------------------------------------------------------------
287 Purpose:
288 ------------------------------------------------------------------------------*/
289 DEF VAR out-line AS CHAR NO-UNDO.
290 DEF VAR i AS INT NO-UNDO.
291 DEF VAR rs-desc AS CHAR NO-UNDO.
292 DEF VAR charged-rental AS DEC NO-UNDO.
294 DO i = 1 TO {&FIELD-COUNT}: f[i] = "". END.
295 RUN save-up-notes( RentalSpace.RentalSpaceCode, RentalSpace.NoteCode, RentalSpace.Description, OUTPUT rs-desc , INPUT-OUTPUT rs-notes, INPUT-OUTPUT rs-codes ).
296 f[1] = WRAP( rs-desc, 24).
297 CASE test-floor-space( RentalSpace.AreaType, RentalSpace.AreaSize):
298 WHEN "Park" THEN DO:
299 f[2] = STRING( RentalSpace.AreaSize, unit-format) + " parks".
300 f[3] = STRING( ((RentalSpace.ContractedRental / RentalSpace.AreaSize) / 52), "->>,>>9.99 pw ").
301 level-parks = level-parks + (IF RentalSpace.AreaSize <> ? THEN RentalSpace.AreaSize ELSE 0).
302 END.
303 WHEN "Yes" THEN DO:
304 f[2] = STRING( RentalSpace.AreaSize, area-format) + " sq.M".
305 f[3] = STRING( (RentalSpace.ContractedRental / RentalSpace.AreaSize), "->>,>>9.99 psm").
306 level-area = level-area + (IF RentalSpace.AreaSize <> ? THEN RentalSpace.AreaSize ELSE 0).
307 END.
308 OTHERWISE DO:
309 IF RentalSpace.AreaType = "N" THEN
310 f[2] = STRING( RentalSpace.AreaSize, unit-format) + " rights".
311 ELSE
312 f[2] = STRING( RentalSpace.AreaSize, unit-format) + " units".
313 END.
314 END.
316 IF RentalSpace.AreaStatus = "V"
317 OR NOT CAN-FIND( TenancyLease OF RentalSpace WHERE TenancyLease.LeaseStatus <> "PAST" )
318 THEN ASSIGN
319 f[4] = STRING( 0, money-format)
320 f[5] = STRING( 0, money-format)
321 f[7] = "* * * VACANT * * *".
322 ELSE DO:
323 ASSIGN
324 charged-rental = get-charged-rent( RentalSpace.ChargedRental, RentalSpace.ContractedRental, RentalSpace.AreaType, RentalSpace.TenancyLeaseCode )
325 f[4] = STRING( RentalSpace.ContractedRental, money-format)
326 f[5] = STRING( charged-rental, money-format)
327 level-contract = level-contract + (IF RentalSpace.ContractedRental <> ? THEN RentalSpace.ContractedRental ELSE 0)
328 level-charged = level-charged + charged-rental
330 RUN get-lease-details.
331 END.
333 DEF VAR ln-count AS INTEGER INITIAL 1 NO-UNDO.
334 DO WHILE true:
335 RUN rental-space-line( ln-count, OUTPUT out-line ).
336 IF TRIM(out-line) = "" THEN LEAVE. /* We've finished! */
337 RUN print-line( out-line, yes ).
338 ln-count = ln-count + 1.
339 END.
341 ASSIGN space-notes = "" lease-notes = "" .
342 END PROCEDURE.
344 /* _UIB-CODE-BLOCK-END */
345 &ANALYZE-RESUME
347 &ENDIF
349 &IF DEFINED(EXCLUDE-for-company-list) = 0 &THEN
351 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE for-company-list Procedure
352 PROCEDURE for-company-list :
353 /*------------------------------------------------------------------------------
354 Purpose:
355 ------------------------------------------------------------------------------*/
356 DEF VAR i AS INT NO-UNDO.
357 DEF VAR n AS INT NO-UNDO.
358 DEF VAR company-code AS INT NO-UNDO.
360 ASSIGN grand-area = 0 grand-contract = 0 grand-charged = 0 .
361 FIND ConsolidationList WHERE ConsolidationList.Name = company-list NO-LOCK.
362 n = NUM-ENTRIES( ConsolidationList.CompanyList ).
363 DO i = 1 TO n:
364 company-code = INT( ENTRY( i, ConsolidationList.CompanyList ) ).
365 FOR EACH Property WHERE Property.CompanyCode = company-code
366 AND Property.Active NO-LOCK:
368 RUN clear-property.
369 IF print-main-schedule THEN RUN property-schedule.
370 IF print-outgoing-page THEN RUN outgoings-page( outgoings-amounts ).
372 PUT SKIP (2).
373 out-line = "* * * * * * * * * * End of Property " + STRING(Property.PropertyCode) + " " + Property.Name + " * * * * * * * * * *".
374 out-line = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(out-line) ) / 2)) + out-line.
375 RUN print-line( out-line, no ).
376 END.
377 END.
378 RUN grand-totals.
381 END PROCEDURE.
383 /* _UIB-CODE-BLOCK-END */
384 &ANALYZE-RESUME
386 &ENDIF
388 &IF DEFINED(EXCLUDE-for-each-property) = 0 &THEN
390 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE for-each-property Procedure
391 PROCEDURE for-each-property :
392 /*------------------------------------------------------------------------------
393 Purpose:
394 ------------------------------------------------------------------------------*/
396 ASSIGN grand-area = 0 grand-contract = 0 grand-charged = 0 .
397 FOR EACH Property WHERE Property.Active AND Property.PropertyCode >= property-1
398 AND Property.PropertyCode <= property-n
399 NO-LOCK:
400 RUN clear-property.
401 IF print-main-schedule THEN RUN property-schedule.
402 IF print-outgoing-page THEN RUN outgoings-page( outgoings-amounts ).
404 PUT SKIP (2).
405 out-line = "* * * * * * * * * * End of Property " + STRING(Property.PropertyCode) + " " + Property.Name + " * * * * * * * * * *".
406 out-line = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(out-line) ) / 2)) + out-line.
407 RUN print-line( out-line, no ).
409 END.
410 RUN grand-totals.
413 END PROCEDURE.
415 /* _UIB-CODE-BLOCK-END */
416 &ANALYZE-RESUME
418 &ENDIF
420 &IF DEFINED(EXCLUDE-for-one-client) = 0 &THEN
422 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE for-one-client Procedure
423 PROCEDURE for-one-client :
424 /*------------------------------------------------------------------------------
425 Purpose:
426 ------------------------------------------------------------------------------*/
428 ASSIGN grand-area = 0 grand-contract = 0 grand-charged = 0 .
429 FOR EACH Company WHERE Company.ClientCode = test-client-code NO-LOCK:
430 FOR EACH Property OF Company WHERE Property.Active NO-LOCK:
431 RUN clear-property.
432 IF print-main-schedule THEN RUN property-schedule.
433 IF print-outgoing-page THEN RUN outgoings-page( outgoings-amounts ).
435 PUT SKIP (2).
436 out-line = "* * * * * * * * * * End of Property " + STRING(Property.PropertyCode) + " " + Property.Name + " * * * * * * * * * *".
437 out-line = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(out-line) ) / 2)) + out-line.
438 RUN print-line( out-line, no ).
439 END.
440 END.
441 RUN grand-totals.
444 END PROCEDURE.
446 /* _UIB-CODE-BLOCK-END */
447 &ANALYZE-RESUME
449 &ENDIF
451 &IF DEFINED(EXCLUDE-get-last-notes) = 0 &THEN
453 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-last-notes Procedure
454 PROCEDURE get-last-notes :
455 /*------------------------------------------------------------------------------
456 Purpose: Collect together various pieces of inforrmation as notes
457 ------------------------------------------------------------------------------*/
458 DEF VAR a-line AS CHAR NO-UNDO.
460 notes-list = "".
461 various-notes = "".
462 RUN get-notes( Property.NoteCode, OUTPUT bldg-notes).
463 IF bldg-notes <> "" THEN bldg-notes = CHR(10) + "Building Notes" + CHR(10) + "--------------" + CHR(10) + CHR(10) + SUBSTRING( bldg-notes, 5).
464 bldg-notes = wrap( bldg-notes, 100 ).
466 /* sub leases for the building */
467 IF CAN-FIND( FIRST bldg-sublease ) THEN DO:
468 various-notes = various-notes + CHR(10) + "Sub Leases" + CHR(10) + "----------" + CHR(10).
469 FOR EACH bldg-sublease:
470 FIND TenancyLease OF bldg-sublease NO-LOCK.
471 FIND Tenant OF Tenancylease NO-LOCK NO-ERROR.
472 various-notes = various-notes + (IF AVAILABLE(Tenant) THEN Tenant.Name ELSE "Tenant not on file") + CHR(10).
473 various-notes = various-notes + " To: " + bldg-sublease.Name + CHR(10).
474 a-line = (IF bldg-sublease.AnnualRental > 0 THEN (" Rent:" + STRING( bldg-sublease.AnnualRental, money-format)) ELSE "")
475 + (IF bldg-sublease.LeaseStartDate > DATE(1,1,1) THEN (" Start:" + STRING( bldg-sublease.LeaseStartDate, "99/99/9999")) ELSE "")
476 + (IF bldg-sublease.LeaseEndDate > DATE(1,1,1) THEN (" End:" + STRING( bldg-sublease.LeaseEndDate, "99/99/9999")) ELSE "").
477 IF TRIM(a-line) <> "" THEN various-notes = various-notes + a-line + CHR(10).
478 IF TRIM(bldg-sublease.Detail) <> "" THEN various-notes = various-notes + bldg-sublease.Detail + CHR(10).
479 various-notes = various-notes + CHR(10).
480 END.
481 various-notes = various-notes + CHR(10).
482 END.
484 /* frontages for the building */
485 IF CAN-FIND( FIRST StreetFrontage WHERE StreetFrontage.PropertyCode = Property.PropertyCode ) THEN DO:
486 various-notes = various-notes + CHR(10) + "Frontages" + CHR(10) + "---------" + CHR(10).
487 FOR EACH StreetFrontage WHERE StreetFrontage.PropertyCode = Property.PropertyCode NO-LOCK:
488 various-notes = various-notes + STRING( StreetFrontage.Length, ">>>>>>9.99m ") + StreetFrontage.Description + CHR(10).
489 END.
490 END.
492 END PROCEDURE.
494 /* _UIB-CODE-BLOCK-END */
495 &ANALYZE-RESUME
497 &ENDIF
499 &IF DEFINED(EXCLUDE-get-lease-details) = 0 &THEN
501 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-lease-details Procedure
502 PROCEDURE get-lease-details :
503 /*------------------------------------------------------------------------------
504 Purpose:
505 ------------------------------------------------------------------------------*/
506 FIND TenancyLease OF RentalSpace WHERE TenancyLease.LeaseStatus <> "PAST" NO-LOCK NO-ERROR.
507 IF AVAILABLE(TenancyLease) THEN DO:
508 first-appearance = INDEX( lease-list, "|" + STRING(TenancyLease.TenancyLeaseCode,"99999") + "|") = 0.
509 IF first-appearance THEN lease-list = lease-list + STRING(TenancyLease.TenancyLeaseCode,"99999") + "|".
511 RUN get-notes( TenancyLease.NoteCode, OUTPUT lease-notes ).
512 RUN get-tenant-details.
513 RUN save-up-notes( TenancyLease.TenancyLeaseCode, TenancyLease.NoteCode, f[7], OUTPUT f[7], INPUT-OUTPUT tl-notes, INPUT-OUTPUT tl-codes ).
514 f[7] = wrap( f[7], 24 ).
515 RUN get-outgoings-details.
516 /* IF NOT first-appearance AND f[8] <> "" THEN ASSIGN f[8] = " as" f[9] = " above". */
518 f[10] = (IF TenancyLease.TermYears > 0 THEN TRIM( STRING( TenancyLease.TermYears, ">>>9y")) ELSE "")
519 + (IF TenancyLease.TermMonths > 0 THEN TRIM( STRING( TenancyLease.TermMonths, ">9m")) ELSE "")
520 + (IF TenancyLease.TermDays > 0 THEN TRIM( STRING( TenancyLease.TermDays, ">9d")) ELSE "").
521 IF (TenancyLease.TermYears < 1 AND TenancyLease.TermMonths <= 1)
522 OR TenancyLease.LeaseEndDate = ?
523 OR f[10] = ""
524 THEN f[10] = "monthly".
525 f[10] = FILL(' ', INTEGER((8 - LENGTH(f[10])) / 2)) + f[10].
527 f[11] = STRING( TenancyLease.LeaseEndDate, "99/99/9999").
528 f[12] = (IF TenancyLease.RORNoticePeriod > 0 THEN STRING( TenancyLease.RORNoticePeriod, ">>9m") ElSE "").
529 f[13] = (IF TenancyLease.RightsOfRenewal <> ? THEN TenancyLease.RightsOfRenewal ElSE "").
531 RUN get-review-details.
533 FOR EACH SubLease OF TenancyLease NO-LOCK:
534 FIND FIRST bldg-sublease WHERE bldg-sublease.TenancyLeaseCode = SubLease.TenancyLeaseCode
535 AND bldg-sublease.SubLeaseCode = SubLease.SubLeaseCode NO-LOCK NO-ERROR.
536 IF NOT AVAILABLE(bldg-sublease) THEN CREATE bldg-sublease.
537 ASSIGN
538 bldg-sublease.Name = SubLease.Name
539 bldg-sublease.TenancyLeaseCode = SubLease.TenancyLeaseCode
540 bldg-sublease.SubLeaseCode = SubLease.SubLeaseCode
541 bldg-sublease.LeaseStartDate = SubLease.LeaseStartDate
542 bldg-sublease.LeaseEndDate = SubLease.LeaseEndDate
543 bldg-sublease.AnnualRental = SubLease.AnnualRental
544 bldg-sublease.Details = SubLease.Details
546 END.
547 END.
548 ELSE DO:
549 f[7] = "Lease not on file!".
550 END.
551 END PROCEDURE.
553 /* _UIB-CODE-BLOCK-END */
554 &ANALYZE-RESUME
556 &ENDIF
558 &IF DEFINED(EXCLUDE-get-notes) = 0 &THEN
560 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-notes Procedure
561 PROCEDURE get-notes :
562 /*------------------------------------------------------------------------------
563 Purpose:
564 ------------------------------------------------------------------------------*/
565 DEF INPUT PARAMETER note-code AS INTEGER NO-UNDO.
566 DEF OUTPUT PARAMETER note-detail AS CHAR NO-UNDO.
568 DEF VAR i AS INT NO-UNDO.
569 DEF VAR no-notes AS INT NO-UNDO.
571 /* search the list of notes already displayed for this property */
572 no-notes = NUM-ENTRIES( notes-list).
573 DO i = 1 TO no-notes:
574 IF note-code = INTEGER(ENTRY(i,notes-list)) THEN DO:
575 note-detail = "see note [" + TRIM( STRING( i, ">>9")) + "] above.".
576 note-code = 0.
577 RETURN.
578 END.
579 END.
581 IF note-code > 0 THEN DO:
582 IF notes-list <> "" THEN notes-list = notes-list + ",".
583 notes-list = notes-list + TRIM(STRING( note-code, ">>>>>>>9")).
584 FIND Note WHERE Note.NoteCode = note-code NO-LOCK NO-ERROR.
585 note-detail = (IF AVAILABLE(Note)
586 THEN "[" + TRIM( STRING(no-notes + 1, ">>9")) + "] " + Note.Detail
587 ELSE "" ).
588 END.
589 ELSE
590 note-detail = "".
592 END PROCEDURE.
594 /* _UIB-CODE-BLOCK-END */
595 &ANALYZE-RESUME
597 &ENDIF
599 &IF DEFINED(EXCLUDE-get-outgoings-details) = 0 &THEN
601 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-outgoings-details Procedure
602 PROCEDURE get-outgoings-details :
603 /*------------------------------------------------------------------------------
604 Purpose: Return the outgoings details for the schedule.
605 ------------------------------------------------------------------------------*/
606 DEF VAR og-chars AS CHAR NO-UNDO.
607 DEF VAR first-desc AS LOGICAL INITIAL Yes NO-UNDO.
608 DEF VAR i AS INT NO-UNDO.
610 ASSIGN f[8] = "" f[9] = "".
611 IF TenancyLease.GrossLease THEN
612 f[17] = "Gross Lease".
613 ELSE IF first-appearance AND TenancyLease.OutgoingsBudget <> 0 THEN DO:
614 f[17] = STRING( TenancyLease.OutgoingsBudget, ">>,>>>,>>9.99").
615 bldg-outgoings = bldg-outgoings + TenancyLease.OutgoingsBudget.
616 END.
617 ELSE IF TenancyLease.OutgoingsBudget <> 0 THEN DO:
618 f[17] = " above".
619 END.
621 FOR EACH og-desc: DELETE og-desc. END.
622 FOR EACH TenancyOutgoing OF TenancyLease NO-LOCK,
623 FIRST ChartOfAccount OF TenancyOutgoing NO-LOCK:
624 FIND FIRST og-desc WHERE og-desc.percent = TenancyOutgoing.Percentage NO-ERROR.
625 IF AVAILABLE(og-desc) THEN ASSIGN
626 og-desc.accounts = og-desc.accounts + "," + STRING(TenancyOutgoing.AccountCode)
627 og-desc.description = og-desc.description + "~n" + ChartOfAccount.ShortName
628 og-desc.count = og-desc.count + 1.
629 ELSE DO:
630 CREATE og-desc.
631 og-desc.percent = TenancyOutgoing.Percentage.
632 og-desc.accounts = STRING(TenancyOutgoing.AccountCode).
633 og-desc.description = ChartOfAccount.ShortName.
634 og-desc.count = 1.
635 END.
636 END.
638 FOR EACH og-desc NO-LOCK BY og-desc.Count DESCENDING
639 BY og-desc.percent DESCENDING:
640 og-chars = STRING( og-desc.percent, ">>9.99" ).
641 IF NOT first-appearance THEN og-chars = "(" + og-chars + ")".
643 IF NUM-ENTRIES(og-desc.description, "~n") > 4 AND first-desc THEN ASSIGN
644 og-desc.description = "All"
645 first-desc = No.
647 DO i = 1 TO NUM-ENTRIES( og-desc.description, "~n"):
648 IF f[8] <> "" THEN ASSIGN f[8] = f[8] + "~n" f[9] = f[9] + "~n".
649 ASSIGN f[8] = f[8] + og-chars
650 f[9] = f[9] + ENTRY(i, og-desc.description, "~n").
652 END.
653 END.
655 END PROCEDURE.
657 /* _UIB-CODE-BLOCK-END */
658 &ANALYZE-RESUME
660 &ENDIF
662 &IF DEFINED(EXCLUDE-get-review-details) = 0 &THEN
664 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-review-details Procedure
665 PROCEDURE get-review-details :
666 /*------------------------------------------------------------------------------
667 Purpose: For each review, put the info on a new line
668 ------------------------------------------------------------------------------*/
669 ASSIGN f[14] = "" f[16] = "" .
670 FOR EACH RentReview OF TenancyLease WHERE RentReview.ReviewStatus <> "DONE"
671 AND RentReview.DateDue <> ? NO-LOCK:
672 IF f[16] <> "" THEN ASSIGN
673 f[14] = f[14] + CHR(10)
674 f[15] = f[15] + CHR(10)
675 f[16] = f[16] + CHR(10)
677 ELSE
678 f[15] = "".
679 ASSIGN
680 f[14] = f[14] + RentReview.ReviewStatus
681 f[15] = f[15] + (IF TenancyLease.ReviewNoticePeriod > 0 THEN STRING( TenancyLease.ReviewNoticePeriod, ">>9m") ElSE " 3m").
682 f[16] = f[16] + STRING( RentReview.DateDue, "99/99/9999")
684 END.
686 END PROCEDURE.
688 /* _UIB-CODE-BLOCK-END */
689 &ANALYZE-RESUME
691 &ENDIF
693 &IF DEFINED(EXCLUDE-get-saved-notes) = 0 &THEN
695 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-saved-notes Procedure
696 PROCEDURE get-saved-notes :
697 /*------------------------------------------------------------------------------
698 Purpose:
699 ------------------------------------------------------------------------------*/
700 DEF OUTPUT PARAMETER rs-text AS CHAR NO-UNDO.
701 DEF OUTPUT PARAMETER tl-text AS CHAR NO-UNDO.
703 DEF VAR i AS INT NO-UNDO.
704 DEF VAR n AS INT NO-UNDO.
705 DEF VAR code AS INT NO-UNDO.
706 DEF VAR note-text AS CHAR NO-UNDO.
707 DEF VAR type-code AS CHAR NO-UNDO.
708 DEF VAR guarantors AS CHAR NO-UNDO.
710 n = NUM-ENTRIES(rs-notes).
711 IF n > 0 THEN DO:
712 rs-text = "Rental Space Notes~n------------------~n".
713 DO i = 1 TO n:
714 code = INTEGER(ENTRY(i,rs-codes)).
715 FIND RentalSpace OF Property WHERE RentalSpaceCode = code NO-LOCK NO-ERROR.
716 code = INTEGER(ENTRY(i,rs-notes)).
717 FIND Note WHERE Note.NoteCode = code NO-LOCK.
718 rs-text = rs-text + "~n"
719 + STRING( STRING(i) + ".", "X(8)")
720 + ( IF AVAILABLE(RentalSpace) THEN
721 STRING( RentalSpace.Level ) + "-"
722 + STRING( RentalSpace.LevelSequence) + " "
723 + RentalSpace.Description
724 ELSE
725 "Rental Space not available(!)"
727 + "~n~n"
728 + Note.Detail + "~n".
729 END.
730 END.
732 n = NUM-ENTRIES(tl-notes).
733 IF n > 0 THEN DO:
734 tl-text = "Tenancy Lease Notes~n-------------------~n".
735 DO i = 1 TO n:
736 code = INTEGER(ENTRY(i,tl-codes)).
737 guarantors = "".
738 FIND TenancyLease OF Property WHERE TenancyLease.TenancyLeaseCode = code NO-LOCK NO-ERROR.
739 IF AVAILABLE(TenancyLease) THEN FIND Tenant OF TenancyLease NO-LOCK NO-ERROR.
741 IF AVAILABLE(TenancyLease) THEN DO:
742 FOR EACH Guarantor NO-LOCK OF TenancyLease, FIRST Person NO-LOCK OF Guarantor :
743 IF Guarantor.TYPE = "B" THEN type-code = "Bank". ELSE DO:
744 IF Guarantor.TYPE = "I" THEN type-code = "Individual". ELSE DO:
745 IF Guarantor.TYPE = "S" THEN type-code = "Security Deposit". ELSE type-code = "Company".
746 END.
747 END.
748 guarantors = guarantors + "Guarantee: " + type-code + ": "
749 + TRIM(STRING( Guarantor.Limit, ">>,>>>,>>9")) + " ".
750 guarantors = guarantors + (IF Guarantor.Type = "I" THEN Person.FirstName + " " + Person.LastName ELSE Person.Company) + "~n".
751 END.
752 IF guarantors <> "" THEN guarantors = guarantors + "~n".
753 END.
755 code = INTEGER(ENTRY(i,tl-notes)).
756 FIND Note WHERE Note.NoteCode = code NO-LOCK.
757 tl-text = tl-text + "~n"
758 + STRING( STRING(i) + ".", "X(8)")
759 + STRING( (IF AVAILABLE(Tenant) THEN STRING(Tenant.TenantCode, "99999") ELSE "no tenant"), "X(10)")
760 + (IF AVAILABLE(Tenant) THEN Tenant.Name ELSE "Lease >>" + STRING(code) + "<<") + "~n~n"
761 + guarantors
762 + Note.Detail + "~n".
763 END.
764 END.
765 END PROCEDURE.
767 /* _UIB-CODE-BLOCK-END */
768 &ANALYZE-RESUME
770 &ENDIF
772 &IF DEFINED(EXCLUDE-get-tenant-details) = 0 &THEN
774 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE get-tenant-details Procedure
775 PROCEDURE get-tenant-details :
776 /*------------------------------------------------------------------------------
777 Purpose: Get the tenant of the lease.
778 ------------------------------------------------------------------------------*/
780 FIND Tenant OF TenancyLease NO-LOCK NO-ERROR.
781 IF AVAILABLE(Tenant) THEN DO:
782 f[7] = Tenant.Name + " (T" + STRING( Tenant.TenantCode, "99999") + ")".
783 IF Tenant.Name <> Tenant.LegalName AND Tenant.LegalName <> "" THEN
784 f[7] = f[7] + "~nT/A: " + Tenant.LegalName.
786 /* Inactive tenants are not charged rental */
787 IF NOT tenant.active THEN DO:
788 level-contract = level-contract - (IF RentalSpace.ContractedRental <> ? THEN RentalSpace.ContractedRental ELSE 0).
789 level-charged = level-charged - (IF RentalSpace.ChargedRental <> ? THEN RentalSpace.ChargedRental ELSE 0).
790 f[5] = STRING( 0, money-format).
791 f[4] = STRING( 0, money-format).
792 f[5] = " inactive" + SUBSTRING( f[5], 10).
793 END.
794 END.
795 ELSE
796 f[7] = "Tenant not on file!".
798 END PROCEDURE.
800 /* _UIB-CODE-BLOCK-END */
801 &ANALYZE-RESUME
803 &ENDIF
805 &IF DEFINED(EXCLUDE-grand-totals) = 0 &THEN
807 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE grand-totals Procedure
808 PROCEDURE grand-totals :
809 /*------------------------------------------------------------------------------
810 Purpose: Display grand totals for report
811 ------------------------------------------------------------------------------*/
812 DEF VAR out-line AS CHAR NO-UNDO.
814 PUT SKIP (4).
816 RUN print-line( e-line, no).
817 out-line = STRING( "Total for Report", "X(25)")
818 + (IF grand-area > 0 THEN STRING( grand-area, area-format) + " square metres" ELSE FILL(' ',24))
819 + FILL(' ',7)
820 + STRING( grand-contract, money-format) + " "
821 + (IF contract-rents THEN "" ELSE STRING( grand-charged, money-format)).
822 RUN print-line( out-line, no ).
823 RUN print-line( e-line, no).
825 out-line = "* * * * * * End of Schedule * * * * * *".
826 out-line = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(out-line) ) / 2)) + out-line.
827 RUN print-line( out-line, no ).
829 END PROCEDURE.
831 /* _UIB-CODE-BLOCK-END */
832 &ANALYZE-RESUME
834 &ENDIF
836 &IF DEFINED(EXCLUDE-new-level) = 0 &THEN
838 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE new-level Procedure
839 PROCEDURE new-level :
840 /*------------------------------------------------------------------------------
841 Purpose:
842 ------------------------------------------------------------------------------*/
843 DEF INPUT PARAMETER last-level AS INT NO-UNDO.
844 DEF INPUT PARAMETER next-level AS INT NO-UNDO.
846 DEF VAR out-line AS CHAR NO-UNDO.
847 DEF VAR level-name AS CHAR NO-UNDO.
848 DEF VAR level-units AS CHAR NO-UNDO.
850 IF last-level <> -99999 AND level-lines > 1 THEN DO:
851 IF last-level = 99 THEN DO:
852 level-name = "Miscellaneous".
853 level-units = (IF level-area > 0 THEN STRING( level-area, area-format) + " square metres" ELSE "").
854 END.
855 ELSE IF last-level >= 90 THEN DO:
856 level-name = "Carparking".
857 level-units = (IF level-parks > 0 THEN STRING( level-parks, unit-format) + " parks" ELSE "").
858 END.
859 ELSE DO:
860 level-name = "Level " + TRIM( STRING(last-level,"->,>>9")).
861 level-units = (IF level-area > 0 THEN STRING( level-area, area-format) + " square metres" ELSE "").
862 END.
863 out-line = FILL(' ', 27) + STRING( "---------", "X(30)") + FILL('-',14) + ' ' + (IF contract-rents THEN "" ELSE FILL('-',14)).
864 RUN print-line( out-line, yes ).
865 out-line = FILL(' ', 4) + STRING( "Total " + level-name, "X(21)")
866 + STRING( level-units, "X(32)")
867 + STRING( level-contract, money-format) + " "
868 + (IF contract-rents THEN "" ELSE STRING( level-charged, money-format)).
869 RUN print-line( out-line, yes ).
870 RUN print-line( u-line, no).
871 END.
872 ELSE IF last-level <> -99999 AND next-level < total-break THEN
873 RUN put-blank-line.
875 ASSIGN
876 bldg-area = bldg-area + level-area
877 bldg-contract = bldg-contract + level-contract
878 bldg-charged = bldg-charged + level-charged
879 level-area = 0
880 level-parks = 0
881 level-contract = 0
882 level-charged = 0
885 IF last-level <> -99999 AND next-level >= total-break THEN RUN property-totals( (next-level = 99999) ).
886 level-lines = 0.
888 END PROCEDURE.
890 /* _UIB-CODE-BLOCK-END */
891 &ANALYZE-RESUME
893 &ENDIF
895 &IF DEFINED(EXCLUDE-outgoings-page) = 0 &THEN
897 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE outgoings-page Procedure
898 PROCEDURE outgoings-page :
899 /*------------------------------------------------------------------------------
900 Purpose: Print outgoings information for the leases/spaces of the property
901 ------------------------------------------------------------------------------*/
902 DEF INPUT PARAMETER times-amt AS LOGICAL NO-UNDO.
904 DEF VAR out-line AS CHAR NO-UNDO.
905 DEF VAR no-accounts AS INTEGER NO-UNDO.
906 DEF VAR i AS INTEGER NO-UNDO.
907 DEF VAR percentage AS DECIMAL NO-UNDO.
908 DEF VAR acct-amnt AS DECIMAL NO-UNDO.
909 DEF VAR money-fmt AS CHAR NO-UNDO.
910 DEF VAR non-zero AS LOGICAL NO-UNDO.
912 DEF BUFFER PrimarySpace FOR RentalSpace.
914 money-fmt = IF times-amt = Yes THEN "->>>,>>9" ELSE "->>>9.99".
916 FOR EACH og-acct: DELETE og-acct. END.
918 no-accounts = 0.
919 FOR EACH PropertyOutgoing NO-LOCK OF Property:
920 no-accounts = no-accounts + 1.
921 FIND ChartOfAccount WHERE ChartOfAccount.AccountCode = PropertyOutgoing.AccountCode NO-LOCK NO-ERROR.
922 CREATE og-acct.
923 ASSIGN
924 og-acct.AccountCode = PropertyOutgoing.AccountCode
925 og-acct.ShortName = (IF AVAILABLE(ChartOfAccount) THEN STRING( (IF TRIM(ChartOfAccount.ShortName) <> "" THEN ChartOfAccount.ShortName ELSE ChartOfAccount.Name), "X(7)") ELSE "???????")
926 og-acct.Recovered = 0
927 og-acct.Vacant = 0
929 og-acct.ShortName = TRIM(og-acct.ShortName).
930 og-acct.ShortName = FILL( " ", 7 - LENGTH(og-acct.ShortName)) + og-acct.ShortName .
931 END.
933 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST",
934 EACH TenancyOutgoing NO-LOCK OF TenancyLease WHERE TenancyOutgoing.Percentage > 0:
935 IF TenancyLease.GrossLease THEN DO:
936 out-line = "Warning: Tenant " + STRING( TenancyLease.TenantCode )
937 + " has a recovery of " + STRING( TenancyOutgoing.Percentage )
938 + "% for account " + STRING( TenancyOutgoing.AccountCode, "9999.99")
939 + " but is a gross lease (recovery is ignored)".
940 /* RUN print-line( out-line, No ).
941 NEXT. */
942 END.
943 FIND FIRST og-acct WHERE og-acct.AccountCode = TenancyOutgoing.AccountCode NO-ERROR.
944 IF AVAILABLE(og-acct) THEN
945 og-acct.Recovered = og-acct.Recovered + TenancyOutgoing.Percentage.
946 ELSE DO:
947 no-accounts = no-accounts + 1.
948 FIND ChartOfAccount WHERE ChartOfAccount.AccountCode = TenancyOutgoing.AccountCode NO-LOCK NO-ERROR.
949 CREATE og-acct.
950 ASSIGN
951 og-acct.AccountCode = TenancyOutgoing.AccountCode
952 og-acct.ShortName = (IF AVAILABLE(ChartOfAccount) THEN STRING( (IF TRIM(ChartOfAccount.ShortName) <> "" THEN ChartOfAccount.ShortName ELSE ChartOfAccount.Name), "X(7)") ELSE "???????")
953 og-acct.Recovered = TenancyOutgoing.Percentage
954 og-acct.Vacant = 0
956 og-acct.ShortName = TRIM(og-acct.ShortName).
957 og-acct.ShortName = FILL( " ", 7 - LENGTH(og-acct.ShortName)) + og-acct.ShortName .
959 END.
961 IF TenancyOutgoing.Percentage > 0 THEN
962 MESSAGE "TOG" TenancyLease.TenantCode TenancyOutgoing.AccountCode TenancyOutgoing.Percentage .
964 END.
966 /* fill in those where a default percentage applies from the lease record */
967 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST"
968 AND NOT TenancyLease.GrossLease,
969 FIRST PrimarySpace OF TenancyLease WHERE PrimarySpace.AreaType <> "C",
970 EACH og-acct WHERE NOT CAN-FIND( FIRST TenancyOutgoing OF TenancyLease WHERE TenancyOutgoing.AccountCode = og-acct.AccountCode):
971 IF TenancyLease.OutgoingsRate <> 100 THEN DO:
972 og-acct.Recovered = og-acct.Recovered + TenancyLease.OutgoingsRate .
973 /* MESSAGE TenancyLease.TenantCode TenancyLease.OutgoingsRate og-acct.AccountCode og-acct.Recovered . */
974 END.
975 END.
978 col-head1 = FILL(" ", 33).
979 col-head2 = STRING( "Tenant / Area", "X(33)").
980 FOR EACH og-acct BY og-acct.AccountCode:
981 col-head1 = col-head1 + " " + (IF og-acct.ShortName = ? THEN "" ELSE og-acct.ShortName).
982 col-head2 = col-head2 + " " + STRING( og-acct.AccountCode, "9999.99").
983 END.
985 IF print-main-schedule THEN PAGE. ELSE RUN set-headings( col-head1, col-head2).
988 /* Net Leases */
989 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST"
990 /* AND NOT TenancyLease.GrossLease */,
991 FIRST PrimarySpace OF TenancyLease WHERE PrimarySpace.AreaType <> "C"
992 /* AND PrimarySpace.RentalSpaceCode = TenancyLease.PrimarySpace */
993 BY PrimarySpace.Level BY PrimarySpace.LevelSequence :
994 FIND Tenant WHERE Tenant.TenantCode = TenancyLease.TenantCode NO-LOCK NO-ERROR.
995 non-zero = No.
996 out-line = STRING( Tenant.tenantCode, "99999 ")
997 + STRING( Tenant.Name, "X(15)") + " "
998 + STRING( TenancyLease.AreaDescription, "X(11)") .
999 FOR EACH og-acct BY og-acct.AccountCode:
1001 IF NOT CAN-FIND( FIRST TenancyOutgoing OF TenancyLease WHERE TenancyOutgoing.AccountCode = og-acct.AccountCode)
1002 AND TenancyLease.OutgoingsRate <> 100 THEN DO:
1003 MESSAGE "Here" TenancyLease.TenantCode TenancyLease.OutgoingsRate og-acct.AccountCode og-acct.Recovered .
1004 END.
1006 FIND TenancyOutgoing NO-LOCK OF TenancyLease WHERE TenancyOutgoing.AccountCode = og-acct.AccountCode NO-ERROR.
1007 percentage = (IF AVAILABLE(TenancyOutgoing) THEN TenancyOutgoing.Percentage ELSE TenancyLease.OutgoingsRate ).
1008 IF percentage = ? THEN percentage = 0. ELSE
1009 percentage = percentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
1010 out-line = out-line + (IF percentage <> 0 THEN STRING( percentage, money-fmt) ELSE " - ").
1011 IF percentage <> 0 THEN non-zero = Yes.
1012 /* MESSAGE percentage non-zero . */
1013 END.
1014 IF /* PrimarySpace.AreaType <> "C" OR */ non-zero THEN RUN print-line( out-line, No).
1015 END.
1016 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
1018 out-line = STRING( "Total Recoverable", "X(33)").
1019 FOR EACH og-acct BY og-acct.AccountCode:
1020 out-line = out-line + STRING( og-acct.Recovered * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
1021 money-fmt) .
1022 END.
1023 RUN print-line( out-line, No).
1026 /* Gross Leases */
1027 RUN print-line( " ", No ).
1028 RUN print-line( " ", No ).
1029 FOR EACH TenancyLease NO-LOCK OF Property WHERE TenancyLease.LeaseStatus <> "PAST"
1030 AND TenancyLease.GrossLease,
1031 FIRST PrimarySpace OF TenancyLease
1032 BY PrimarySpace.Level BY PrimarySpace.LevelSequence :
1033 FIND Tenant WHERE Tenant.TenantCode = TenancyLease.TenantCode NO-LOCK NO-ERROR.
1034 non-zero = No.
1035 out-line = STRING( Tenant.tenantCode, "99999 ")
1036 + STRING( Tenant.Name, "X(15)") + " "
1037 + STRING( TenancyLease.AreaDescription, "X(11)") .
1038 percentage = 0.
1039 FOR EACH RentalSpace OF TenancyLease:
1040 percentage = percentage + RentalSpace.OutgoingsPercentage.
1041 END.
1042 IF percentage = 0 THEN NEXT.
1044 FOR EACH og-acct BY og-acct.AccountCode:
1045 acct-amnt = percentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
1046 IF CAN-FIND( TenancyOutgoing OF TenancyLease WHERE TenancyOutgoing.Percentage > 0
1047 AND TenancyOutgoing.AccountCode = og-acct.AccountCode) THEN
1048 acct-amnt = 0.
1049 ELSE
1050 og-acct.Gross = og-acct.Gross + percentage.
1051 out-line = out-line + (IF acct-amnt <> 0 THEN STRING( acct-amnt, money-fmt) ELSE " - ") .
1052 END.
1053 RUN print-line( out-line, No).
1055 END.
1056 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
1058 out-line = STRING( "Total Non-Recoverable", "X(33)").
1059 FOR EACH og-acct BY og-acct.AccountCode:
1060 out-line = out-line + STRING( og-acct.Gross * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
1061 money-fmt) .
1062 END.
1063 RUN print-line( out-line, No).
1066 RUN print-line( " ", No ).
1067 RUN print-line( " ", No ).
1068 FOR EACH RentalSpace NO-LOCK OF Property WHERE RentalSpace.AreaStatus = "V"
1069 AND RentalSpace.OutgoingsPercentage <> 0
1070 BY Level BY LevelSequence:
1071 out-line = STRING( TRIM( STRING( RentalSpace.Level, "->>>9/")) + TRIM( STRING( RentalSpace.LevelSequence, ">>>9 ")), "X(8)")
1072 + STRING( RentalSpace.Description, "X(25)").
1073 FOR EACH og-acct BY og-acct.AccountCode:
1074 percentage = RentalSpace.OutgoingsPercentage * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ).
1075 out-line = out-line + (IF percentage <> 0 THEN STRING( percentage, money-fmt) ELSE " - ") .
1076 og-acct.Vacant = og-acct.Vacant + RentalSpace.OutgoingsPercentage.
1077 END.
1078 RUN print-line( out-line, No).
1079 END.
1081 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("-",7), no-accounts), No).
1082 out-line = STRING( "Total Vacant", "X(33)").
1083 FOR EACH og-acct BY og-acct.AccountCode:
1084 out-line = out-line + STRING( og-acct.Vacant * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
1085 money-fmt) .
1086 END.
1087 RUN print-line( out-line, No).
1090 RUN print-line( " ", No ).
1091 RUN print-line( " ", No ).
1092 RUN print-line( FILL(" ", 33) + FILL( " " + FILL("=",7), no-accounts), No).
1093 out-line = STRING( "Total", "X(33)").
1094 FOR EACH og-acct BY og-acct.AccountCode:
1095 out-line = out-line + STRING( (og-acct.Recovered + og-acct.Gross + og-acct.Vacant) * get-prop-og( times-amt, Property.PropertyCode, og-acct.AccountCode ),
1096 money-fmt) .
1097 END.
1098 RUN print-line( out-line, No).
1100 END PROCEDURE.
1102 /* _UIB-CODE-BLOCK-END */
1103 &ANALYZE-RESUME
1105 &ENDIF
1107 &IF DEFINED(EXCLUDE-parse-parameters) = 0 &THEN
1109 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE parse-parameters Procedure
1110 PROCEDURE parse-parameters :
1111 /*------------------------------------------------------------------------------
1112 Purpose:
1113 ------------------------------------------------------------------------------*/
1114 DEF VAR i AS INT NO-UNDO.
1115 DEF VAR token AS CHAR NO-UNDO.
1117 {inc/showopts.i "report-options"}
1119 DO i = 1 TO NUM-ENTRIES( report-options, "~n" ):
1120 token = ENTRY( i, report-options, "~n" ).
1122 CASE( ENTRY( 1, token ) ):
1123 WHEN "Properties" THEN ASSIGN
1124 property-1 = INT( ENTRY(2,token) )
1125 property-n = INT( ENTRY(3,token) ).
1127 WHEN "Client" THEN test-client-code = ENTRY(2,token).
1128 WHEN "CompanyList" THEN company-list = ENTRY(2,token).
1129 WHEN "Selection" THEN selection-style = ENTRY(2,token).
1130 WHEN "Warnings" THEN show-warnings = ENTRY(2,token) BEGINS "Y".
1131 WHEN "Preview" THEN preview = ENTRY(2,token) BEGINS "Y".
1132 WHEN "Main Schedule" THEN print-main-schedule = ENTRY(2,token) BEGINS "Y".
1133 WHEN "Outgoings Page" THEN print-outgoing-page = ENTRY(2,token) BEGINS "Y".
1134 WHEN "O/G as Amounts" THEN outgoings-amounts = ENTRY(2,token) BEGINS "Y".
1135 WHEN "No Charged Rents" THEN contract-rents = ENTRY(2,token) BEGINS "Y".
1136 WHEN "No Notes" THEN no-notes = ENTRY(2,token) BEGINS "Y".
1137 END CASE.
1138 END.
1140 IF property-n < property-1 THEN property-n = property-1.
1141 IF selection-style = "AP" THEN ASSIGN
1142 property-1 = 0
1143 property-n = 999999.
1144 ELSE IF selection-style = "1P" THEN ASSIGN
1145 property-n = property-1.
1147 END PROCEDURE.
1149 /* _UIB-CODE-BLOCK-END */
1150 &ANALYZE-RESUME
1152 &ENDIF
1154 &IF DEFINED(EXCLUDE-print-line) = 0 &THEN
1156 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE print-line Procedure
1157 PROCEDURE print-line :
1158 /*------------------------------------------------------------------------------
1159 Purpose: Print a line of output
1160 ------------------------------------------------------------------------------*/
1161 DEF INPUT PARAMETER the-line AS CHAR NO-UNDO.
1162 DEF INPUT PARAMETER split AS LOGICAL NO-UNDO.
1164 IF split THEN DO:
1165 the-line = STRING( the-line, "X(" + TRIM(STRING({&page-width},">>>>9")) + ")").
1166 IF SUBSTRING( the-line, vert-pos, 1) = " " THEN SUBSTRING( the-line, vert-pos, 1) = "|".
1167 END.
1168 PUT UNFORMATTED the-line SKIP.
1170 END PROCEDURE.
1172 /* _UIB-CODE-BLOCK-END */
1173 &ANALYZE-RESUME
1175 &ENDIF
1177 &IF DEFINED(EXCLUDE-print-notes) = 0 &THEN
1179 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE print-notes Procedure
1180 PROCEDURE print-notes :
1181 /*------------------------------------------------------------------------------
1182 Purpose: Print the notes
1183 ------------------------------------------------------------------------------*/
1184 DEF INPUT PARAMETER left-notes AS CHAR NO-UNDO.
1185 DEF INPUT PARAMETER right-notes AS CHAR NO-UNDO.
1187 DEF VAR out-line AS CHAR NO-UNDO.
1188 DEF VAR one-note AS CHAR NO-UNDO.
1190 DEF VAR no-lines AS INT NO-UNDO.
1191 no-lines = NUM-ENTRIES( left-notes, CHR(10)).
1192 IF no-lines < NUM-ENTRIES( right-notes, CHR(10)) THEN no-lines = NUM-ENTRIES( right-notes, CHR(10)).
1194 DEF VAR l-no AS INTEGER INITIAL 1 NO-UNDO.
1195 DO l-no = 1 TO no-lines:
1196 ASSIGN one-note = ""
1197 one-note = ENTRY( l-no, left-notes, CHR(10)) NO-ERROR.
1198 IF one-note = ? THEN one-note = "".
1199 out-line = ' ' + STRING( one-note, "X(70)") + ' '.
1201 ASSIGN one-note = ""
1202 one-note = ENTRY( l-no, right-notes, CHR(10)) NO-ERROR.
1203 IF one-note = ? THEN one-note = "".
1204 out-line = out-line + ' ' + STRING( one-note, "X(100)").
1206 RUN print-line( out-line, yes ).
1207 END.
1209 END PROCEDURE.
1211 /* _UIB-CODE-BLOCK-END */
1212 &ANALYZE-RESUME
1214 &ENDIF
1216 &IF DEFINED(EXCLUDE-property-schedule) = 0 &THEN
1218 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE property-schedule Procedure
1219 PROCEDURE property-schedule :
1220 /*------------------------------------------------------------------------------
1221 Purpose: Schedule for a single building
1222 ------------------------------------------------------------------------------*/
1223 DEF VAR last-level AS INT INITIAL -99999 NO-UNDO.
1224 DEF VAR out-line AS CHAR NO-UNDO.
1226 RUN set-headings( col-head1-base, col-head2-base).
1227 FOR EACH RentalSpace OF Property NO-LOCK
1228 BY RentalSpace.PropertyCode BY RentalSpace.Level BY RentalSpace.LevelSequence:
1229 IF RentalSpace.Level <> last-level THEN DO:
1230 RUN new-level ( last-level, RentalSpace.Level ).
1231 last-level = RentalSpace.Level.
1232 END.
1233 RUN each-rental-space.
1234 level-lines = level-lines + 1.
1235 END.
1236 RUN new-level( last-level, 99999 ).
1238 IF no-notes THEN RETURN.
1240 RUN get-last-notes.
1241 ASSIGN col-head1 = "" col-head2 = "" .
1242 RUN print-notes( various-notes, bldg-notes ).
1243 PUT SKIP (2).
1244 RUN get-saved-notes( OUTPUT space-notes, OUTPUT lease-notes).
1245 space-notes = wrap( space-notes, 70 ).
1246 lease-notes = wrap( lease-notes, 100 ).
1247 RUN print-notes( space-notes, lease-notes ).
1249 END PROCEDURE.
1251 /* _UIB-CODE-BLOCK-END */
1252 &ANALYZE-RESUME
1254 &ENDIF
1256 &IF DEFINED(EXCLUDE-property-totals) = 0 &THEN
1258 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE property-totals Procedure
1259 PROCEDURE property-totals :
1260 /*------------------------------------------------------------------------------
1261 Purpose: Display final- or sub- totals for this property
1262 ------------------------------------------------------------------------------*/
1263 DEF INPUT PARAMETER final-total AS LOGICAL NO-UNDO.
1265 DEF VAR out-line AS CHAR NO-UNDO.
1267 RUN print-line( e-line, no).
1268 IF final-total THEN
1269 out-line = "Total for " + Property.Name.
1270 ELSE
1271 out-line = " " + "Total floor rental".
1272 out-line = STRING( out-line, "X(25)")
1273 + (IF bldg-area > 0 THEN STRING( bldg-area, area-format) + " square metres" ELSE FILL(' ',24))
1274 + FILL(' ',7)
1275 + STRING( bldg-contract, money-format) + " "
1276 + (IF contract-rents THEN FILL(' ',14) ELSE STRING( bldg-charged, money-format))
1277 + FILL(' ',104)
1278 + STRING( bldg-outgoings, money-format) + " "
1280 RUN print-line( out-line, no ).
1281 RUN print-line( e-line, no).
1283 IF final-total THEN DO:
1284 ASSIGN
1285 grand-area = grand-area + bldg-area
1286 grand-contract = grand-contract + bldg-contract
1287 grand-charged = grand-charged + bldg-charged
1288 bldg-area = 0
1289 bldg-contract = 0
1290 bldg-charged = 0
1292 END.
1293 ELSE
1294 total-break = total-break * 10.
1296 END PROCEDURE.
1298 /* _UIB-CODE-BLOCK-END */
1299 &ANALYZE-RESUME
1301 &ENDIF
1303 &IF DEFINED(EXCLUDE-put-blank-line) = 0 &THEN
1305 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE put-blank-line Procedure
1306 PROCEDURE put-blank-line :
1307 /*------------------------------------------------------------------------------
1308 Purpose: Put a blank line - with a vertical in it?
1309 ------------------------------------------------------------------------------*/
1310 DEF VAR out-line AS CHAR NO-UNDO.
1311 out-line = FILL(' ',vert-pos).
1312 RUN print-line( out-line, yes).
1313 END PROCEDURE.
1315 /* _UIB-CODE-BLOCK-END */
1316 &ANALYZE-RESUME
1318 &ENDIF
1320 &IF DEFINED(EXCLUDE-rental-space-line) = 0 &THEN
1322 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE rental-space-line Procedure
1323 PROCEDURE rental-space-line :
1324 /*------------------------------------------------------------------------------
1325 Purpose: Create an output line.
1326 ------------------------------------------------------------------------------*/
1327 DEF INPUT PARAMETER l-no AS INTEGER NO-UNDO.
1328 DEF OUTPUT PARAMETER line AS CHAR NO-UNDO.
1330 DEF VAR fval AS CHAR NO-UNDO.
1331 DEF VAR i AS INT NO-UNDO.
1333 line = "".
1334 DO i = 1 TO {&FIELD-COUNT}:
1335 IF contract-rents AND i = 5 THEN NEXT.
1336 ASSIGN fval = ""
1337 fval = ENTRY( l-no, f[i], CHR(10)) NO-ERROR.
1338 IF fval = ? THEN fval = "".
1339 line = line + STRING( fval, f-fmt[i]) + ' '.
1340 END.
1342 END PROCEDURE.
1344 /* _UIB-CODE-BLOCK-END */
1345 &ANALYZE-RESUME
1347 &ENDIF
1349 &IF DEFINED(EXCLUDE-save-up-notes) = 0 &THEN
1351 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE save-up-notes Procedure
1352 PROCEDURE save-up-notes :
1353 /*------------------------------------------------------------------------------
1354 Purpose:
1355 ------------------------------------------------------------------------------*/
1356 DEF INPUT PARAMETER record-code AS INT NO-UNDO.
1357 DEF INPUT PARAMETER note-code AS INT NO-UNDO.
1358 DEF INPUT PARAMETER i-desc AS CHAR NO-UNDO.
1359 DEF OUTPUT PARAMETER o-desc AS CHAR NO-UNDO.
1360 DEF INPUT-OUTPUT PARAMETER n-list AS CHAR NO-UNDO.
1361 DEF INPUT-OUTPUT PARAMETER c-list AS CHAR NO-UNDO.
1363 DEF VAR n AS INT NO-UNDO.
1364 DEF VAR i AS INT NO-UNDO.
1365 DEF VAR result AS INT NO-UNDO INITIAL 0.
1367 o-desc = i-desc.
1368 IF note-code = ? OR note-code = 0 THEN RETURN.
1369 FIND Note WHERE Note.NoteCode = note-code NO-LOCK NO-ERROR.
1370 IF NOT AVAILABLE(Note) THEN RETURN.
1371 IF TRIM(Note.Detail) = "" THEN RETURN.
1373 n = NUM-ENTRIES(n-list).
1374 DO i = 1 TO n:
1375 IF INTEGER(ENTRY(i,n-list)) = note-code THEN DO:
1376 result = i.
1377 LEAVE.
1378 END.
1379 END.
1381 IF result = 0 THEN DO:
1382 result = n + 1.
1383 n-list = n-list + (IF n-list <> "" THEN "," ELSE "") + STRING(note-code).
1384 c-list = c-list + (IF c-list <> "" THEN "," ELSE "") + STRING(record-code).
1385 END.
1387 o-desc = i-desc + " *" + TRIM(STRING(result)).
1389 END PROCEDURE.
1391 /* _UIB-CODE-BLOCK-END */
1392 &ANALYZE-RESUME
1394 &ENDIF
1396 &IF DEFINED(EXCLUDE-set-headings) = 0 &THEN
1398 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE set-headings Procedure
1399 PROCEDURE set-headings :
1400 /*------------------------------------------------------------------------------
1401 Purpose: Set the headings for the building schedule report.
1402 ------------------------------------------------------------------------------*/
1403 DEF INPUT PARAMETER column-1 AS CHAR NO-UNDO.
1404 DEF INPUT PARAMETER column-2 AS CHAR NO-UNDO.
1406 DEF VAR pos AS INT NO-UNDO.
1408 FIND Company WHERE Company.CompanyCode = Property.CompanyCode NO-LOCK NO-ERROR.
1409 ASSIGN
1410 hline2 = (IF AVAILABLE(Company) THEN Company.LegalName ELSE "No Company Assigned")
1411 hline3 = Property.Name + " (P" + TRIM( STRING( Property.PropertyCode, ">>>>9")) + ")"
1412 hline4 = Property.StreetAddress
1413 col-head1 = column-1
1414 col-head2 = column-2
1417 Replace-EOL-With-Commas:
1418 DO WHILE TRUE:
1419 pos = INDEX( hline4, CHR(10)).
1420 IF pos > 0 THEN
1421 hline4 = SUBSTRING( hline4, 1, pos - 1) + ", " + SUBSTRING( hline4, pos + 1).
1422 ELSE
1423 LEAVE Replace-EOL-With-Commas.
1424 END.
1425 hline2 = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(hline2) ) / 2)) + hline2.
1426 hline3 = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(hline3) ) / 2)) + hline3.
1427 hline4 = SUBSTRING( STRING("","X({&page-width})"), 1, INTEGER(({&page-width} - LENGTH(hline4) ) / 2)) + hline4.
1429 IF first-building THEN DO:
1430 VIEW FRAME heading-frame.
1431 first-building = no.
1432 END.
1433 ELSE DO:
1434 PAGE.
1435 END.
1437 END PROCEDURE.
1439 /* _UIB-CODE-BLOCK-END */
1440 &ANALYZE-RESUME
1442 &ENDIF
1444 /* ************************ Function Implementations ***************** */
1446 &IF DEFINED(EXCLUDE-get-prop-og) = 0 &THEN
1448 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION get-prop-og Procedure
1449 FUNCTION get-prop-og RETURNS DECIMAL
1450 ( INPUT doit AS LOGICAL, INPUT pc AS INTEGER, INPUT ac AS DECIMAL ) :
1451 /*------------------------------------------------------------------------------
1452 Purpose:
1453 Notes:
1454 ------------------------------------------------------------------------------*/
1455 IF doit <> Yes THEN RETURN 1.0 .
1456 FIND PropertyOutgoing WHERE PropertyOutgoing.PropertyCode = pc
1457 AND PropertyOutgoing.AccountCode = ac NO-LOCK NO-ERROR.
1458 IF AVAILABLE(PropertyOutgoing) THEN
1459 RETURN PropertyOutgoing.BudgetAmount / 100 .
1461 RETURN 0.00 .
1463 END FUNCTION.
1465 /* _UIB-CODE-BLOCK-END */
1466 &ANALYZE-RESUME
1468 &ENDIF
1470 &IF DEFINED(EXCLUDE-test-floor-space) = 0 &THEN
1472 &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION test-floor-space Procedure
1473 FUNCTION test-floor-space RETURNS CHARACTER
1474 ( INPUT type AS CHAR, INPUT area AS DECIMAL ) :
1475 /*------------------------------------------------------------------------------
1476 Purpose: Decide if this is actual floor space
1477 ------------------------------------------------------------------------------*/
1478 DEF BUFFER LocAreaType FOR AreaType.
1480 IF area = ? THEN RETURN "No".
1481 FIND LocAreaType WHERE LocAreaType.AreaType = type NO-LOCK NO-ERROR.
1482 IF AVAILABLE(LocAreaType) THEN DO:
1483 IF LocAreaType.IsCarPark THEN RETURN "Park".
1484 IF LocAreaType.IsFloorArea THEN RETURN "Yes".
1485 RETURN "No".
1486 END.
1488 CASE type:
1489 WHEN "C" THEN RETURN "Park".
1490 WHEN "O" THEN RETURN "Yes".
1491 WHEN "R" THEN RETURN "Yes".
1492 WHEN "W" THEN RETURN "Yes".
1493 WHEN "N" THEN RETURN "No".
1494 /* OTHERWISE
1495 IF area > 10 OR (area <> INTEGER(area)) THEN RETURN "Yes". */
1496 END CASE.
1498 RETURN "No".
1500 END FUNCTION.
1502 /* _UIB-CODE-BLOCK-END */
1503 &ANALYZE-RESUME
1505 &ENDIF