Skip to content
Snippets Groups Projects
Commit 9c7dcd8f authored by Reinhold Kainhofer's avatar Reinhold Kainhofer
Browse files

Implement premium composition, excel exort

- Start of premium decomposition
- Net reserves
- Excel export
- add p to the death probabilities data frame of ValuationTable
- Add function to convert 3-D cash flow matrix to 2-D
- Move excel loading from xlsx to openxlsx library
parent c2d20d57
No related branches found
No related tags found
No related merge requests found
......@@ -55,6 +55,9 @@ calculatePVDeath = function(q, benefits, ..., v=1) {
res[1:l]
}
getSavingsPremium = function(reserves, v=1) {
pad0(reserves[-1], length(reserves))*v - reserves
}
correctionPaymentFrequency = function(m = 1, i = self$i, order = 0) {
# 0th-order approximation
......
library(R6)
library(openxlsx);
# require(xlsx)
InsuranceContract = R6Class(
"InsuranceContract",
......@@ -35,6 +38,8 @@ InsuranceContract = R6Class(
premiums = NA,
reserves = NA,
premiumComposition = NA,
#### The code:
......@@ -49,8 +54,8 @@ InsuranceContract = R6Class(
self$tarif = tarif;
self$age = age;
self$policyPeriod = policyPeriod;
if (missing(premiumPeriod) && !is.na(self$tarif$premiumPeriod)) {
self$premiumPeriod = self$tarif$premiumPeriod;
if (missing(premiumPeriod) && !is.na(self$tarif$defaultPremiumPeriod)) {
self$premiumPeriod = self$tarif$defaultPremiumPeriod;
} else {
self$premiumPeriod = premiumPeriod;
}
......@@ -74,6 +79,171 @@ InsuranceContract = R6Class(
self$calculatePremiums();
self$calculatePresentValuesAllBenefits();
self$calculateReserves();
self$premiumAnalysis();
},
exportExcel.new = function(filename) {
crow=1;
nrrows = dim(self$cashFlows)[[1]]; # Some vectors are longer (e.g. qx), so determine the max nr or rows
wb = openxlsx::createWorkbook();
addWorksheet(wb, "Tarifinformationen");
addWorksheet(wb, "Reserven");
addWorksheet(wb, "Barwerte");
addWorksheet(wb, "Cash-Flows");
# Print out general Contract and Tariff information, including results
crow = 1;
writeData(wb, "Tarifinformationen", matrix(c(
"Tarif:", self$tarif$tarif,
"Tarifname:", self$tarif$name,
"Description:", self$tarif$desc
), 3, 2, byrow = TRUE), startCol=1, startRow=1, colNames=FALSE, rowNames=FALSE,
borders = "all");
mergeCells(wb, "Tarifinformationen", cols=2:10, rows=1);
mergeCells(wb, "Tarifinformationen", cols=2:10, rows=2);
mergeCells(wb, "Tarifinformationen", cols=2:10, rows=3);
crow = crow+4;
# Basic parameters
values=c(
"Sum insured"=self$sumInsured,
"Mortality table"=self$tarif$mortalityTable@name,
"YOB"=self$YOB,
"Age"=self$age,
"Policy duration"=self$policyPeriod,
"Premium period"=self$premiumPeriod,
"Deferral"=self$deferral,
"Guaranteed payments"=self$guaranteed,
i=self$tarif$i);
writeData(wb, "Tarifinformationen", "Basisdaten des Vertrags und Tarifs", startCol=1, startRow=crow);
mergeCells(wb, "Tarifinformationen", cols=1:length(values), rows=crow:crow);
writeDataTable(wb, "Tarifinformationen", as.data.frame(t(values)),
startCol=1, startRow=crow+1, colNames=TRUE, rowNames=FALSE,
tableStyle="TableStyleMedium3", withFilter = FALSE);
crow = crow + 4;
# Premiums
writeData(wb, "Tarifinformationen", "Prämien", startCol=1, startRow=crow);
mergeCells(wb, "Tarifinformationen", cols=1:length(self$premiums), rows=crow:crow);
writeDataTable(wb, "Tarifinformationen", as.data.frame(t(self$premiums)),
startCol=1, startRow=crow+1, colNames=TRUE, rowNames=FALSE,
tableStyle="TableStyleMedium3", withFilter = FALSE);
crow = crow + 4;
################################################
# Print out Reserves and premium decomposition
################################################
# Age, death and survival probabilities
ccol = 1;
writeDataTable(wb, "Reserven", self$transitionProbabilities[1:nrrows,],
startRow=3, startCol = ccol, colNames = TRUE, rowNames = TRUE,
tableStyle = "TableStyleMedium3", withFilter = FALSE);
ccol = ccol + dim(self$transitionProbabilities)[[2]] + 2;
writeDataTable(wb, "Reserven", as.data.frame(self$reserves), startRow=3,
startCol=ccol, colNames=TRUE, rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="Reserves", withFilter = FALSE)
ccol = ccol + dim(self$reserves)[[2]] + 1;
writeDataTable(wb, "Reserven", as.data.frame(self$premiumComposition), startRow=3,
startCol=ccol, colNames=TRUE, rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="Premium_Decomposition", withFilter = FALSE)
ccol = ccol + dim(self$premiumComposition)[[2]] + 1;
################################################
# Print out present values
################################################
# Age, death and survival probabilities
ccol = 1;
writeDataTable(wb, "Barwerte", self$transitionProbabilities[1:nrrows,],
startRow=3, startCol = ccol, colNames = TRUE, rowNames = TRUE,
tableStyle = "TableStyleMedium3", withFilter = FALSE);
ccol = ccol + dim(self$transitionProbabilities)[[2]] + 2;
writeDataTable(wb, "Barwerte", as.data.frame(self$presentValues), startRow=3,
startCol=ccol, colNames=TRUE, rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="PresentValues_Benefits", withFilter = FALSE)
ccol = ccol + dim(self$presentValues)[[2]] + 1;
costPV = as.data.frame(self$tarif$costValuesAsMatrix(self$presentValuesCosts));
writeDataTable(wb, "Barwerte", as.data.frame(costPV), startRow=3, startCol=ccol,
colNames=TRUE, rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="PresentValues_Costs", withFilter = FALSE)
ccol = ccol + dim(costPV)[[2]] + 1;
################################################
# Print out cash flows
################################################
# Age, death and survival probabilities
ccol = 1;
writeDataTable(wb, "Cash-Flows", self$transitionProbabilities[1:nrrows,],
startRow=3, startCol = ccol, colNames = TRUE, rowNames = TRUE,
tableStyle = "TableStyleMedium3", withFilter = FALSE);
ccol = ccol + dim(self$transitionProbabilities)[[2]] + 2;
# Benefit Cash Flows
writeDataTable(wb, "Cash-Flows", self$cashFlows, startRow=3, startCol=ccol,
colNames=TRUE, rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="CashFlows_CBenefots", withFilter = TRUE)
ccol = ccol + dim(self$cashFlows)[[2]] + 1;
# Costs Cash Flows
# Age, death and survival probabilities
costCF = as.data.frame(self$tarif$costValuesAsMatrix(self$cashFlowsCosts));
writeDataTable(wb, "Cash-Flows", costCF, startRow=3, startCol=ccol, colNames=TRUE,
rowNames=FALSE, tableStyle="TableStyleMedium3",
tableName="CashFlows_Costs", withFilter = TRUE)
ccol = ccol + dim(costCF)[[2]] + 1;
openxlsx::saveWorkbook(wb, filename, overwrite = TRUE)
# #### Contract
# premiumPayments = PaymentTimeEnum("in advance"),
# benefitPayments = PaymentTimeEnum("in advance"),
# premiumFrequency = 1,
# benefitFrequency = 1, # Only for annuities!
# loadings = list(), # Allow overriding the tariff-defined loadings (see the InsuranceTariff class for all possible names)
# premiumSum = 0,
#
#
# #### TARIF:
# tariffType = TariffTypeEnum("wholelife"), # possible values: annuity, wholelife, endowment, pureendowment, terme-fix
# premiumFrequencyOrder = 0,
# benefitFrequencyOrder = 0,
# widowFactor = 0,
# premiumRefund = 0,
# premiumRefundLoading = 0, # Mindesttodesfallrisiko soll damit erreicht werden, z.B. 105% der einbezahlten Prämien
# costs = list(),
# benefitFrequencyLoading = list("1" = 0.0, "2" = 0.0, "4" = 0.0, "12" = 0.0), # TODO: Properly implement this
# premiumFrequencyLoading = list("1" = 0.0, "2" = 0.0, "4" = 0.0, "12" = 0.0), # TODO: Implement this
# loadings = list( # Loadings can also be function(sumInsured, premiums) # TODO: Add other possible arguments
# "ongoingAlphaGrossPremium" = 0, # Acquisition cost that increase the gross premium
# "tax" = 0.04, # insurance tax, factor on each premium paid
# "unitcosts" = 0, # annual unit cost for each policy (Stückkosten), absolute value
# "security" = 0, # Additional security loading on all benefit payments, factor on all benefits
# "noMedicalExam" = 0, # Loading when no medicial exam is done, % of SumInsured
# "noMedicalExamRelative" = 0, # Loading when no medicial exam is done, % of gross premium
# "sumRebate" = 0, # gross premium reduction for large premiums, % of SumInsured
# "premiumRebate" = 0, # gross premium reduction for large premiums, % of gross premium # TODO
# "advanceProfitParticipation" = 0, # Vorweggewinnbeteiligung (%-Satz der Bruttoprämie)
# "advanceProfitParticipationInclUnitCost" = 0, # Vorweggewinnbeteiligung (%-Satz der Prämie mit Zu-/Abschlägen, insbesondere nach Stückkosten)
# "partnerRebate" = 0 # Partnerrabatt auf Prämie mit Zu-/Abschlägen, wenn mehr als 1 Vertrag gleichzeitig abgeschlossen wird, additiv mit advanceBonusInclUnitCost and premiumRebate
# ),
},
......@@ -98,7 +268,7 @@ InsuranceContract = R6Class(
# Add total benefits present value to the PV array. This can only be done after premium calculation, because e.g. premium refund depends on gross premium!
calculatePresentValuesAllBenefits = function() {
pvAllBenefits = self$tarif$presentValueBenefits(presentValues = self$presentValues, premiums = self$premiums, sumInsured = self$sumInsured);
pvAllBenefits = self$tarif$presentValueBenefits(presentValues = self$presentValues, premiums = self$premiums, sumInsured = self$sumInsured );
self$presentValues = cbind(self$presentValues, pvAllBenefits)
self$presentValues
},
......@@ -112,6 +282,12 @@ InsuranceContract = R6Class(
self$reserves = self$tarif$reserveCalculation(premiums=self$premiums, pvBenefits=self$presentValues, pvCosts=self$presentValuesCosts, sumInsured=self$sumInsured, loadings = self$loadings);
},
premiumAnalysis = function() {
self$premiumComposition = self$tarif$premiumDecomposition(premiums=self$premiums, reserves=self$reserves, pvBenefits=self$presentValues, pvCosts=self$presentValuesCosts, sumInsured=self$sumInsured);
# self$premiums = cbind(self$premiums, premiumComposition)
# self$premiums
},
dummy=NA
)
);
......@@ -46,7 +46,7 @@ InsuranceTarif = R6Class(
benefitFrequencyOrder = 0,
widowFactor = 0,
premiumPeriod = NA,
defaultPremiumPeriod = NA,
premiumRefund = 0,
premiumRefundLoading = 0, # Mindesttodesfallrisiko soll damit erreicht werden, z.B. 105% der einbezahlten Prämien
......@@ -77,7 +77,7 @@ InsuranceTarif = R6Class(
if (!missing(benefitFrequencyOrder)) self$benefitFrequencyOrder = benefitFrequencyOrder;
if (!missing(premiumFrequencyOrder)) self$premiumFrequencyOrder = premiumFrequencyOrder;
# Set default premiumPeriod, e.g. single premium, to be used when the contract has no explicit premium period
if (!missing(premiumPeriod)) self$premiumPeriod = premiumPeriod;
if (!missing(premiumPeriod)) self$defaultPremiumPeriod = premiumPeriod;
self$v = 1/(1+self$i);
......@@ -99,7 +99,7 @@ InsuranceTarif = R6Class(
# p = 1 - q;
# len = length(p);
# df = data.frame(p, q=q, rep(0,len), rep(1,len), row.names = ages)
df = data.frame(age=ages, q=q, row.names = ages-age)
df = data.frame(age=ages, q=q, p=1-q, row.names = ages-age)
df
},
getBasicCashFlows = function(age, ..., guaranteed = 0, policyPeriod = inf, deferral = 0, maxAge = getOmega(self$mortalityTable)) {
......@@ -232,6 +232,17 @@ InsuranceTarif = R6Class(
pvc
},
# Cost values (CF, present values, etc.) are an Tx5x3 matrix => convert to Tx15 matrix (alpha | Zillmer | beta | gamma)
costValuesAsMatrix = function (costValues) {
dm = dim(costValues);
nm = dimnames(costValues);
colnames=t(outer(nm[[2]], nm[[3]], paste, sep="."));
res = aperm(costValues, c(1,3,2));
dim(res) = c(dm[[1]], dm[[2]]*dm[[3]]);
dimnames(res) = list(nm[[1]], colnames)
res
},
presentValueBenefits = function(presentValues, premiums, sumInsured=1) {
benefits.unit = presentValues[,"survival"] + presentValues[,"death_SumInsured"];
benefits = benefits.unit * sumInsured;
......@@ -281,16 +292,16 @@ InsuranceTarif = R6Class(
} else if (type=="Zillmer") {
coefficients[["SumInsured"]][["costs"]]["Zillmer","SumInsured"] = 1;
coefficients[["SumInsured"]][["costs"]]["beta", "SumInsured"] = 1;
coefficients[["SumInsured"]][["costs"]]["gamma", "SumInsured"] = 1;
# coefficients[["SumInsured"]][["costs"]]["beta", "SumInsured"] = 1;
# coefficients[["SumInsured"]][["costs"]]["gamma", "SumInsured"] = 1;
coefficients[["SumInsured"]][["costs"]]["Zillmer","SumPremiums"] = premiumSum * premiums[["unit.gross"]];
coefficients[["SumInsured"]][["costs"]]["beta", "SumPremiums"] = premiumSum * premiums[["unit.gross"]];
coefficients[["SumInsured"]][["costs"]]["gamma", "SumPremiums"] = premiumSum * premiums[["unit.gross"]];
# coefficients[["SumInsured"]][["costs"]]["beta", "SumPremiums"] = premiumSum * premiums[["unit.gross"]];
# coefficients[["SumInsured"]][["costs"]]["gamma", "SumPremiums"] = premiumSum * premiums[["unit.gross"]];
coefficients[["SumInsured"]][["costs"]]["Zillmer","GrossPremium"] = premiums[["unit.gross"]];
coefficients[["SumInsured"]][["costs"]]["beta", "GrossPremium"] = premiums[["unit.gross"]];
coefficients[["SumInsured"]][["costs"]]["gamma", "GrossPremium"] = premiums[["unit.gross"]];
# coefficients[["SumInsured"]][["costs"]]["beta", "GrossPremium"] = premiums[["unit.gross"]];
# coefficients[["SumInsured"]][["costs"]]["gamma", "GrossPremium"] = premiums[["unit.gross"]];
}
coefficients
......@@ -355,18 +366,29 @@ str(premiumBeforeTax);
},
reserveCalculation = function (premiums, pvBenefits, pvCosts, sumInsured=1, ...) {
resNet = pvBenefits[,"allBenefits"]*(1+self$loadings$security) - premiums[["net"]] * pvBenefits[,"premiums"];
resZ = pvBenefits[,"allBenefits"]*(1+self$loadings$security) - premiums[["Zillmer"]] * pvBenefits[,"premiums"];
res.gamma = (pvCosts[,"gamma", "SumInsured"] - pvCosts["0", "gamma", "SumInsured"]/pvBenefits["0", "premiums"]*pvBenefits[,"premiums"])*sumInsured;
# res.premiumfree =
# res.gamma.premiumfree =
res = cbind("Reserve"=resZ, "Reserve.gamma"=res.gamma#, "Reserve.premiumfree"=res.premiumfree, "Reserve.gamma.premiumfree"=res.gamma.premiumfree);
res = cbind("net"=resNet, "Zillmer"=resZ, "gamma"=res.gamma#, "Reserve.premiumfree"=res.premiumfree, "Reserve.gamma.premiumfree"=res.gamma.premiumfree);
);
rownames(res) <- rownames(pvBenefits);
res
},
premiumDecomposition = function(premiums, reserves, pvBenefits, pvCosts, sumInsured=1, ...) {
premium.savings = getSavingsPremium(reserves[,"Zillmer"], self$v) + getSavingsPremium(reserves[,"gamma"], self$v);
# TODO: Sparprämie,
res = cbind("savings"=premium.savings);
rownames(res) <- rownames(premiums);
res
},
......
File added
......@@ -339,8 +339,8 @@ plotValuationTables = function(data, ..., title = "", legend.position=c(0.9,0.1)
}
pl# + coord_flip()
}
plotValuationTables(mort.AT.census.1869.male, mort.AT.census.1869.female, mort.AT.census.2011.male, mort.AT.census.2011.female, AVOe2005R.male, AVOe2005R.female, YOB=1972,title="Vergleich österreichische Sterbetafeln, YOB=1972 (bei Generationentafeln)")
plotValuationTables(mort.AT.census.2001.male, AVOe2005R.male, YOB=1972, title="Vergleich österreichische Sterbetafeln")
plotValuationTables(getCohortTable(AVOe2005R.male, YOB=1972), getCohortTable(AVOe2005R.male, YOB=2016), title="Vergleich österreichische Sterbetafeln")
#
# plotValuationTables(mort.AT.census.1869.male, mort.AT.census.1869.female, mort.AT.census.2011.male, mort.AT.census.2011.female, AVOe2005R.male, AVOe2005R.female, YOB=1972,title="Vergleich österreichische Sterbetafeln, YOB=1972 (bei Generationentafeln)")
#
# plotValuationTables(mort.AT.census.2001.male, AVOe2005R.male, YOB=1972, title="Vergleich österreichische Sterbetafeln")
plotValuationTables(getCohortTable(AVOe2005R.male, YOB=1972), getCohortTable(AVOe2005R.male, YOB=2016), title="Vergleich österreichische Sterbetafeln")
......@@ -5,7 +5,7 @@
# setwd(dirname(PATH))
setwd("R")
library("gdata")
library("openxlsx")
......@@ -13,13 +13,12 @@ library("gdata")
### RR67 Rententafel für Männer, 3%
###############################################################################
rr67.data=read.xls(
"Tables/AVOe_R.xls",
sheet="OeVM59-61 RR67", skip=1, #row.names=1,
col.names=c("age","qx"));
rr67.data=read.xlsx(
"Tables/AVOe_R.xlsx",
sheet="OeVM59-61 RR67", startRow = 3, colNames = TRUE);
rr67=valuationTable.period(
name="ÖVM 59/61 RR67", ages=rr67.data$age, deathProbs=rr67.data$qx
name="ÖVM 59/61 RR67", ages=rr67.data$Alter, deathProbs=rr67.data$qx
);
# rm(rr67.data);
......@@ -28,51 +27,42 @@ rr67=valuationTable.period(
### EROM/EROF 85 and G 1985 (period and age-shifted generation)
###############################################################################
eromf.data=read.xls(
"Tables/AVOe_R.xls",
sheet="EROM-F Basistafeln", skip=2, #row.names=1,
col.names=c("age", "EROM85", "EROF85", "EROMG1950", "EROFG1950","","","")
);
eromf.data=read.xlsx("Tables/AVOe_R.xlsx", sheet="EROM-F Basistafeln", startRow = 3)
erom85.male=valuationTable.period(
name="EROM 85, male", ages=eromf.data$age, deathProbs=eromf.data$EROM85
name="EROM 85, male", ages=eromf.data$Alter, deathProbs=eromf.data$EROM.85
);
erom85.female=valuationTable.period(
name="EROF 85, female", ages=eromf.data$age, deathProbs=eromf.data$EROF85
name="EROF 85, female", ages=eromf.data$Alter, deathProbs=eromf.data$EROF.85
);
EROM.G1950.male=valuationTable.period(
name="EROM G 1950 Basistafel, male",
ages=eromf.data$age,
deathProbs=eromf.data$EROMG1950,
ages=eromf.data$Alter,
deathProbs=eromf.data$EROM.G1950,
baseYear=1950
);
EROF.G1950.female=valuationTable.period(
name="EROF G 1950 Basistafel, female",
ages=eromf.data$age,
deathProbs=eromf.data$EROFG1950,
ages=eromf.data$Alter,
deathProbs=eromf.data$EROF.G1950,
baseYear=1950
);
eromf.data.av=read.xls(
"Tables/AVOe_R.xls",
sheet="EROM-F G AV", skip=1, row.names=1,
col.names=c("YOB", "shiftM", "shiftF")
);
eromf.data.av=read.xlsx("Tables/AVOe_R.xlsx", sheet="EROM-F G AV", startRow = 3, rowNames = TRUE, colNames = TRUE)
EROM.G1950.male.av=valuationTable.ageShift(
name="EROM G 1950 mit Altersverschiebung, male",
ages=eromf.data$age,
deathProbs=eromf.data$EROMG1950,
ageShifts=eromf.data.av[1],
ages=eromf.data$Alter,
deathProbs=eromf.data$EROM.G1950,
ageShifts=eromf.data.av["Shift.M"],
baseYear=1950
);
EROF.G1950.female.av=valuationTable.ageShift(
name="EROF G 1950 mit Altersverschiebung, female",
ages=eromf.data$age,
deathProbs=eromf.data$EROFG1950,
ageShifts=eromf.data.av[2],
ages=eromf.data$Alter,
deathProbs=eromf.data$EROF.G1950,
ageShifts=eromf.data.av["Shift.F"],
baseYear=1950
);
......@@ -81,15 +71,10 @@ EROF.G1950.female.av=valuationTable.ageShift(
# AVÖ 1996R exact (Male, Female), 1st-order only
###############################################################################
AVOe1996R.exakt.data=read.xls(
"Tables/AVOe_R.xls",
sheet="AVOe 1996R exakt", skip=2, #row.names=1,
col.names=c("age",
"q1991M", "trendM.long", "trendM.short", "factorMG", "factorM",
"",
"q1991F", "trendF.long", "trendF.short", "factorFG", "factorF",
rep("",16))
);
AVOe1996R.exakt.data=read.xlsx("Tables/AVOe_R.xlsx",
sheet="AVOe 1996R exakt", startRow = 3, cols=c(1:6, 8:12));
AVOe1996R.exakt.data
AVOe1996R.trend.switching=function(year) {
if (year<=1971) {
15/(1991-year)
......@@ -107,7 +92,7 @@ AVOe1996R.trend.switching=function(year) {
AVÖ1996R.male=valuationTable.trendProjection(
name="AVÖ 1996R male",
ages=AVOe1996R.exakt.data$age, baseYear=1991,
deathProbs=AVOe1996R.exakt.data$q1991M*AVOe1996R.exakt.data$factorM,
deathProbs=AVOe1996R.exakt.data$qx1991 * AVOe1996R.exakt.data$factorM,
trend=AVOe1996R.exakt.data$trendM.long,
trend2=AVOe1996R.exakt.data$trendM.short,
dampingFunction=AVOe1996R.trend.switching
......@@ -115,7 +100,7 @@ AVÖ1996R.male=valuationTable.trendProjection(
AVÖ1996R.female=valuationTable.trendProjection(
name="AVÖ 1996R female",
ages=AVOe1996R.exakt.data$age, baseYear=1991,
deathProbs=AVOe1996R.exakt.data$q1991F*AVOe1996R.exakt.data$factorF,
deathProbs=AVOe1996R.exakt.data$qy1991 * AVOe1996R.exakt.data$factorF,
trend=AVOe1996R.exakt.data$trendF.long,
trend2=AVOe1996R.exakt.data$trendF.short,
dampingFunction=AVOe1996R.trend.switching
......@@ -123,7 +108,7 @@ AVÖ1996R.female=valuationTable.trendProjection(
AVÖ1996R.male.group=valuationTable.trendProjection(
name="AVÖ 1996R male, group",
ages=AVOe1996R.exakt.data$age, baseYear=1991,
deathProbs=AVOe1996R.exakt.data$q1991M*AVOe1996R.exakt.data$factorMG,
deathProbs=AVOe1996R.exakt.data$qx1991 * AVOe1996R.exakt.data$factorMG,
trend=AVOe1996R.exakt.data$trendM.long,
trend2=AVOe1996R.exakt.data$trendM.short,
dampingFunction=AVOe1996R.trend.switching
......@@ -131,7 +116,7 @@ AVÖ1996R.male.group=valuationTable.trendProjection(
AVÖ1996R.female.group=valuationTable.trendProjection(
name="AVÖ 1996R female, group",
ages=AVOe1996R.exakt.data$age, baseYear=1991,
deathProbs=AVOe1996R.exakt.data$q1991F*AVOe1996R.exakt.data$factorFG,
deathProbs=AVOe1996R.exakt.data$qy1991 * AVOe1996R.exakt.data$factorFG,
trend=AVOe1996R.exakt.data$trendF.long,
trend2=AVOe1996R.exakt.data$trendF.short,
dampingFunction=AVOe1996R.trend.switching
......@@ -144,20 +129,7 @@ AVÖ1996R.female.group=valuationTable.trendProjection(
# gender-specific tables also have 2nd-order tables, unisex only 1st-order table
###############################################################################
AVOe2005R.exakt.data=read.xls(
"Tables/AVOe_R.xls",
sheet="AVOe 2005R", skip=3, #row.names=1,
header=FALSE,
col.names=c("age",
"q2001M","q2001MG", "trendM",
"q2001F", "q2001FG", "trendF",
"",
"q2001M.2Ord", "2001MG.2Ord", "trendM.2Ord",
"q2001F.2Ord", "q2001FG.2Ord", "trendF.2Ord",
"",
"q2001U", "q2001UG", "trendU",
rep("", 10))
);
AVOe2005R.exakt.data=read.xlsx("Tables/AVOe_R.xlsx", sheet="AVOe 2005R", startRow = 3, cols=c(1:7, 9:14, 16:18));
AVOe2005R.trend.damping=function(t) {
100*atan(t/100)
......@@ -174,14 +146,14 @@ AVOe2005R_gen=function(nm, probs, trend) {
)
}
AVOe2005R.male =AVOe2005R_gen("AVÖ 2005R male (exact), loaded", "q2001M", "trendM");
AVOe2005R.female=AVOe2005R_gen("AVÖ 2005R female (exact), loaded", "q2001F", "trendF");
AVOe2005R.unisex=AVOe2005R_gen("AVÖ 2005R unisex (exact), loaded", "q2001U", "trendU");
AVOe2005R.male.unloaded =AVOe2005R_gen("AVÖ 2005R male (exact), unloaded", "q2001M.2Ord", "trendM.2Ord");
AVOe2005R.female.unloaded=AVOe2005R_gen("AVÖ 2005R female (exact), unloaded", "q2001F.2Ord", "trendF.2Ord");
AVOe2005R.male.group =AVOe2005R_gen("AVÖ 2005R male group (exact), loaded", "q2001MG", "trendM");
AVOe2005R.female.group=AVOe2005R_gen("AVÖ 2005R female group (exact), loaded", "q2001FG", "trendF");
AVOe2005R.unisex.group=AVOe2005R_gen("AVÖ 2005R unisex group (exact), loaded", "q2001UG", "trendU");
AVOe2005R.male =AVOe2005R_gen("AVÖ 2005R male (exact), loaded", "qx2001", "trendM");
AVOe2005R.female=AVOe2005R_gen("AVÖ 2005R female (exact), loaded", "qy2001", "trendF");
AVOe2005R.unisex=AVOe2005R_gen("AVÖ 2005R unisex (exact), loaded", "qu2001", "trendU");
AVOe2005R.male.unloaded =AVOe2005R_gen("AVÖ 2005R male (exact), unloaded", "qx2001.2Ord", "trendM.2Ord");
AVOe2005R.female.unloaded=AVOe2005R_gen("AVÖ 2005R female (exact), unloaded", "qy2001.2Ord", "trendF.2Ord");
AVOe2005R.male.group =AVOe2005R_gen("AVÖ 2005R male group (exact), loaded", "qx2001G", "trendM");
AVOe2005R.female.group=AVOe2005R_gen("AVÖ 2005R female group (exact), loaded", "qy2001G", "trendF");
AVOe2005R.unisex.group=AVOe2005R_gen("AVÖ 2005R unisex group (exact), loaded", "qu2001G", "trendU");
AVOe2005R.male.nodamping = undampenTrend(AVOe2005R.male);
AVOe2005R.female.nodamping = undampenTrend(AVOe2005R.female);
......@@ -197,17 +169,8 @@ AVOe2005R.unisex.nodamping.group = undampenTrend(AVOe2005R.unisex.group);
#AVÖ 2005R with age-shifting (Male, Female, unisex), 1st-order only
###############################################################################
AVOe2005R.av.base=read.xls(
"Tables/AVOe_R.xls",
sheet="AVOe 2005R AV Basistafel", skip=1, # row.names=1,
col.names=c("age", "q1965M", "q1965MG", "q1965F", "q1965FG", "q1972U", "q1972UG")
);
AVOe2005R.av.verschiebung=read.xls(
"Tables/AVOe_R.xls",
sheet="AVOe 2005R AV Verschiebung",skip=2,row.names=1,
col.names=c("YOB", "shiftM", "shiftMG", "shiftF", "shiftFG", "shiftU", "shiftUG")
)
AVOe2005R.av.base = read.xlsx("Tables/AVOe_R.xlsx", sheet="AVOe 2005R AV Basistafel", startRow = 3, rowNames = FALSE);
AVOe2005R.av.verschiebung = read.xlsx("Tables/AVOe_R.xlsx", sheet="AVOe 2005R AV Verschiebung", startRow = 3, rowNames = TRUE);
AVOe2005R_gen.av=function(nm, probs, shft) {
valuationTable.ageShift(
......@@ -218,17 +181,17 @@ AVOe2005R_gen.av=function(nm, probs, shft) {
)
}
AVOe2005R.male.av =AVOe2005R_gen.av("AVÖ 2005R male (age-shifted), loaded", "q1965M", "shiftM");
AVOe2005R.female.av=AVOe2005R_gen.av("AVÖ 2005R female (age-shifted), loaded", "q1965F", "shiftF");
AVOe2005R.unisex.av=AVOe2005R_gen.av("AVÖ 2005R unisex (age-shifted), loaded", "q1972U", "shiftU");
AVOe2005R.male.group.av =AVOe2005R_gen.av("AVÖ 2005R male group (age-shifted), loaded", "q1965MG", "shiftMG");
AVOe2005R.female.group.av=AVOe2005R_gen.av("AVÖ 2005R female group (age-shifted), loaded", "q1965FG", "shiftFG");
AVOe2005R.unisex.group.av=AVOe2005R_gen.av("AVÖ 2005R unisex group (age-shifted), loaded", "q1972UG", "shiftUG");
AVOe2005R.male.av =AVOe2005R_gen.av("AVÖ 2005R male (age-shifted), loaded", "qx1965", "shiftM");
AVOe2005R.female.av=AVOe2005R_gen.av("AVÖ 2005R female (age-shifted), loaded", "qy1965", "shiftF");
AVOe2005R.unisex.av=AVOe2005R_gen.av("AVÖ 2005R unisex (age-shifted), loaded", "qu1972", "shiftU");
AVOe2005R.male.group.av =AVOe2005R_gen.av("AVÖ 2005R male group (age-shifted), loaded", "qx1965G", "shiftMG");
AVOe2005R.female.group.av=AVOe2005R_gen.av("AVÖ 2005R female group (age-shifted), loaded", "qy1965G", "shiftFG");
AVOe2005R.unisex.group.av=AVOe2005R_gen.av("AVÖ 2005R unisex group (age-shifted), loaded", "qu1972G", "shiftUG");
###############################################################################
options("scipen" = 3)
t=AVOe2005R.male;
deathProbabilities(t, YOB=2001)
# options("scipen" = 3, "digits"=10)
# t=AVOe2005R.unisex;
# deathProbabilities(t, YOB=1981)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment