From ba38b54aa0283e1ac47e0ef5767bc26c849f4b25 Mon Sep 17 00:00:00 2001 From: Reinhold Kainhofer <reinhold@kainhofer.com> Date: Sun, 22 Jan 2023 05:03:20 +0100 Subject: [PATCH] Implement contract$addExtension to add a contract extension after maturity (both premium-free and with regular premiums) * Allow premiumPeriod=0, indicating no premiums are paid (so an initial capital must be given) * Fix aggregating values of child-blocks that go beyond the main contract's duration * move sumInsured calculation to its own function for cleaner premium calculation. That function will be called earlier, so the CF data frames already use the correct sumInsured * The additional_capital cash flow is no longer relative to the sumInsured, but gives the absolute capital --- R/InsuranceContract.R | 131 +++++++++- R/InsuranceTarif.R | 238 +++++++++++------- man/InsuranceContract.ParameterDefaults.Rd | 1 + man/InsuranceContract.Rd | 67 ++++- man/InsuranceTarif.Rd | 34 +++ man/head0.Rd | 4 +- man/pad0.Rd | 7 +- man/padLast.Rd | 11 +- tests/testthat/test-extendContract.R | 43 ++++ ...ing-the-lifeinsurancecontracts-package.Rmd | 186 ++++++++++++++ 10 files changed, 607 insertions(+), 115 deletions(-) create mode 100644 tests/testthat/test-extendContract.R diff --git a/R/InsuranceContract.R b/R/InsuranceContract.R index 20bc205..acf4e74 100644 --- a/R/InsuranceContract.R +++ b/R/InsuranceContract.R @@ -227,7 +227,9 @@ InsuranceContract = R6Class( #' \code{policyPeriod} for regular premium payments for the whole #' contract period, while other premium payment durations indicate #' premium payments only for shorter periods than the whole contract - #' duration). Default is equal to \code{policyPeriod} + #' duration. Contract extensions without any premium payments are + #' indicated by \code{premiumPeriod}=0). Default is equal to + #' \code{policyPeriod} #' * \code{sumInsured} ... The sum insured (i.e. survival benefit for #' endowments, death benefit for whole/term life insurances, #' annuity payments for annuities) @@ -375,6 +377,8 @@ InsuranceContract = R6Class( #' the child's values need to be translated to the parent contracts's #' time frame using this parameter #' @param comment The comment to use in the history snapshot. + #' @param blockType The type of block to be added (e.g. Dynamics, Extension, + #' etc.). Can be any (short) string. #' @param ... parameters to be passed to \ifelse{html}{\href{#method-new}{\code{InsuranceContract$new()}}}{\code{InsuranceContract$new()()}} when #' \code{block} is not given and a copy of the parent should be #' created with overrides. @@ -469,7 +473,7 @@ InsuranceContract = R6Class( if (is.null(params)) params = list() if (!is.null(params$age)) params$age = params$age + t if (!is.null(params$policyPeriod)) params$policyPeriod = params$policyPeriod - t - if (!is.null(params$premiumPeriod)) params$premiumPeriod = max(1, params$premiumPeriod - t) + if (!is.null(params$premiumPeriod)) params$premiumPeriod = max(0, params$premiumPeriod - t) if (!is.null(params$deferralPeriod)) params$deferralPeriod = max(0, params$deferralPeriod - t) if (!is.null(params$contractClosing)) params$contractClosing = params$contractClosing + years(t) params$initialCapital = NULL @@ -498,6 +502,88 @@ InsuranceContract = R6Class( arguments = list(...) params[names(arguments)] = arguments[names(arguments)] params$comment = sprintf("Dynamic increase at time %d to sum %0.2f", t, NewSumInsured) + params$blockType = "Dynamics"; + do.call(self$addBlock, params) + }, + + + #' @description Add a contract extension after the contract has ended + #' (existing reserve is used as initial capital of the follow-up contract). + #' + #' @details When a contract expires, this function adds a follow-up contract + #' (with either the same or a different tariff), using the existing + #' reserve as `additionalCapital` at inception. + #' Technically, a child block using the new contract data of the extension + #' is added to the original contract. The over-all contract values are then + #' the sum of the original contract (providing values until expiration) + #' and the extension (providing values after the extension). + #' + #' + #' @param id The identifier of the child block to be inserted + #' @param t The time of the extension (relative to the parent block), + #' by default contract expiration of the parent block. + #' The extension is calculated independently (with time 0 + #' describing its own start), but using the existing reserve as + #' initialCapital and the parent's parameters as fall-back values. + #' @param comment The comment to use in the history snapshot. + #' @param ... Additional parameters to be passed to + #' \ifelse{html}{\href{#method-new}{\code{InsuranceContract$new()}}} + #' {\code{InsuranceContract$new()()}} to create the contract + #' extension object. + #' + #' @examples + #' # TODO + addExtension = function(id = NULL, t = NULL, comment = paste0("Contract extension at time t=", t), ...) { + if (getOption('LIC.debug.addExtension', FALSE)) { + browser(); + } + if (missing(id) | is.null(id)) { + # numbering extensions: Use nr. of blocks (except main) as a + # simplification => numbering is withint all dynamics, + # extensions, riders, etc.! + id = paste0("dyn", max(1, length(self$blocks))) + } + if (missing(t) | is.null(t)) { + # By default, use the parent's expiration, so the extension + # is appended after the original contract has ended. + t = self$Parameters$ContractData$policyPeriod + } + + # TODO: Override only the required parameters + params = private$initParams + if (is.null(params)) params = list() + if (!is.null(params$age)) params$age = params$age + t + # Remaining premium period is kept, can be overwritten in the + # arguments to this method. If premiumPeriod has already ended, + # a premium-free extension is added by default + if (!is.null(params$premiumPeriod)) params$premiumPeriod = max(0, params$premiumPeriod - t) + if (!is.null(params$deferralPeriod)) params$deferralPeriod = max(0, params$deferralPeriod - t) + if (!is.null(params$contractClosing)) params$contractClosing = params$contractClosing + years(t) + # Use the existing reserve as initialCapital, reset premium parameter and sumInsured of the old contract + params$initialCapital = self$Values$reserves[t + 1, "contractual"] + params$sumInsured = NULL + params$premium = NULL + + + # TODO: Adjust non-constant parameters (e.g. profit rates or benefits given as vector) to the later start time + + + params$t = t + params$id = id + # Override with arguments explicitly given + arguments = list(...) + params[names(arguments)] = arguments[names(arguments)] + params$comment = comment + params$blockType = "Contract Extension" + + # Two cases: + # 1) extension with premium => either premium or sumInsured must be given + # 2) premium-free extension => no premium, no sumInsured given => set premium to 0, calculate sumInsured + + noPremiums = (is.null(params$sumInsured) || (params$sumInsured == 0)) && (is.null(params$premium) || (params$premium == 0)); + if (noPremiums) { + params$premium = 0; + } do.call(self$addBlock, params) }, @@ -587,7 +673,7 @@ InsuranceContract = R6Class( t = valuesFrom); if (additionalCapital > 0) { - self$values$cashFlows[as.character(premiumCalculationTime), "additional_capital"] = additionalCapital / self$values$ContractData$sumInsured + self$Values$cashFlows[as.character(premiumCalculationTime), "additional_capital"] = additionalCapital } if (recalculatePremiumSum) { @@ -626,6 +712,13 @@ InsuranceContract = R6Class( } if (calculate == "presentvalues") return(invisible(self)); + + # If we have the premium given, determine the sumInsured from it + # Since the cash flows depend on the sumInsured (in particular, ) + if (is.null(self$Parameters$ContractData$sumInsured)) { + self$Parameters$ContractData$sumInsured = private$calculateSumInsured(calculationTime = premiumCalculationTime) + } + # the premiumCalculation function returns the premiums AND the cofficients, # so we have to extract the coefficients and store them in a separate variable if (recalculatePremiums) { @@ -754,12 +847,31 @@ InsuranceContract = R6Class( self$Values$reservesBalanceSheet = consolidateField("reservesBalanceSheet", keyed = TRUE) # TODO: Basic Data cannot simply be summed, e.g. the interest rate! self$Values$basicData = consolidateField("basicData") - # self$Values$basicData[,c("InterestRate", "PolicyDuration", "PremiumPeriod")] = NULL # Some fields can NOT be summed, but have to be left untouched. # Hard-code these to use the values from the main contract part: - self$Values$reservesBalanceSheet[,c("date", "time")] = self$blocks[[1]]$Values$reservesBalanceSheet[,c("date", "time")] - self$Values$basicData[,c("InterestRate", "PolicyDuration", "PremiumPeriod")] = self$blocks[[1]]$Values$basicData[,c("InterestRate", "PolicyDuration", "PremiumPeriod")] + rows = nrow(self$Values$reservesBalanceSheet) + colDt = rep(as.Date(NA), rows) + colTime = rep(NA_real_, rows) + colIntR = rep(NA_real_, rows) + colDur = rep(NA_real_, rows) + colPrem = rep(NA_real_, rows) + for (b in self$blocks) { + start = b$Parameters$ContractData$blockStart + colDt = coalesce(colDt, pad0(b$Values$reservesBalanceSheet[,"date"], start = start, value = as.Date(NA), value.start = as.Date(NA), l = rows)) + colTime = coalesce(colTime, pad0(b$Values$reservesBalanceSheet[,"time"] + start, start = start, value = NA, value.start = NA, l = rows)) + + colIntR = coalesce(colIntR, pad0(b$Values$basicData[,"InterestRate"], start = start, value = NA, value.start = NA, l = rows)) + colDur = coalesce(colDur, pad0(b$Values$basicData[,"PolicyDuration"], start = start, value = NA, value.start = NA, l = rows)) + colPrem = coalesce(colPrem, pad0(b$Values$basicData[,"PremiumPeriod"], start = start, value = NA, value.start = NA, l = rows)) + } + self$Values$reservesBalanceSheet[,"date"] = colDt; + self$Values$reservesBalanceSheet[,"time"] = colTime; + self$Values$basicData[,"InterestRate"] = colIntR + self$Values$basicData[,"PolicyDuration"] = colDur + self$Values$basicData[,"PremiumPeriod"] = colPrem + + self$Values$int$l = rows invisible(self) }, @@ -958,10 +1070,10 @@ InsuranceContract = R6Class( self$Parameters$ContractData$premiumPeriod = valueOrFunction( self$Parameters$ContractData$premiumPeriod, params = self$Parameters, values = self$Values); - # At least 1 year premium period, at most contract duration! + # premium period is at most contract duration! self$Parameters$ContractData$premiumPeriod = min( - max(self$Parameters$ContractData$premiumPeriod, 1), + self$Parameters$ContractData$premiumPeriod, self$Parameters$ContractData$policyPeriod ); @@ -1066,6 +1178,9 @@ InsuranceContract = R6Class( calculatePresentValuesCosts = function(...) { self$tarif$presentValueCashFlowsCosts(params = self$Parameters, values = self$Values, ...); }, + calculateSumInsured = function(...) { + self$tarif$sumInsuredCalculation(params = self$Parameters, values = self$Values, ...) + }, calculatePremiums = function(...) { self$tarif$premiumCalculation(params = self$Parameters, values = self$Values, ...); }, diff --git a/R/InsuranceTarif.R b/R/InsuranceTarif.R index 737dd05..4bf183a 100644 --- a/R/InsuranceTarif.R +++ b/R/InsuranceTarif.R @@ -411,6 +411,9 @@ InsuranceTarif = R6Class( browser(); } premPeriod = min(params$ContractData$premiumPeriod, params$ContractData$policyPeriod, len); + if (premPeriod <= 0) { + return(rep(0, len)) + } if (is.null(params$ContractData$premiumIncrease)) { pad0(rep(1, premPeriod - 1), len) } else { @@ -580,13 +583,8 @@ InsuranceTarif = R6Class( row.names = ages - age ); - if (is.null(params$ContractData$sumInsured)) { - # No sumInsured given, determine SI from premium provided - # - cf$additional_capital = pad0(params$ContractData$initialCapital, cflen) - } else { - cf$additional_capital = pad0(params$ContractData$initialCapital / params$ContractData$sumInsured, cflen) - } + cf$additional_capital = pad0(params$ContractData$initialCapital, cflen) + # Premiums: if (!params$ContractState$premiumWaiver) { premiums = self$getPremiumCF(len = cflen, params = params, values = values) @@ -642,8 +640,10 @@ InsuranceTarif = R6Class( dimnames = list(0:(values$int$l - 1), dmnames[[1]], dmnames[[2]], c("survival", "guaranteed", "after.death")) ); cf[1,,,"survival"] = cf[1,,,"survival"] + params$Costs[,,"once"] - for (i in 1:values$int$premiumTerm) { - cf[i,,,"survival"] = cf[i,,,"survival"] + params$Costs[,,"PremiumPeriod"]; + if (values$int$premiumTerm > 0){ + for (i in 1:values$int$premiumTerm) { + cf[i,,,"survival"] = cf[i,,,"survival"] + params$Costs[,,"PremiumPeriod"]; + } } if (values$int$premiumTerm < values$int$policyTerm) { for (i in (values$int$premiumTerm + 1):values$int$policyTerm) { @@ -801,8 +801,7 @@ InsuranceTarif = R6Class( # of the sumInsured (in cashFlowsBasic) for non-constant sums insured. # So here, we don't need to multiply with values$cashFlowsBasic$sumInsured! propGP = c("premiums_advance", "premiums_arrears"); - propSI = c("additional_capital", - "guaranteed_advance", "guaranteed_arrears", + propSI = c("guaranteed_advance", "guaranteed_arrears", "survival_advance", "survival_arrears", "death_SumInsured", "death_PremiumFree", "disease_SumInsured"); propPS = c("death_GrossPremium", "death_Refund_past"); @@ -926,14 +925,16 @@ InsuranceTarif = R6Class( ); coeff[["Premium"]][["benefits"]][["premiums"]] = 1; - coeff[["SumInsured"]][["benefits"]][["additional_capital"]] = -1; + coeff[["SumInsured"]][["benefits"]][["additional_capital"]] = -1 / params$ContractData$sumInsured; # Costs proportional to NetPremium introduce a non-linearity, as the NP is not available when the gross premium is calculated # => the corresponding costs PV is included in the coefficient! coeff.benefits = (1 + securityLoading); if (type == "gross") { # TODO: How to include this into the Zillmer premium calculation? - coeff.benefits = coeff.benefits * (1 + sum(values$presentValuesCosts[t, c("alpha", "beta", "gamma"), "NetPremium",]) / values$presentValues[[t,"premiums"]]) + if (values$presentValues[[t,"premiums"]] != 0) { + coeff.benefits = coeff.benefits * (1 + sum(values$presentValuesCosts[t, c("alpha", "beta", "gamma"), "NetPremium",]) / values$presentValues[[t,"premiums"]]) + } } coeff[["SumInsured"]][["benefits"]][["guaranteed"]] = coeff.benefits; coeff[["SumInsured"]][["benefits"]][["survival"]] = coeff.benefits; @@ -975,17 +976,17 @@ InsuranceTarif = R6Class( applyHook(params$Hooks$adjustPremiumCoefficients, coeff, type = type, premiums = premiums, params = params, values = values, premiumCalculationTime = premiumCalculationTime) }, - #' @description Calculate the premiums of the InsuranceContract given the - #' parameters, present values and premium cofficients already calculated and + #' @description Calculate the sumInsured of the InsuranceContract given the + #' parameters and premiums given and teh , present values already calculated and #' stored in the \code{params} and \code{values} lists. + #' @param calculationTime the time when the sumInsured should be recalculated from the given premium #' #' @details Not to be called directly, but implicitly by the [InsuranceContract] object. - premiumCalculation = function(params, values, premiumCalculationTime = values$int$premiumCalculationTime) { - if (getOption('LIC.debug.premiumCalculation', FALSE)) { + sumInsuredCalculation = function(params, values, calculationTime = values$int$premiumCalculationTime) { + if (getOption('sumInsuredCalculation', FALSE)) { browser(); } loadings = params$Loadings; - sumInsured = params$ContractData$sumInsured values$premiums = c( "unit.net" = 0, "unit.Zillmer" = 0, "unit.gross" = 0, "net" = 0, "Zillmer" = 0, "gross" = 0, @@ -993,95 +994,141 @@ InsuranceTarif = R6Class( "written_beforetax" = 0, "tax" = 0, "written" = 0, "additional_capital" = 0); coefficients = list("gross" = c(), "Zillmer" = c(), "net" = c()); - # Get the present values of the premiums, claims and costs at time 'premiumCalculationTime' (where the premium is to be calculated) - t = as.character(premiumCalculationTime) + # Get the present values of the premiums, claims and costs at time 'calculationTime' (where the premium is to be calculated) + t = as.character(calculationTime) pv = values$presentValues[t,] pvCost = values$presentValuesCosts[t,,,] - if (pv[["premiums"]] == 0) { - return(list("premiums" = values$premiums, "coefficients" = coefficients, "sumInsured" = params$ContractData$sumInsured)) - } - #======================================================================== = # Calculate sumInsured from Premium, if needed # ======================================================================= = - if (is.null(sumInsured)) { - sumInsured = 1 - params$ContractData$sumInsured = 1 # Temporarily set to 1! - - # Premium type can be given using a named array, e.g. premium = c(gross = 1000) - premiumtype = names(params$ContractData$premium) - if (is.null(premiumtype)) premiumtype = "written"; - premium = unname(params$ContractData$premium); - calculating = FALSE; - - - # Calculate unit gross premium (sumInsured=1) - values$premiums["additional_capital"] = values$cashFlows[t, "additional_capital"] - coeff = self$getPremiumCoefficients("gross", pv * 0, pvCost * 0, premiums = values$premiums, params = params, values = values, premiumCalculationTime = premiumCalculationTime) - enumerator = sum(coeff[["SumInsured"]][["benefits"]] * pv) + sum(coeff[["SumInsured"]][["costs"]] * pvCost); - denominator = sum(coeff[["Premium" ]][["benefits"]] * pv) + sum(coeff[["Premium" ]][["costs"]] * pvCost); + sumInsured = 1 + params$ContractData$sumInsured = 1 # Temporarily set to 1! + + # Premium type can be given using a named array, e.g. premium = c(gross = 1000) + premiumtype = names(params$ContractData$premium) + if (is.null(premiumtype)) premiumtype = "written"; + premium = unname(params$ContractData$premium); + # if ((premium == 0) || (params$ContractData$premiumPeriod == 0)) premiumtype = "noPremium"; + calculating = FALSE; + + + # Calculate unit gross premium (sumInsured=1) + values$premiums["additional_capital"] = values$cashFlows[t, "additional_capital"] + coeff = self$getPremiumCoefficients("gross", pv * 0, pvCost * 0, premiums = values$premiums, params = params, values = values, premiumCalculationTime = calculationTime) + #### BEGIN TWEAK_RK 21.1.2023 + # Since we don't know the sumInsured, the initial capital cannot be scaled to sumInsured=1 => handle differently! + # Calculate pv of benefits without initialCapital: + coeff.initialCapital = coeff[["SumInsured"]][["benefits"]][["additional_capital"]] + coeff[["SumInsured"]][["benefits"]][["additional_capital"]] = 0 + #### END TWEAK_RK 21.1.2023 + + enumerator = sum(coeff[["SumInsured"]][["benefits"]] * pv) + sum(coeff[["SumInsured"]][["costs"]] * pvCost); + denominator = sum(coeff[["Premium" ]][["benefits"]] * pv) + sum(coeff[["Premium" ]][["costs"]] * pvCost); + if (is.na(denominator) || (denominator == 0)) { + values$premiums[["unit.gross"]] = 0; + denominator = 1 + } else { values$premiums[["unit.gross"]] = enumerator/denominator * (1 + loadings$ongoingAlphaGrossPremium); + } - # Calculate other premium components: - # ATTENTION: This will not work if any of these depend on the absolute values of the premiums, or depend on net or Zillmer premium! - tax = valueOrFunction(loadings$tax, params = params, values = values); - unitCosts = valueOrFunction(loadings$unitcosts, params = params, values = values); - noMedicalExam = valueOrFunction(loadings$noMedicalExam,params = params, values = values); - noMedicalExam.relative = valueOrFunction(loadings$noMedicalExamRelative,params = params, values = values); - extraRebate = valueOrFunction(loadings$extraRebate, params = params, values = values); - sumRebate = valueOrFunction(loadings$sumRebate, params = params, values = values); - premiumRebateRate = valueOrFunction(loadings$premiumRebate,params = params, values = values); - premiumRebate = applyHook(params$Hooks$premiumRebateCalculation, premiumRebateRate, params = params, values = values); - - extraChargeGrossPremium = valueOrFunction(loadings$extraChargeGrossPremium, params = params, values = values); - advanceProfitParticipation = 0; - advanceProfitParticipationUnitCosts = 0; - ppScheme = params$ProfitParticipation$profitParticipationScheme; - if (!is.null(ppScheme)) { - advanceProfitParticipation = ppScheme$getAdvanceProfitParticipation(params = params, values = values) - advanceProfitParticipationUnitCosts = ppScheme$getAdvanceProfitParticipationAfterUnitCosts(params = params, values = values) - } - if (is.null(advanceProfitParticipation)) advanceProfitParticipation = 0; - if (is.null(advanceProfitParticipationUnitCosts)) advanceProfitParticipationUnitCosts = 0; + # Calculate other premium components: + # ATTENTION: This will not work if any of these depend on the absolute values of the premiums, or depend on net or Zillmer premium! + tax = valueOrFunction(loadings$tax, params = params, values = values); + unitCosts = valueOrFunction(loadings$unitcosts, params = params, values = values); + noMedicalExam = valueOrFunction(loadings$noMedicalExam,params = params, values = values); + noMedicalExam.relative = valueOrFunction(loadings$noMedicalExamRelative,params = params, values = values); + extraRebate = valueOrFunction(loadings$extraRebate, params = params, values = values); + sumRebate = valueOrFunction(loadings$sumRebate, params = params, values = values); + premiumRebateRate = valueOrFunction(loadings$premiumRebate,params = params, values = values); + premiumRebate = applyHook(params$Hooks$premiumRebateCalculation, premiumRebateRate, params = params, values = values); + + extraChargeGrossPremium = valueOrFunction(loadings$extraChargeGrossPremium, params = params, values = values); + advanceProfitParticipation = 0; + advanceProfitParticipationUnitCosts = 0; + ppScheme = params$ProfitParticipation$profitParticipationScheme; + if (!is.null(ppScheme)) { + advanceProfitParticipation = ppScheme$getAdvanceProfitParticipation(params = params, values = values) + advanceProfitParticipationUnitCosts = ppScheme$getAdvanceProfitParticipationAfterUnitCosts(params = params, values = values) + } + if (is.null(advanceProfitParticipation)) advanceProfitParticipation = 0; + if (is.null(advanceProfitParticipationUnitCosts)) advanceProfitParticipationUnitCosts = 0; - partnerRebate = valueOrFunction(loadings$partnerRebate, params = params, values = values); + partnerRebate = valueOrFunction(loadings$partnerRebate, params = params, values = values); - # Start from the given premium to derive the sumInsured step-by-step: - # - # Written premium after tax - calculating = calculating | (premiumtype == "written"); - if (calculating) { - premium = premium / (1 + tax); - } - # Written premium before tax - calculating = calculating | (premiumtype == "written_beforetax"); - if (calculating) { - premium = premium / (1 - premiumRebate - advanceProfitParticipationUnitCosts - partnerRebate); - - pv.unitcosts = sum( - pvCost["unitcosts","SumInsured",] * sumInsured + - pvCost["unitcosts","SumPremiums",] * values$unitPremiumSum * values$premiums[["gross"]] + - pvCost["unitcosts","GrossPremium",] * values$premiums[["gross"]] + - pvCost["unitcosts","NetPremium",] * values$premiums[["net"]] + - pvCost["unitcosts","Constant",] - ) + # Start from the given premium to derive the sumInsured step-by-step: + temp = premium + # + # Written premium after tax + calculating = calculating | (premiumtype == "written"); + if (calculating) { + temp = temp / (1 + tax); + } + # Written premium before tax + calculating = calculating | (premiumtype == "written_beforetax"); + if (calculating) { + temp = temp / (1 - premiumRebate - advanceProfitParticipationUnitCosts - partnerRebate); + + pv.unitcosts = sum( + pvCost["unitcosts","SumInsured",] * sumInsured + + pvCost["unitcosts","SumPremiums",] * values$unitPremiumSum * values$premiums[["gross"]] + + pvCost["unitcosts","GrossPremium",] * values$premiums[["gross"]] + + pvCost["unitcosts","NetPremium",] * values$premiums[["net"]] + + pvCost["unitcosts","Constant",] + ) + if (pv[["premiums"]] == 0) { + premium.unitcosts = 0 + } else { premium.unitcosts = pv.unitcosts / pv[["premiums"]] + valueOrFunction(loadings$unitcosts, params = params, values = values); - if (!params$Features$unitcostsInGross) { - premium = premium - premium.unitcosts; - } - premium = premium / (1 - advanceProfitParticipation) } - calculating = calculating | (premiumtype == "gross"); - if (calculating) { - sumInsured = premium / - (values$premiums[["unit.gross"]]*(1 + noMedicalExam.relative + extraChargeGrossPremium) + noMedicalExam - sumRebate - extraRebate); + if (!params$Features$unitcostsInGross) { + temp = temp - premium.unitcosts; } - params$ContractData$sumInsured = sumInsured + temp = temp / (1 - advanceProfitParticipation) + } + calculating = calculating | (premiumtype == "gross"); + if (calculating) { + # handle initialCapital here (coefficient for initialCapital is typically negative, as it reduces the premium!) + temp = temp - coeff.initialCapital * values$premiums[["additional_capital"]] / denominator; + temp = temp / + (enumerator / denominator * (1 + noMedicalExam.relative + extraChargeGrossPremium) + noMedicalExam - sumRebate - extraRebate); + } + sumInsured = temp + + sumInsured + }, + + #' @description Calculate the premiums of the InsuranceContract given the + #' parameters, present values and premium cofficients already calculated and + #' stored in the \code{params} and \code{values} lists. + #' + #' @details Not to be called directly, but implicitly by the [InsuranceContract] object. + premiumCalculation = function(params, values, premiumCalculationTime = values$int$premiumCalculationTime) { + if (getOption('LIC.debug.premiumCalculation', FALSE)) { + browser(); } + loadings = params$Loadings; + sumInsured = params$ContractData$sumInsured + values$premiums = c( + "unit.net" = 0, "unit.Zillmer" = 0, "unit.gross" = 0, + "net" = 0, "Zillmer" = 0, "gross" = 0, + "unitcost" = 0, "written_yearly" = 0, + "written_beforetax" = 0, "tax" = 0, "written" = 0, "additional_capital" = 0); + coefficients = list("gross" = c(), "Zillmer" = c(), "net" = c()); + + # Get the present values of the premiums, claims and costs at time 'premiumCalculationTime' (where the premium is to be calculated) + t = as.character(premiumCalculationTime) + pv = values$presentValues[t,] + pvCost = values$presentValuesCosts[t,,,] + + values$premiums["additional_capital"] = values$cashFlows[t, "additional_capital"] + + # If there are no premium payments, no need to calculate premium components + # if (pv[["premiums"]] == 0) { + # return(list("premiums" = values$premiums, "coefficients" = coefficients, "sumInsured" = params$ContractData$sumInsured)) + # } - values$premiums["additional_capital"] = values$cashFlows[t, "additional_capital"] * sumInsured #======================================================================== = # net, gross and Zillmer premiums are calculated from the present values using the coefficients on each present value as described in the formulas document @@ -1091,7 +1138,7 @@ InsuranceTarif = R6Class( coeff = self$getPremiumCoefficients("gross", pv * 0, pvCost * 0, premiums = values$premiums, params = params, values = values, premiumCalculationTime = premiumCalculationTime) enumerator = sum(coeff[["SumInsured"]][["benefits"]] * pv) + sum(coeff[["SumInsured"]][["costs"]] * pvCost); denominator = sum(coeff[["Premium" ]][["benefits"]] * pv) + sum(coeff[["Premium" ]][["costs"]] * pvCost); - values$premiums[["unit.gross"]] = enumerator/denominator * (1 + loadings$ongoingAlphaGrossPremium); + values$premiums[["unit.gross"]] = enumerator/ifelse(denominator == 0, 1, denominator) * (1 + loadings$ongoingAlphaGrossPremium); values$premiums[["gross"]] = values$premiums[["unit.gross"]] * sumInsured; coefficients[["gross"]] = coeff; @@ -1101,7 +1148,7 @@ InsuranceTarif = R6Class( coeff = self$getPremiumCoefficients("net", pv*0, pvCost*0, premiums = values$premiums, params = params, values = values, premiumCalculationTime = premiumCalculationTime) enumerator = sum(coeff[["SumInsured"]][["benefits"]] * pv) + sum(coeff[["SumInsured"]][["costs"]] * pvCost); denominator = sum(coeff[["Premium" ]][["benefits"]] * pv) + sum(coeff[["Premium" ]][["costs"]] * pvCost); - values$premiums[["unit.net"]] = enumerator/denominator; + values$premiums[["unit.net"]] = enumerator/ifelse(denominator == 0, 1, denominator); values$premiums[["net"]] = values$premiums[["unit.net"]] * sumInsured; coefficients[["net"]] = coeff; @@ -1111,7 +1158,7 @@ InsuranceTarif = R6Class( coeff = self$getPremiumCoefficients("Zillmer", pv * 0, pvCost * 0, premiums = values$premiums, params = params, values = values, premiumCalculationTime = premiumCalculationTime); enumerator = sum(coeff[["SumInsured"]][["benefits"]] * pv) + sum(coeff[["SumInsured"]][["costs"]] * pvCost); denominator = sum(coeff[["Premium" ]][["benefits"]] * pv) + sum(coeff[["Premium" ]][["costs"]] * pvCost); - values$premiums[["unit.Zillmer"]] = enumerator/denominator; + values$premiums[["unit.Zillmer"]] = enumerator/ifelse(denominator == 0, 1, denominator); values$premiums[["Zillmer"]] = values$premiums[["unit.Zillmer"]] * sumInsured; coefficients[["Zillmer"]] = coeff; @@ -1149,8 +1196,7 @@ InsuranceTarif = R6Class( pvCost["unitcosts","NetPremium",] * values$premiums[["net"]] + pvCost["unitcosts","Constant",] ) - premium.unitcosts = pv.unitcosts / pv[["premiums"]] + valueOrFunction(loadings$unitcosts, params = params, values = values); - values$premiums[["unitcost"]] = premium.unitcosts; + premium.unitcosts = ifelse(pv[["premiums"]] == 0, 0, pv.unitcosts / pv[["premiums"]] + valueOrFunction(loadings$unitcosts, params = params, values = values)); frequencyLoading = self$evaluateFrequencyLoading(loadings$premiumFrequencyLoading, params$ContractData$premiumFrequency, params = params, values = values) diff --git a/man/InsuranceContract.ParameterDefaults.Rd b/man/InsuranceContract.ParameterDefaults.Rd index 2b4bb4b..5c8ad7a 100644 --- a/man/InsuranceContract.ParameterDefaults.Rd +++ b/man/InsuranceContract.ParameterDefaults.Rd @@ -39,6 +39,7 @@ for single-premium contracts. contracts with multiple parts, e.g. dynamic increases), default = "Hauptvertrag"} \item{\code{$sumInsured}}{Sum insured, default = 100,000} +\item{\code{$premium}}{Premium, given to determine the sumInsured (default: NULL)} \item{\code{$initialCapital}}{Reserve/Capital that is already available at contract inception, e.g. from a previous contract. No tax or acquisition costs are applied to this capital.} diff --git a/man/InsuranceContract.Rd b/man/InsuranceContract.Rd index 258c2eb..e31e169 100644 --- a/man/InsuranceContract.Rd +++ b/man/InsuranceContract.Rd @@ -159,7 +159,9 @@ for single-premium contracts, \code{premiumPeriod} equals \code{policyPeriod} for regular premium payments for the whole contract period, while other premium payment durations indicate premium payments only for shorter periods than the whole contract -duration). Default is equal to \code{policyPeriod} +duration. Contract extensions without any premium payments are +indicated by \code{premiumPeriod}=0). Default is equal to +\code{policyPeriod} \item \code{sumInsured} ... The sum insured (i.e. survival benefit for endowments, death benefit for whole/term life insurances, annuity payments for annuities) @@ -212,6 +214,14 @@ as its own \code{sumInsured}. total values of the overall contract. }\if{html}{\out{</div>}} +When a contract expires, this function adds a follow-up contract +(with either the same or a different tariff), using the existing +reserve as \code{additionalCapital} at inception. +Technically, a child block using the new contract data of the extension +is added to the original contract. The over-all contract values are then +the sum of the original contract (providing values until expiration) +and the extension (providing values after the extension). + This method calculates all contract values (potentially starting from and preserving all values before a later time \code{valuesFrom}). This function is not meant to be called @@ -279,6 +289,12 @@ are stored in a list of profit scenarios inside the contract. # TODO +## ------------------------------------------------ +## Method `InsuranceContract$addExtension` +## ------------------------------------------------ + +# TODO + ## ------------------------------------------------ ## Method `InsuranceContract$premiumWaiver` ## ------------------------------------------------ @@ -349,6 +365,7 @@ contract state and its values before the change).} \item \href{#method-InsuranceContract-addHistorySnapshot}{\code{InsuranceContract$addHistorySnapshot()}} \item \href{#method-InsuranceContract-addBlock}{\code{InsuranceContract$addBlock()}} \item \href{#method-InsuranceContract-addDynamics}{\code{InsuranceContract$addDynamics()}} +\item \href{#method-InsuranceContract-addExtension}{\code{InsuranceContract$addExtension()}} \item \href{#method-InsuranceContract-calculateContract}{\code{InsuranceContract$calculateContract()}} \item \href{#method-InsuranceContract-consolidateBlocks}{\code{InsuranceContract$consolidateBlocks()}} \item \href{#method-InsuranceContract-premiumWaiver}{\code{InsuranceContract$premiumWaiver()}} @@ -467,6 +484,7 @@ Add a child contract block (e.g. a dynamic increase or a rider) to an insurance block = NULL, t = block$Values$int$blockStart, comment = paste0("Additional block at time t=", t), + blockType = "Dynamics", ... )}\if{html}{\out{</div>}} } @@ -489,6 +507,9 @@ time frame using this parameter} \item{\code{comment}}{The comment to use in the history snapshot.} +\item{\code{blockType}}{The type of block to be added (e.g. Dynamics, Extension, +etc.). Can be any (short) string.} + \item{\code{...}}{parameters to be passed to \ifelse{html}{\href{#method-new}{\code{InsuranceContract$new()}}}{\code{InsuranceContract$new()()}} when \code{block} is not given and a copy of the parent should be created with overrides.} @@ -555,6 +576,50 @@ they can be overridden per dynamic increase block.} } +} +\if{html}{\out{<hr>}} +\if{html}{\out{<a id="method-InsuranceContract-addExtension"></a>}} +\if{latex}{\out{\hypertarget{method-InsuranceContract-addExtension}{}}} +\subsection{Method \code{addExtension()}}{ +Add a contract extension after the contract has ended +(existing reserve is used as initial capital of the follow-up contract). +\subsection{Usage}{ +\if{html}{\out{<div class="r">}}\preformatted{InsuranceContract$addExtension( + id = NULL, + t = NULL, + comment = paste0("Contract extension at time t=", t), + ... +)}\if{html}{\out{</div>}} +} + +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{id}}{The identifier of the child block to be inserted} + +\item{\code{t}}{The time of the extension (relative to the parent block), +by default contract expiration of the parent block. +The extension is calculated independently (with time 0 +describing its own start), but using the existing reserve as +initialCapital and the parent's parameters as fall-back values.} + +\item{\code{comment}}{The comment to use in the history snapshot.} + +\item{\code{...}}{Additional parameters to be passed to +\ifelse{html}{\href{#method-new}{\code{InsuranceContract$new()}}} +{\code{InsuranceContract$new()()}} to create the contract +extension object.} +} +\if{html}{\out{</div>}} +} +\subsection{Examples}{ +\if{html}{\out{<div class="r example copy">}} +\preformatted{# TODO +} +\if{html}{\out{</div>}} + +} + } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-InsuranceContract-calculateContract"></a>}} diff --git a/man/InsuranceTarif.Rd b/man/InsuranceTarif.Rd index 624d5b3..6a5d167 100644 --- a/man/InsuranceTarif.Rd +++ b/man/InsuranceTarif.Rd @@ -821,6 +821,40 @@ array has NOT yet been filled! Instead, all premiums already calculated argument. } +} +\if{html}{\out{<hr>}} +\if{html}{\out{<a id="method-InsuranceTarif-sumInsuredCalculation"></a>}} +\if{latex}{\out{\hypertarget{method-InsuranceTarif-sumInsuredCalculation}{}}} +\subsection{Method \code{sumInsuredCalculation()}}{ +Calculate the sumInsured of the InsuranceContract given the +parameters and premiums given and teh , present values already calculated and +stored in the \code{params} and \code{values} lists. +\subsection{Usage}{ +\if{html}{\out{<div class="r">}}\preformatted{InsuranceTarif$sumInsuredCalculation( + params, + values, + calculationTime = values$int$premiumCalculationTime +)}\if{html}{\out{</div>}} +} + +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{params}}{Contract-specific, full set of parameters of the contract +(merged parameters of the defaults, the tariff, the profit participation +scheme and the contract)} + +\item{\code{values}}{Contract values calculated so far (in the \code{contract$Values} +list) then this method is called by the contract object} + +\item{\code{calculationTime}}{the time when the sumInsured should be recalculated from the given premium} +} +\if{html}{\out{</div>}} +} +\subsection{Details}{ +Not to be called directly, but implicitly by the \link{InsuranceContract} object. +} + } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-InsuranceTarif-premiumCalculation"></a>}} diff --git a/man/head0.Rd b/man/head0.Rd index 7f4b9ac..a71e9cb 100644 --- a/man/head0.Rd +++ b/man/head0.Rd @@ -4,12 +4,14 @@ \alias{head0} \title{Set all entries of the given vector to 0 up until index 'start'} \usage{ -head0(v, start = 0) +head0(v, start = 0, value.start = 0) } \arguments{ \item{v}{the vector to modify} \item{start}{how many leading elements to zero out} + +\item{value.start}{the value to insert before the start index.} } \value{ the vector \code{v} with the first \code{start} elements replaced by 0. diff --git a/man/pad0.Rd b/man/pad0.Rd index 522ed6e..5bba7c9 100644 --- a/man/pad0.Rd +++ b/man/pad0.Rd @@ -4,7 +4,7 @@ \alias{pad0} \title{Pad a vector with 0 to a desired length} \usage{ -pad0(v, l, value = 0, start = 0) +pad0(v, l, value = 0, start = 0, value.start = 0) } \arguments{ \item{v}{the vector to pad with 0} @@ -14,9 +14,12 @@ pad0(v, l, value = 0, start = 0) \item{value}{the value to pad with (if padding is needed). Default to 0, but can be overridden to pad with any other value.} -\item{start}{the first \code{start} values are always set to 0 (default is 0), +\item{start}{the first \code{start} values are always set to 0 (default is 0, +can be changed using the \code{value.start} argument), the vector \code{v} starts only after these leading zeroes. The number of leading zeroes counts towards the desired length} + +\item{value.start}{the value to insert before the start index.} } \value{ returns the vector \code{v} padded to length \code{l} with value \code{value} (default 0). diff --git a/man/padLast.Rd b/man/padLast.Rd index 6d9d7b8..7997f18 100644 --- a/man/padLast.Rd +++ b/man/padLast.Rd @@ -5,19 +5,16 @@ \title{Pad the vector \code{v} to length \code{l} by repeating the last entry of the vector.} \usage{ -padLast(v, l, start = 0) +padLast(v, ...) } \arguments{ \item{v}{the vector to pad by repeating the last element} -\item{l}{the desired (resulting) length of the vector} - -\item{start}{the first \code{start} values are always set to 0 (default is 0), -the vector \code{v} starts only after these leading zeroes. The number of -leading zeroes counts towards the desired length} +\item{...}{arguments passed through to \code{pad0}} } \description{ -This function callc \code{\link[=pad0]{pad0()}} with the last element of the vector as padding value +This function is just a trivial wrapper around \code{pad0} and only calls \code{\link[=pad0]{pad0()}} +with the last element of the vector as padding value instead of the default 0. } \examples{ padLast(1:5, 7) # 5 is repeated twice diff --git a/tests/testthat/test-extendContract.R b/tests/testthat/test-extendContract.R new file mode 100644 index 0000000..59e0413 --- /dev/null +++ b/tests/testthat/test-extendContract.R @@ -0,0 +1,43 @@ +test_that("Extend contract by $addExtension", { + library(MortalityTables) + mortalityTables.load("Austria_Census") + + Tarif.EndowmentA = InsuranceTarif$new( + name = "Example Tariff - Endowment 1981", + type = "endowment", + tarif = "E1-RP81", + desc = "An endowment with regular premiums (standard tariff)", + + mortalityTable = mort.AT.census.1981.male, + cost = initializeCosts(alpha = 0.04, gamma.contract = 0.0005, unitcosts = 10), + i = 0.03 + ) + Tarif.EndowmentB = Tarif.EndowmentA$createModification( + name = "Example Tariff - Endowment 2001", + tarif = "E1-RP01", + mortalityTable = mort.AT.census.2001.male, + cost = initializeCosts(alpha = 0.024, gamma.contract = 0.00075, unitcosts = 20), + i = 0.01) + + ContractA = InsuranceContract$new( + tarif = Tarif.EndowmentA, + age = 40, policyPeriod = 20, + sumInsured = 10000, + contractClosing = as.Date("2000-07-01") + ) + + + # premium-free extension + ContractB = ContractA$clone()$addExtension(id = "Verlängerung1", contractPeriod = 5, premiumPeriod = 0) + expect_equal(ContractB$blocks$Verlängerung1$Parameters$ContractData$sumInsured, 15117.03896) + + + # extension with given sumInsured resulting in 0 premiums + ContractC = ContractA$clone()$addExtension(id = "Verlängerung1", contractPeriod = 5, sumInsured = 15117.03896) + expect_equal(ContractC$blocks$Verlängerung1$Values$premiums[["gross"]], 0, tolerance = 1e-06) + + # extension with increased sumInsured: real premiums are charged, reserves start from the existing reserve: + ContractD = ContractA$clone()$addExtension(id = "Verlängerung1", contractPeriod = 5, sumInsured = 20000) + expect_equal(ContractD$blocks$Verlängerung1$Values$premiums[["written"]], 315.109) + expect_equal(ContractD$blocks$Verlängerung1$Values$reserves[["0", "contractual"]], 10000) +}) diff --git a/vignettes/using-the-lifeinsurancecontracts-package.Rmd b/vignettes/using-the-lifeinsurancecontracts-package.Rmd index f293d09..cdaed0e 100644 --- a/vignettes/using-the-lifeinsurancecontracts-package.Rmd +++ b/vignettes/using-the-lifeinsurancecontracts-package.Rmd @@ -1342,6 +1342,192 @@ One can give a base name and an extra name to distinguish different calculations in the file names. +# Contracts combining multiple contract layers / slices + +In real life, an insurance contract is not merely signed initially and then left +untouched until it expires or is surrendered. Rather, some contracts already have +an automatic increase of the sumInsured or the premium (depending usually on some +kind of observed consumer price index) included in the contract. Other contracts +have additional biometric riders like an additional death or disability cover. +Other contracts are extended after their expiration, using the existing reserve +as a one-time payment (`initialCapital`) for the follow-up contract. + +In all these cases, the original contract can be calculated as an `InsuranceContract`, +but the additional dynamic increases, additional riders or extensions are mathematically +calculated as separate contracts (potentiall using different tariffs / types of +insurance), although most parameters are shared from the original main contract. + +In addition to modelling one particular tariff, the LifeInsuranceContract class +can also act as a wrapper to bundle multiple related contracts / contract slices +together. The class provides several methods for this: +* `$addDynamics(t, NewSumInsured, SumInsuredDelta, id, ...)`: + Include (at time `t`) a dynamic increase of premium or sumInsured, but + with the same basic parameters (age, tariff, maturity, + interest rate, etc.) as the main contract. The increase can + be given either as the new total sumInsured or as the + increase in the sumInsured caused by that one increase. Other parameters + given as `...` are passed on to the `InsuranceContract$new` constructor + of the layer for the dynamic increase. This also means that one can + potentially override all parameters for the increase, including the + tariff or the interest rate. +* `$addExtension(t = NULL, policyPeriod, ...)` + After the original contracts maturity, append a follow-up contract (by + default paid-up, i.e. no new premiums are paid) that uses the existing + reserve as initial capital. By default, no further premiums are paid + and the sumInsured is calculated from the existing reserve and the tariff + of the extension. One can, however, also provide either a sumInsured or + a premium of the contract extension. In that case, the premium or the sumInsured + will be calculated, using the existing reserves as initialCapital. +* `$addBlock(id = NULL, block = NULL, t, ...)` + Generic function to add a child block to the contract. If a block (object + of type `LifeInsuranceContract` is passed, it is inserted and flagged as + starting at time `t`. If no block is passed, a new insurance contract + is created using the arguments passed as `...`, combined with the + parameters of the main contract. If `t>0`, the child block starts later + than the original contract. It is also possible that the child block extends + beyond the maturity of the original contract (e.g. contract extensions + are implemented this way). + + +In these case, the main contract will have several child blocks (also +LifeInsuranceContract objects), and the values of the main contract object will +be the aggregated values of all its children, rather than the results of a +calculation from an underlying tariff. + +## Dynamic increases + +To increase the sum insured or premium by a given value () + +```{r contractLayers} +# Contract with initial capital of 5.000 EUR +ctr.dynInc = InsuranceContract$new( + tarif = Tarif.Endowment, + sumInsured = 10000, + age = 40, policyPeriod = 10, + contractClosing = as.Date("2020-09-01") +)$ + addDynamics(t = 1, SumInsuredDelta = 1000)$ + addDynamics(t = 5, NewSumInsured = 15000)$ + addDynamics(t = 8, SumInsuredDelta = 4000) + + +ctr.dynInc$Values$basicData +``` +As seen in this table, the sum insured increases and the premium with it. The +`PremiumPayment` column is no longer a 0/1-column indicating whether a premium is +paid or not, but rather is the number of blocks/layers where a premium is paid. + +The individual blocks can be accessed with the `contract$blocks` list: +```{r contractLayers.blocks} +for (b in ctr.dynInc$blocks) { + cat(paste0("Block: ", b$Parameters$ContractData$id, ", starts at t=", b$Parameters$ContractData$blockStart, ", policyPeriod=", b$Parameters$ContractData$policyPeriod, "\n")) +} +``` + +Each block is formally handled like a separate contract, each starting at its own time `t=0`. +The over-all contract then takes care to correctly shift the child blocks to the +time relative to the parent block, before aggregating the data: +```{r contractLayers.blocks.data} +ctr.dynInc$blocks$Hauptvertrag$Values$basicData +ctr.dynInc$blocks$dyn1$Values$basicData +ctr.dynInc$blocks$dyn2$Values$basicData +ctr.dynInc$blocks$dyn3$Values$basicData +``` + + +## General biometric riders + +Instead of adding a dynamic increase, which typically uses the same tariff as +the main contract, it is also possible to bundle e.g. a protection rider to a +saving product. The savings product and the protection rider are calculated +individually as child blocks, and the overall values of the contract are +obtained by aggregating the values from the two children (savings and protection +part). Of course, in this scenario, the combined sumInsured of the overall contract +is not meaningful, but the sumInsured of the individual blocks is. + +```{r addBlock.rider} +ctr.main = InsuranceContract$new( + tarif = Tarif.Endowment, + sumInsured = 10000, + age = 40, policyPeriod = 10, + contractClosing = as.Date("2020-09-01") +) +ctr.Rider = InsuranceContract$new( + tarif = Tarif.L71U, + sumInsured = 100000, + age = 40, policyPeriod = 10, + contractClosing = as.Date("2020-09-01") +) +ctr.main$addBlock(block = ctr.Rider) + +ctr.withRider = InsuranceContract$new( + tarif = Tarif.Endowment, + sumInsured = 10000, + age = 40, policyPeriod = 10, + contractClosing = as.Date("2020-09-01") +)$ + addBlock(tarif = Tarif.L71U, sumInsured = 100000, + age = 40, policyPeriod = 10, + contractClosing = as.Date("2020-09-01")) +``` + + +## Extending a contract beyond its maturity + +When a contract expires, many companies offer premium-free contract extensions, +where the existing reserve is used as initial reserve for a follow-up contract +(possibly with new terms and parameters like interest rate or mortalities). + +Instead of modifying the original contract and re-calculating it, it is easier +to model the extension as a new block with the existing reserve given as +\code{initialCapital}. The extension will be calculated like a standalone-contract +and the overall contract will aggregate the values from the original contract +and the extension. As the extension is a separate contract object, one can pass +all contract parameters to the \code{$addExtension} method. + +The original premiumPeriod of the main contract is used, so by default the extension +will be a premium-free extension, where the sumInsured is calculated from the +existing reserve and the benefits and costs of the extensions' tariff. + +To create a premium-free extension explicitly, one can pass \code{premiumPeriod=0} (which +is the default anyway). To create an extension with regular (or single) premium +payments, one can pass either a \code{sumInsured} or a \code{premium} to provide +the sum insured and the premium and calculate the other from the given value + +```{r contractExtension} +# original contract, expiring after 20 years +ContractA = InsuranceContract$new( + tarif = Tarif.Endowment, + age = 40, policyPeriod = 20, + sumInsured = 10000, + contractClosing = as.Date("2000-07-01") +) + +# premium-free extension +ContractB = ContractA$clone()$ + addExtension(id = "Verlängerung1", contractPeriod = 5, premiumPeriod = 0) +# sumInsured calculated from existing reserve: +ContractB$blocks$Verlängerung1$Parameters$ContractData$sumInsured +ContractB$Values$basicData + +# extension with given sumInsured resulting in 0 (gross) premiums +ContractC = ContractA$clone()$ + addExtension(id = "Verlängerung1", contractPeriod = 5, sumInsured = 10723.07973354) +ContractC$blocks$Verlängerung1$Values$premiums[["gross"]] +ContractC$Values$basicData + +# extension with increased sumInsured: real premiums are charged, reserves start from the existing reserve: +ContractD = ContractA$clone()$ + addExtension(id = "Verlängerung1", contractPeriod = 5, sumInsured = 20000) +ContractD$Values$basicData + +# extension with regular premiums, which are given: sumInsured is calculated from it, reserves start from the existing reserve: +ContractD = ContractA$clone()$ + addExtension(id = "Verlängerung1", contractPeriod = 5, premium = 597.8771) +ContractD$Values$basicData +``` + + # Handling contracts with increases While many insurance contracts have a fixed sum insured and constant premium, -- GitLab