Loading [MathJax]/extensions/tex2jax.js
MRFFL: MR Fortran Finance Library 2024-12-28
Computational Tools For Finance
All Namespaces Files Functions Variables
mrffl_cashflows.f90
Go to the documentation of this file.
1! -*- Mode:F90; Coding:us-ascii-unix; fill-column:129 -*-
2!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!.H.S.!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!.H.E.!!
3!>
4!! @file mrffl_cashflows.f90
5!! @author Mitch Richling http://www.mitchr.me/
6!! @date 2024-12-19
7!! @brief Time value of money for general cashflows.@EOL
8!! @keywords finance fortran monte carlo inflation cashflow time value of money tvm percentages taxes stock market
9!! @std F2023
10!! @see https://github.com/richmit/FortranFinance
11!! @copyright
12!! @parblock
13!! Copyright (c) 2024, Mitchell Jay Richling <http://www.mitchr.me/> All rights reserved.
14!!
15!! Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following
16!! conditions are met:
17!!
18!! 1. Redistributions of source code must retain the above copyright notice, this list of conditions, and the following
19!! disclaimer.
20!!
21!! 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions, and the following
22!! disclaimer in the documentation and/or other materials provided with the distribution.
23!!
24!! 3. Neither the name of the copyright holder nor the names of its contributors may be used to endorse or promote products
25!! derived from this software without specific prior written permission.
26!!
27!! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
28!! INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
29!! DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
30!! EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF
31!! USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
32!! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
33!! OF THE POSSIBILITY OF SUCH DAMAGE.
34!! @endparblock
35!!
36!!
37
38!----------------------------------------------------------------------------------------------------------------------------------
39!> Tools for TVM computations with irregular/uneven cashflows.
40!!
41!! The traditional definition of a cashflow is money received (positive) or paid (negative). A cashflow stream or series (or
42!! sequence) is one or more cashflows received over a period of time. Time up into a series of discreet "periods" corresponding
43!! naturally to the problem at hand. Each cashflow occurs at the beginning or ending of one of these periods. For example, we
44!! might break time up into months to model the cashflows related to a loan. Software approaches vary with regard to how
45!! cashflows are entered, stored, and processed.
46!!
47!! In this library the time of a cashflow is specified by the period boundary on which it occurs -- i.e. we say "boundary 1"
48!! instead of the equivalent possibilities of "the end of period 1" or "the beginning of period 2". An n period cashflow is
49!! stored in a simple array (or a column of a matrix) with capacity for n+1 elements (one for each boundary) -- note that is one
50!! more than the number of periods. The first element of a cash flow array represents time *zero* and is the *beginning* of time
51!! period 1. The second element of the array represents the *end* of time period 1 or the *beginning* of time period 2. The
52!! last element represents the *end* of the final period -- i.e. period n.
53!!
54!! Consider an example. We get a loan for 1000 over 6 months with a monthly interest rate of 1%. This is a 6 period cash flow
55!! with the principal received at the beginning of period 1. Conventionally we think of the first payment occurring at the end
56!! of period 1; however, we could think of this payment as occurring at the beginning of period 2. For this example, th cashflow
57!! array would be: [1000, -172.55, -172.55, -172.55, -172.55, -172.55, -172.55]. In tabular form:
58!!
59!! Array Index Cashflow
60!! 1 1000.00 ==> Time 0 (start of 1st period)
61!! 2 -172.55
62!! 3 -172.55
63!! 4 -172.55
64!! 5 -172.55
65!! 6 -172.55
66!! 7 -172.55 ==> Time 6 (end of 6th period)
67!!
68!! This library encourages the use of multiple cashflow series for problem solving. Each cashflow sequence is stored as the
69!! column of a matrix. The entire matrix may then be used for TVM calculations.
70!!
72 use mrffl_config, only: rk=>mrfflrk, ik=>mrfflik, cnfmt=>mrfflcnfmt, ctfmt=>mrfflctfmt, zero_epsilon
77 implicit none
78 private
79
80 ! Work with one or more cashflow series in the columns of a matrix
82
83 ! Work with one cashflow series in a vector
85
86 ! Construct cashflow series
89
90 ! Modify cashflow series
92
93 ! interface cashflow_total_pv
94 ! module procedure cashflow_matrix_total_pv, cashflow_vector_total_pv
95 ! end interface cashflow_total_pv
96 ! public :: cashflow_total_pv
97
98contains
99
100 !------------------------------------------------------------------------------------------------------------------------------
101 !> Compute pv for a cashflow vector.
102 !!
103 !! See: cashflow_matrix_total_pv()
104 !!
105 real(kind=rk) pure function cashflow_vector_total_pv(cf_vec, i)
106 real(kind=rk), intent(in) :: cf_vec(:)
107 real(kind=rk), intent(in) :: i
108 integer(kind=ik) :: j
110 do j=1,size(cf_vec)
112 end do
113 end function cashflow_vector_total_pv
114
115 !------------------------------------------------------------------------------------------------------------------------------
116 !> Compute pv for a cashflow matrix.
117 !!
118 !! In this library, initial cashflows are simply at time 0. NPV and PV are the same value in this context. The value
119 !! returned by this function is identical to summing the pv_vec returned by cashflow_matrix_pv_fv; however, this function is
120 !! much faster and requires no temporary arrays.
121 !!
122 !! @param cf_mat Matrix of cashflows (one cashflow sequence per column)
123 !! @param i Interest/Rate/Growth
124 !!
125 real(kind=rk) pure function cashflow_matrix_total_pv(cf_mat, i)
126 real(kind=rk), intent(in) :: cf_mat(:,:)
127 real(kind=rk), intent(in) :: i
128 real(kind=rk) :: cf
129 integer(kind=ik) :: j, k
131 do j=1,size(cf_mat, 1)
132 cf = cf_mat(j, 1)
133 do k=2,size(cf_mat, 2)
134 cf = cf + cf_mat(j, k)
135 end do
137 end do
138 end function cashflow_matrix_total_pv
139
140 !------------------------------------------------------------------------------------------------------------------------------
141 !> Compute IRR for a cashflow vector.
142 !!
143 !! @param cf_vec Vector of cashflows
144 !! @param irr If the solver is successful, this will be the irr on return.
145 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 4193-4224
146 !!
147 subroutine cashflow_vector_irr(cf_vec, irr, status)
148 real(kind=rk), intent(in) :: cf_vec(:)
149 real(kind=rk), intent(inout) :: irr
150 integer(kind=ik), intent(out) :: status
151 real(kind=rk) :: islvivl0(3) = [0.0_rk+zero_epsilon, -100.0_rk+zero_epsilon, -99999.0_rk]
152 real(kind=rk) :: islvivl1(3) = [ 99999.0_rk, 0.0_rk-zero_epsilon, -100.0_rk-zero_epsilon]
153 call multi_bisection(irr, islvivl0, islvivl1, irr_solve, 1.0e-5_rk, 1.0e-5_rk, 1000_ik, status, .false.)
154 if (status /= 0) then
155 status = 4161 ! "ERROR(cashflow_vector_irr): irr solver failed!"
156 end if
157 return
158 contains
159 real(kind=rk) function irr_solve(i)
160 real(kind=rk), intent(in) :: i
162 end function irr_solve
163 end subroutine cashflow_vector_irr
164
165 !------------------------------------------------------------------------------------------------------------------------------
166 !> Compute IRR for a cashflow matrix.
167 !!
168 !! @param cf_mat Matrix of cashflows (one cashflow sequence per column)
169 !! @param irr If the solver is successful, this will be the irr on return.
170 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 4193-4224
171 !!
172 subroutine cashflow_matrix_irr(cf_mat, irr, status)
173 real(kind=rk), intent(in) :: cf_mat(:,:)
174 real(kind=rk), intent(inout) :: irr
175 integer(kind=ik), intent(out) :: status
176 real(kind=rk) :: islvivl0(3) = [0.0_rk+zero_epsilon, -100.0_rk+zero_epsilon, -99999.0_rk]
177 real(kind=rk) :: islvivl1(3) = [ 99999.0_rk, 0.0_rk-zero_epsilon, -100.0_rk-zero_epsilon]
178 call multi_bisection(irr, islvivl0, islvivl1, irr_solve, 1.0e-5_rk, 1.0e-5_rk, 1000_ik, status, .false.)
179 if (status /= 0) then
180 status = 4193 ! "ERROR(cashflow_matrix_irr): irr solver failed!"
181 end if
182 return
183 contains
184 real(kind=rk) function irr_solve(i)
185 real(kind=rk), intent(in) :: i
187 end function irr_solve
188 end subroutine cashflow_matrix_irr
189
190 !------------------------------------------------------------------------------------------------------------------------------
191 !> Convert a cashflow number into a padded string for titles
192 !!
193 character(len=5) function i2s(n)
194 implicit none
195 integer(kind=ik), intent(in) :: n
196 write(i2s,'(i5.5)') n
197 end function i2s
198
199 !------------------------------------------------------------------------------------------------------------------------------
200 !> Compute present and future values for a cashflow vector.
201 !!
202 !! See: cashflow_matrix_pv_fv()
203 !!
204 subroutine cashflow_vector_pv_fv(cf_vec, i, pv_vec, fv_vec, status)
205 real(kind=rk), intent(in) :: cf_vec(:)
206 real(kind=rk), intent(in) :: i
207 real(kind=rk), intent(out) :: pv_vec(:), fv_vec(:)
208 integer(kind=ik), intent(out) :: status
209 call cashflow_matrix_pv_fv_print(reshape(cf_vec, [size(cf_vec), 1]), i, pv_vec, fv_vec, status, prt_none)
210 end subroutine cashflow_vector_pv_fv
211
212 !------------------------------------------------------------------------------------------------------------------------------
213 !> Compute present and future values for a cashflow vector.
214 !!
215 !! See: cashflow_matrix_pv_fv_print()
216 !!
217 subroutine cashflow_vector_pv_fv_print(cf_vec, i, pv_vec, fv_vec, status, print_out)
218 real(kind=rk), intent(in) :: cf_vec(:)
219 real(kind=rk), intent(in) :: i
220 real(kind=rk), intent(out) :: pv_vec(:), fv_vec(:)
221 integer(kind=ik), intent(out) :: status
222 integer(kind=ik), intent(in) :: print_out
223 call cashflow_matrix_pv_fv_print(reshape(cf_vec, [size(cf_vec), 1]), i, pv_vec, fv_vec, status, print_out)
224 end subroutine cashflow_vector_pv_fv_print
225
226 !------------------------------------------------------------------------------------------------------------------------------
227 !> Compute present and future values for a cashflow matrix.
228 !!
229 !! @param cf_mat Matrix of cashflows (one cashflow sequence per column)
230 !! @param i Interest/Rate/Growth
231 !! @param pv_vec Returns the present value vector
232 !! @param fv_vec Returns the future value vector
233 !! @param status Returns status of operation. 0 if everything worked. See: cashflow_matrix_pv_fv_print() for range.
234 !!
235 subroutine cashflow_matrix_pv_fv(cf_mat, i, pv_vec, fv_vec, status)
236 real(kind=rk), intent(in) :: cf_mat(:,:)
237 real(kind=rk), intent(in) :: i
238 real(kind=rk), intent(out) :: pv_vec(:), fv_vec(:)
239 integer(kind=ik), intent(out) :: status
240 call cashflow_matrix_pv_fv_print(cf_mat, i, pv_vec, fv_vec, status, prt_none)
241 end subroutine cashflow_matrix_pv_fv
242
243 !------------------------------------------------------------------------------------------------------------------------------
244 !> Compute present and future values for a cashflow matrix.
245 !!
246 !! As a side effect, the cashflows may be printed.
247 !!
248 !! @param cf_mat Matrix of cashflows (one cashflow sequence per column)
249 !! @param i Interest/Rate/Growth
250 !! @param pv_vec Returns the present value vector
251 !! @param fv_vec Returns the future value vector
252 !! @param status Returns status of operation. 0 if everything worked. Range: 0 & 2129-2160.
253 !! @param print_out Bitset built from the following constants prt_param, prt_title, prt_table, prt_total, & prt_space
254 !!
255 subroutine cashflow_matrix_pv_fv_print(cf_mat, i, pv_vec, fv_vec, status, print_out)
256 real(kind=rk), intent(in) :: cf_mat(:,:)
257 real(kind=rk), intent(in) :: i
258 real(kind=rk), intent(out) :: pv_vec(:), fv_vec(:)
259 integer(kind=ik), intent(out) :: status
260 integer(kind=ik), intent(in) :: print_out
261 integer(kind=ik) :: num_bdrys, num_flows, j, flow
262 real(kind=rk),allocatable :: dfactors(:), cf_aggr(:), total_pv(:), total_fv(:)
263 num_bdrys = size(cf_mat, 1, kind=ik)
264 num_flows = size(cf_mat, 2, kind=ik)
265 if (num_flows < 1) then
266 status = 2130 ! "ERROR(cashflow_matrix_pv_fv): No flows found in matrix!"
267 return
268 else if (abs(i+100) < zero_epsilon) then
269 status = 2132 ! "ERROR(cashflow_matrix_pv_fv): Value for i is too close -100%!"
270 return
271 else if (num_bdrys < 2) then
272 status = 2133 ! "ERROR(cashflow_matrix_pv_fv): Number of periods in cashflow is too small!"
273 return
274 else if (num_bdrys > size(pv_vec)) then
275 status = 2134 ! "ERROR(cashflow_matrix_pv_fv): The pv_vec array is not long enough!"
276 return
277 else if (num_bdrys > size(fv_vec)) then
278 status = 2135 ! "ERROR(cashflow_matrix_pv_fv): The fv_vec array is not long enough!"
279 return
280 else
281 status = 0
282 end if
283 if (bitset_subsetp(prt_space, print_out) .and. bitset_intersectp(prt_param+prt_table+prt_total, print_out)) then
284 print *, ""
285 end if
286 cf_aggr = sum(cf_mat,2)
287 if (abs(i+100) < zero_epsilon) then
288 dfactors = [(1,j=1,num_bdrys)]
289 else
290 dfactors = (1+percentage_to_fraction(i))**[(j-1,j=1,num_bdrys)]
291 end if
292 pv_vec = cf_aggr / dfactors
293 fv_vec = cf_aggr * dfactors(num_bdrys:1:-1)
295 if (bitset_subsetp(prt_param, print_out)) then
296 print "(a15, i25)", "Period Count: ", (num_bdrys-1)
297 print "(a15, f25.4)", "Discount Rate: ", i
298 end if
299 if (bitset_subsetp(prt_space, print_out) .and. bitset_intersectp(prt_title+prt_total, print_out)) then
300 print *, ""
301 end if
302 if (bitset_subsetp(prt_title+prt_table, print_out)) then
303 if (num_flows > 1) then
304 print "(a6,*("//ctfmt//"))", "Time", ( "CF_"//i2s(flow), flow = 1_rk, num_flows ), &
305 "CF_Aggregate", "PV", "FV", "PV_Total", "FV_Total"
306 else
307 print "(a6,*("//ctfmt//"))", "Time", "CF", "PV", "FV", "PV_Total", "FV_Total"
308 end if
309 end if
310 if (bitset_subsetp(prt_table, print_out)) then
311 do j = 1, num_bdrys
312 if (num_flows > 1) then
313 print "(i6,*("//cnfmt//"))", (j-1), cf_mat(j, :), cf_aggr(j), pv_vec(j), fv_vec(j), sum(pv_vec(1:j)), sum(fv_vec(1:j))
314 else
315 print "(i6,5("//cnfmt//"))", (j-1), cf_aggr(j), pv_vec(j), fv_vec(j), sum(pv_vec(1:j)), sum(fv_vec(1:j))
316 end if
317 end do
318 end if
319 if (bitset_subsetp(prt_space+prt_total+prt_table, print_out)) then
320 print *, ""
321 end if
322 if (bitset_subsetp(prt_total, print_out)) then
323 if (bitset_subsetp(prt_title, print_out) .and. bitset_not_subsetp(prt_table, print_out)) then
324 if (num_flows > 1) then
325 print "(a6,*("//ctfmt//"))", "", ( "CF_"//i2s(flow), flow = 1, num_flows ), "CF_Aggregate"
326 else
327 print "(a6,*("//ctfmt//"))", "", "CF"
328 end if
329 end if
330 total_pv = [(sum(cf_mat(:,flow) / dfactors), flow = 1, num_flows)]
331 total_fv = [(sum(cf_mat(:,flow) * dfactors(num_bdrys:1:-1)), flow = 1, num_flows)]
332 if (num_flows > 1) then
333 print "(a6,*("//cnfmt//"))", "PV", total_pv, sum(pv_vec)
334 print "(a6,*("//cnfmt//"))", "FV", total_fv, sum(fv_vec)
335 else
336 print "(a6,*("//cnfmt//"))", "PV", total_pv
337 print "(a6,*("//cnfmt//"))", "FV", total_fv
338 end if
339 end if
340 if (bitset_subsetp(prt_space, print_out) .and. bitset_intersectp(prt_param+prt_table+prt_total, print_out)) then
341 print *, ""
342 end if
343 end if
344 end subroutine cashflow_matrix_pv_fv_print
345
346 !------------------------------------------------------------------------------------------------------------------------------
347 !> Create a cashflow with a single (lump sum) payment.
348 !!
349 !! The number of periods is assumed from the size of the cashflow vector at size(cashflow)-1.
350 !! All payments other than the lump sum payment are set to zero.
351 !!
352 !! @param cf_vec The resulting cashflow vector.
353 !! @param a The cashflow amount.
354 !! @param d Delay from time zero. i.e. d=0 is the beginning of period 1 otherwise d=j is the end if period j.
355 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 2097-2128.
356 !!
357 subroutine make_cashflow_vector_delayed_lump(cf_vec, a, d, status)
358 implicit none
359 real(kind=rk), intent(out) :: cf_vec(:)
360 real(kind=rk), intent(in) :: a
361 integer(kind=ik), intent(in) :: d
362 integer(kind=ik), intent(out) :: status
363 integer :: n
364 n = size(cf_vec)-1
365 if (n < 1) then
366 status = 2097 ! "ERROR(make_cashflow_vector_delayed_lump): n<1!"
367 else if (d < 0) then
368 status = 2098 ! "ERROR(make_cashflow_vector_delayed_lump): d<0!"
369 else if (d > n) then
370 status = 2099 ! "ERROR(make_cashflow_vector_delayed_lump): d>n!"
371 else
372 cf_vec = 0
373 cf_vec(1+d) = a
374 status = 0
375 end if
377
378 !------------------------------------------------------------------------------------------------------------------------------
379 !> Create a cashflow of payments for a fixed annuity.
380 !!
381 !! The number of periods is assumed from the size of the cashflow vector at size(cashflow)-1.
382 !! All payments other than the annuity payments are set to zero.
383 !!
384 !! @param cf_vec The resulting cashflow vector.
385 !! @param a Annuity payment.
386 !! @param d Delay from time zero. i.e. d=0 is the beginning of period 1 otherwise d=j is the end if period j.
387 !! @param e Early end counted from time end (t=n). i.e. e=0 means the last payment is at end of period n.
388 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 2065-2096.
389 !!
390 subroutine make_cashflow_vector_delayed_level_annuity(cf_vec, a, d, e, status)
391 real(kind=rk), intent(out) :: cf_vec(:)
392 real(kind=rk), intent(in) :: a
393 integer(kind=ik), intent(in) :: d, e
394 integer(kind=ik), intent(out) :: status
395 integer :: n
396 n = size(cf_vec)-1
397 if (n < 1) then
398 status = 2065 ! "ERROR(make_cashflow_vector_delayed_level_annuity): n<1!"
399 else if (d < 0) then
400 status = 2066 ! "ERROR(make_cashflow_vector_delayed_level_annuity): d<0!"
401 else if (d > n) then
402 status = 2067 ! "ERROR(make_cashflow_vector_delayed_level_annuity): d>n!"
403 else if (e < 0) then
404 status = 2068 ! "ERROR(make_cashflow_vector_delayed_level_annuity): e<0!"
405 else if (e > n) then
406 status = 2069 ! "ERROR(make_cashflow_vector_delayed_level_annuity): e>n!"
407 else if ((d+e) > n) then
408 status = 2070 ! "ERROR(make_cashflow_vector_delayed_level_annuity): d+e>n!"
409 else
410 cf_vec = 0
411 cf_vec(1+d:1+n-e) = a
412 status = 0
413 end if
415
416 !------------------------------------------------------------------------------------------------------------------------------
417 !> Create a cashflow of payments for a growing annuity.
418 !!
419 !! The number of periods is assumed from the size of the cashflow vector at size(cashflow)-1.
420 !! All payments other than the annuity payments are set to zero.
421 !!
422 !! @param cf_vec The resulting cashflow vector.
423 !! @param g Growth rate as a percentage.
424 !! @param a First annuity payment.
425 !! @param d Delay from time zero. i.e. d=0 is the beginning of period 1 otherwise d=j is the end if period j.
426 !! @param e Early end counted from time end (t=n). i.e. e=0 means the last payment is at end of period n.
427 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 2033-2064.
428 !!
429 subroutine make_cashflow_vector_delayed_geometric_annuity(cf_vec, g, a, d, e, status)
430 real(kind=rk), intent(out) :: cf_vec(:)
431 real(kind=rk), intent(in) :: g, a
432 integer(kind=ik), intent(in) :: d, e
433 integer(kind=ik), intent(out) :: status
434 integer :: j, n
435 n = size(cf_vec)-1
436 if (n < 1) then
437 status = 2033 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): n<1!"
438 else if (d < 0) then
439 status = 2034 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): d<0!"
440 else if (d > n) then
441 status = 2035 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): d>n!"
442 else if (e < 0) then
443 status = 2036 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): e<0!"
444 else if (e > n) then
445 status = 2037 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): e>n!"
446 else if ((d+e) > n) then
447 status = 2038 ! "ERROR(make_cashflow_vector_delayed_geometric_annuity): d+e>n!"
448 else
449 cf_vec = 0
450 cf_vec(1+d:1+n-e) = [(a*(1+percentage_to_fraction(g))**j,j=0,n-e-d)]
451 status = 0
452 end if
454
455 !------------------------------------------------------------------------------------------------------------------------------
456 !> Create a cashflow of payments for an arithmatic annuity.
457 !!
458 !! The number of periods is assumed from the size of the cashflow vector at size(cashflow)-1.
459 !! All payments other than the annuity payments are set to zero.
460 !!
461 !! @param cf_vec The resulting cashflow vector.
462 !! @param q Amount added at each payment.
463 !! @param a First annuity payment.
464 !! @param d Delay from time zero. i.e. d=0 is the beginning of period 1 otherwise d=j is the end if period j.
465 !! @param e Early end counted from time end (t=n). i.e. e=0 means the last payment is at end of period n.
466 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 2001- 2032.
467 !!
468 subroutine make_cashflow_vector_delayed_arithmetic_annuity(cf_vec, q, a, d, e, status)
469 real(kind=rk), intent(out) :: cf_vec(:)
470 real(kind=rk), intent(in) :: q, a
471 integer(kind=ik), intent(in) :: d, e
472 integer(kind=ik), intent(out) :: status
473 integer :: j, n
474 n = size(cf_vec)-1
475 if (n < 1) then
476 status = 2001 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): n<1!"
477 else if (d < 0) then
478 status = 2002 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): d<0!"
479 else if (d > n) then
480 status = 2003 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): d>n!"
481 else if (e < 0) then
482 status = 2004 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): e<0!"
483 else if (e > n) then
484 status = 2005 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): e>n!"
485 else if ((d+e) > n) then
486 status = 2006 ! "ERROR(make_cashflow_vector_delayed_arithmetic_annuity): d+e>n!"
487 else
488 cf_vec = 0
489 cf_vec(1+d:1+n-e) = [((a+q*j),j=0,n-e-d)]
490 status = 0
491 end if
493
494 !------------------------------------------------------------------------------------------------------------------------------
495 !> Add interest cashflows to a cashflow sequence as if the sequence were being added to an interest baring account over time.
496 !!
497 !! @param cf_vec The cashflow vector to modify (one cashflow per period boundary).
498 !! @param rate The rate
499 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 4033-4064.
500 !!
501 subroutine add_intrest_to_cashflow_vector(cf_vec, rate, status)
502 implicit none
503 real(kind=rk), intent(out) :: cf_vec(:)
504 real(kind=rk), intent(in) :: rate
505 integer(kind=ik), intent(out) :: status
506 integer :: nb, j
507 real(kind=rk) :: rsum
508 nb = size(cf_vec)
509 if (nb > 1) then
510 rsum = cf_vec(1)
511 do j=2,nb
512 cf_vec(j) = cf_vec(j) + rsum * percentage_to_fraction(rate)
513 rsum = rsum + cf_vec(j)
514 end do
515 end if
516 status = 0
517 end subroutine add_intrest_to_cashflow_vector
518
519 !------------------------------------------------------------------------------------------------------------------------------
520 !> Add interest cashflows to a cashflow sequence as if the sequence were being added to an interest baring account over time.
521 !!
522 !! @param cf_vec The cashflow vector to modify (one cashflow per period boundary).
523 !! @param vrate A vector of rates (one rate per period).
524 !! @param status Returns status of computation. 0 if everything worked. Range: 0 & 4065-4096.
525 !!
526 subroutine add_multi_intrest_to_cashflow_vector(cf_vec, vrate, status)
527 implicit none
528 real(kind=rk), intent(out) :: cf_vec(:)
529 real(kind=rk), intent(in) :: vrate(:)
530 integer(kind=ik), intent(out) :: status
531 integer :: nb, j
532 real(kind=rk) :: rsum
533 nb = size(cf_vec)
534 if (nb > 1) then
535 if (size(vrate) < (nb-1)) then
536 status = 4065 ! "ERROR(add_multi_intrest_to_cashflow_vector): More periods than rates!"
537 else
538 rsum = cf_vec(1)
539 do j=2,nb
540 cf_vec(j) = cf_vec(j) + rsum * percentage_to_fraction(vrate(j-1))
541 rsum = rsum + cf_vec(j)
542 end do
543 end if
544 end if
545 status = 0
547
548end module mrffl_cashflows
real(kind=rk) function irr_solve(i)
Simple sets (using the bits of an integer to indicate element existence).
logical pure function, public bitset_intersectp(bitset1, bitset2)
logical pure function, public bitset_not_subsetp(bitset1, bitset2)
logical pure function, public bitset_subsetp(bitset1, bitset2)
Tools for TVM computations with irregular/uneven cashflows.
real(kind=rk) pure function, public cashflow_vector_total_pv(cf_vec, i)
Compute pv for a cashflow vector.
subroutine, public cashflow_vector_pv_fv(cf_vec, i, pv_vec, fv_vec, status)
Compute present and future values for a cashflow vector.
subroutine, public add_intrest_to_cashflow_vector(cf_vec, rate, status)
Add interest cashflows to a cashflow sequence as if the sequence were being added to an interest bari...
subroutine, public make_cashflow_vector_delayed_arithmetic_annuity(cf_vec, q, a, d, e, status)
Create a cashflow of payments for an arithmatic annuity.
character(len=5) function i2s(n)
Convert a cashflow number into a padded string for titles.
subroutine, public make_cashflow_vector_delayed_level_annuity(cf_vec, a, d, e, status)
Create a cashflow of payments for a fixed annuity.
subroutine, public cashflow_matrix_irr(cf_mat, irr, status)
Compute IRR for a cashflow matrix.
subroutine, public make_cashflow_vector_delayed_geometric_annuity(cf_vec, g, a, d, e, status)
Create a cashflow of payments for a growing annuity.
real(kind=rk) pure function, public cashflow_matrix_total_pv(cf_mat, i)
Compute pv for a cashflow matrix.
subroutine, public cashflow_matrix_pv_fv_print(cf_mat, i, pv_vec, fv_vec, status, print_out)
Compute present and future values for a cashflow matrix.
subroutine, public cashflow_matrix_pv_fv(cf_mat, i, pv_vec, fv_vec, status)
Compute present and future values for a cashflow matrix.
subroutine, public cashflow_vector_pv_fv_print(cf_vec, i, pv_vec, fv_vec, status, print_out)
Compute present and future values for a cashflow vector.
subroutine, public add_multi_intrest_to_cashflow_vector(cf_vec, vrate, status)
Add interest cashflows to a cashflow sequence as if the sequence were being added to an interest bari...
subroutine, public make_cashflow_vector_delayed_lump(cf_vec, a, d, status)
Create a cashflow with a single (lump sum) payment.
subroutine, public cashflow_vector_irr(cf_vec, irr, status)
Compute IRR for a cashflow vector.
Configuration for MRFFL (MR Fortran Finance Library).
integer, parameter, public mrfflrk
Real kind used in interfaces.
real(kind=mrfflrk), parameter, public zero_epsilon
Used to test for zero.
integer, parameter, public mrfflik
Integer kinds used in interfaces.
character(len=5), public mrfflcnfmt
Used to print cash values.
character(len=5), public mrfflctfmt
Used to print cash titles.
Simple functions for working with percentages.
elemental real(kind=rk) function, public percentage_to_fraction(p)
Convert a percentage to a fraction.
Constants to select what *_print subroutines will print.
integer(kind=ik), parameter, public prt_table
Print a table.
integer(kind=ik), parameter, public prt_param
Print parameters before the table/titles.
integer(kind=ik), parameter, public prt_total
Print totals PV & FV after the table.
integer(kind=ik), parameter, public prt_title
Print titles on the tables.
integer(kind=ik), parameter, public prt_space
Print vertical whitespace between parameters & table/titles & totals.
integer(kind=ik), parameter, public prt_none
Print nothing.
Root solvers.
subroutine, public multi_bisection(xc, x0_init, x1_init, f, x_epsilon, y_epsilon, max_itr, status, progress)
Use bisection() to search for a root for the function f in a list of intervals returning the first ro...