The ANNUITY function returns a numeric value that approximates the ratio of an annuity paid at the end of each period for the number of periods specified by argument-2 to an initial investment of one. Interest is earned at the rate specified by argument-1 and is applied at the end of the period, before the payment.
The type of this function is numeric.
Format
FUNCTION
ANNUITY
(argument-1 argument-2)
Arguments
argument-1 must be class "numeric".
The value of argument-1 must be greater than or equal to zero.
argument-2 must be a positive integer.
Returned values
When the value of argument-1 is equal to zero, the value of the function is the approximation of:
1 / argument-2When the value of argument-1 is not equal to zero, the value of the function is the approximation of:
argument-1 / (1-
(1 + argument-1)**(-
argument-2))The error default value is
-
2.
See also: PRESENT-VALUE
Example 9-2
The following program calculates the annual payments for a loan of 100000 at three different interest rates over a period of 1 to 10 years.
IDENTIFICATION DIVISION. PROGRAM-ID. INTEREST-TABLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS WINDOW DECIMAL-POINT IS COMMA. DATA DIVISION. WORKING-STORAGE SECTION. 01 CAPITAL PIC 9(9). 01 PD PIC 99. 01 CALC-TABLE. 02 INTEREST PIC V9(7) OCCURS 3 INDEXED BY R-IND-S. 01 HEADER-LINE. 02 PIC XX VALUE SPACE. 02 OCCURS 3 INDEXED BY T-IND-S. 10 INTR-ED PIC BBBZZ9,999999B. 10 PIC X VALUE FROM (1) "%" REPEATED TO END. 01 OUTPUT-TABLE. 02 THIS-LINE OCCURS 10 INDEXED BY A-IND-Z. 10 PERIOD PIC Z9. 10 RATE PIC BZZZBZZZBZZ9,99 OCCURS 3 INDEXED BY A-IND-S. PROCEDURE DIVISION. ONLY SECTION. PARA. MOVE 100000 TO CAPITAL *** Interest 5,75 % *** MOVE 0,0575 TO INTEREST (1) *** Interest 8,90 % *** MOVE 0,0890 TO INTEREST (2) *** Interest 12,10 % *** MOVE 0,1210 TO INTEREST (3) PERFORM VARYING R-IND-S FROM 1 BY 1 UNTIL R-IND-S > 3 SET T-IND-S TO R-IND-S MULTIPLY INTEREST (R-IND-S) BY 100 GIVING INTR-ED (T-IND-S) END-PERFORM PERFORM VARYING A-IND-Z FROM 1 BY 1 UNTIL A-IND-Z > 10 PERFORM VARYING A-IND-S FROM 1 BY 1 UNTIL A-IND-S > 3 SET R-IND-S TO A-IND-S SET PD TO A-IND-Z MOVE PD TO PERIOD (A-IND-Z) COMPUTE RATE (A-IND-Z A-IND-S) = CAPITAL * FUNCTION ANNUITY (INTEREST (R-IND-S) PD) END-PERFORM END-PERFORM DISPLAY HEADER-LINE UPON WINDOW PERFORM VARYING A-IND-Z FROM 1 BY 1 UNTIL A-IND-Z > 10 DISPLAY THIS-LINE (A-IND-Z) UPON WINDOW END-PERFORM STOP RUN.
Result:
|
|
|
|