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

Fix Austrian population mortality, fix plotMortalityTables (axes labels not overridable)

parent e5138273
Branches
No related tags found
No related merge requests found
...@@ -86,7 +86,6 @@ plotMortalityTables = function( ...@@ -86,7 +86,6 @@ plotMortalityTables = function(
if (log) { if (log) {
pl = pl + scale_y_log10( pl = pl + scale_y_log10(
name = ylab,
breaks = scales::trans_breaks('log10', function(x) 10^x), breaks = scales::trans_breaks('log10', function(x) 10^x),
labels = scales::trans_format('log10', scales::math_format(10^.x)) labels = scales::trans_format('log10', scales::math_format(10^.x))
#minor_breaks = log(c(sapply(x, function(x) seq(0, x, x/10))), 10) #minor_breaks = log(c(sapply(x, function(x) seq(0, x, x/10))), 10)
...@@ -95,12 +94,11 @@ plotMortalityTables = function( ...@@ -95,12 +94,11 @@ plotMortalityTables = function(
} }
pl = pl + scale_x_continuous( pl = pl + scale_x_continuous(
name = xlab,
minor_breaks = function(limits) seq(max(round(min(limits)), 0), round(max(limits)), 1) minor_breaks = function(limits) seq(max(round(min(limits)), 0), round(max(limits)), 1)
) + ) +
coord_cartesian(xlim = xlim, ylim = ylim) + coord_cartesian(xlim = xlim, ylim = ylim) +
xlab("Alter") + labs(x = xlab, y = ylab, colour = legend.title);
labs(colour = legend.title);
if (title != "") { if (title != "") {
pl = pl + ggtitle(title); pl = pl + ggtitle(title);
} }
......
No preview for this file type
File added
File added
library(tidyverse) library(tidyverse)
library(openxlsx) library(openxlsx)
library(here) library(here)
library(readODS)
library(progress)
library(reshape2)
################################################################################
# Helper Functions
################################################################################
StatAustria.readODSMortality = function(filename, sheet, jahr = sheet, oldFormat = FALSE, ...) {
# browser()
# The tables provided by statistik Austria have duplicate column names (for
# male, female and unisex data), so when selecting the corresponding columns,
# we also need to rename them to contain the sex!
tmp.tbl = read_ods(filename, sheet = sheet, skip = ifelse(oldFormat, 10, 5), .name_repair = "minimal")
# alle Spalten mit q(x)
qxname = ifelse(oldFormat, "q.x.", "qx")
indices = which(colnames(tmp.tbl) %in% paste0(qxname, c("", ".1", "..1", ".2", "..2", ".3", "..3")))
# bis 2002 nur M/F, ab 2002 auch unisex
geschlecht = c("M", "F", "U")[1:length(indices)]
names(indices) <- geschlecht
# Extraktion Spalten mit q(x), Umbenennung, Transformation auf langes Format
tmp.tbl %>%
select(any_of(c(Alter = 1, indices))) %>%
mutate(Jahr = jahr, Alter = suppressWarnings(as.numeric(Alter))) %>%
filter(!is.na(Alter)) %>%
pivot_longer(cols = geschlecht, names_to = "Geschlecht", values_to = "qx")
}
################################################################################
# OFFICIAL Population Mortality Tables provided by Statistik Austria
################################################################################
# url.StT.official = "https://www.statistik.at/fileadmin/pages/413/Ausfuehrliche_allgemeine_und_ausgeglichene_Sterbetafeln_186871_bis_202022.ods"
# filename.StT.official = here("data-raw", "Austria", basename(url.StT.official))
# download.file(url.StT.official, filename.StT.official, method = "curl")
# => Downloaded manually and pasted into Austria_Census.xlsx
################################################################################
# YEARLY GRADUATED Population Mortality Tables (2016--2022) provided by Statistik Austria
################################################################################
url.StT.yearlyGrad = "https://www.statistik.at/fileadmin/pages/413/Geglaettete_Sterbetafeln_2016_2022.ods"
filename.StT.yearlyGrad = here("data-raw", "Austria", basename(url.StT.yearlyGrad))
download.file(url.StT.yearlyGrad, filename.StT.yearlyGrad, method = "curl")
Jahre = list_ods_sheets(filename.StT.yearlyGrad)
pb = progress_bar$new(total = length(Jahre),
format = " Lade Sterbetafeln [:bar] :percent (:current/:total), eta :eta"
);
pb$tick(0);
df.qx = data.frame(Jahr = NA_character_, Alter = NA_integer_, Geschlecht = NA_character_, qx = NA_real_) %>%
filter(!is.na(Alter))
for (jahr in Jahre) {
# Worksheet laden und in globalem DF zwischenspeichern
qx = StatAustria.readODSMortality(filename.StT.yearlyGrad, sheet = jahr)
df.qx = bind_rows(df.qx, qx)
pb$tick()
}
## Nach Excel und CSV rausschreiben (pro Geschlecht):
filename.StT.yearlyGradTable = file.path(dirname(filename.StT.yearlyGrad), paste0("Austria_JaehrlicheSterbetafeln_Geglättet_", str_sub(min(Jahre), 1, 4), "-", str_sub(max(Jahre), -4, -1), ".xlsx"))
wb <- createWorkbook()
options(openxlsx.borderColour = "#4F80BD")
options(openxlsx.borderStyle = "thin")
modifyBaseFont(wb, fontSize = 10, fontName = "Arial Narrow")
for (g in c("M", "F", "U")) {
qx.data = df.qx %>%
filter(Geschlecht == g) %>%
acast(Alter ~ Jahr, value.var = "qx") %>%
as_tibble(rownames = "Alter") %>%
mutate(Alter = as.integer(Alter))
addWorksheet(wb, sheetName = g, gridLines = FALSE)
writeData(wb, sheet = g, startCol = 1, startRow = 1,
x = paste0("Jährliche Sterbetafeln Österreich ", c("M"= "Männer", "F"="Frauen", "U" = "Unisex")[g], ", ", str_sub(min(Jahre), 1, 4), "-",str_sub(max(Jahre), -4, -1)))
writeData(wb, sheet = g, startCol = 1, startRow = 2,
x = "Quelle: Statistik Austria, https://www.statistik.at/statistiken/bevoelkerung-und-soziales/bevoelkerung/demographische-indikatoren-und-tafeln/sterbetafeln")
writeDataTable(wb, sheet = g, startRow = 4, x = qx.data, colNames = TRUE, rowNames = FALSE, tableStyle = "TableStyleLight9")
freezePane(wb, sheet = g, firstActiveRow = 4, firstActiveCol = 2)
}
saveWorkbook(wb, filename.StT.yearlyGradTable, overwrite = TRUE)
df.qx %>%
write.csv(file = file.path("inst", "extdata", paste0("Austria_Population_YearlyGraduated.csv")), row.names = FALSE)
# openXL(filename.StT.yearlyGradTable)
################################################################################
# Yearly Population Mortality Tables (ungraduated) provided by Statistik Austria
################################################################################
## Download current population mortality tables and extract / convert to an easier-to-handle format ## Download current population mortality tables and extract / convert to an easier-to-handle format
## Source: Statistik Austria, https://www.statistik.at/statistiken/bevoelkerung-und-soziales/bevoelkerung/demographische-indikatoren-und-tafeln/sterbetafeln ## Source: Statistik Austria, https://www.statistik.at/statistiken/bevoelkerung-und-soziales/bevoelkerung/demographische-indikatoren-und-tafeln/sterbetafeln
## Data: * graduated census tables (1868/71 - 2020/22), roughly every 10 years ## Data: * graduated census tables (1868/71 - 2020/22), roughly every 10 years
## * yearly ungraduated / raw population mortality tables (1947 - 2022), yearly; From 2002 on also unisex ## * yearly ungraduated / raw population mortality tables (1947 - 2022), yearly; From 2002 on also unisex
library(readODS)
library(progress)
# yearly mortality tables 1947--2022 # yearly mortality tables 1947--2022
...@@ -27,25 +126,6 @@ pb = progress_bar$new(total = length(Jahre), ...@@ -27,25 +126,6 @@ pb = progress_bar$new(total = length(Jahre),
); );
pb$tick(0); pb$tick(0);
StatAustria.readODSMortality = function(filename, sheet, jahr = sheet, oldFormat = FALSE, ...) {
# The tables provided by statistik Austria have duplicate column names (for
# male, female and unisex data), so when selecting the corresponding columns,
# we also need to rename them to contain the sex!
tmp.tbl = read_ods(filename, sheet = sheet, skip = ifelse(oldFormat, 8, 5))
# alle Spalten mit q(x)
qxname = ifelse(oldFormat, "q(x)", "qx")
indices = which(colnames(tmp.tbl) == qxname)
# bis 2002 nur M/F, ab 2002 auch unisex
geschlecht = c("M", "F", "U")[1:length(indices)]
names(indices) <- geschlecht
# Extraktion Spalten mit q(x), Umbenennung, Transformation auf langes Format
tmp.tbl %>%
select(c(Alter = 1, indices)) %>%
mutate(Jahr = jahr, Alter = as.numeric(Alter)) %>%
filter(!is.na(Alter)) %>%
pivot_longer(cols = geschlecht, names_to = "Geschlecht", values_to = "qx")
}
df.qx = data.frame(Jahr = NA_integer_, Alter = NA_integer_, Geschlecht = NA_character_, qx = NA_real_) df.qx = data.frame(Jahr = NA_integer_, Alter = NA_integer_, Geschlecht = NA_character_, qx = NA_real_)
for (jahr in Jahre) { for (jahr in Jahre) {
...@@ -66,23 +146,21 @@ for (g in c("M", "F", "U")) { ...@@ -66,23 +146,21 @@ for (g in c("M", "F", "U")) {
qx.data = df.qx %>% qx.data = df.qx %>%
filter(Geschlecht == g) %>% filter(Geschlecht == g) %>%
acast(Alter ~ Jahr, value.var = "qx") %>% acast(Alter ~ Jahr, value.var = "qx") %>%
as_tibble as_tibble(rownames = "Alter") %>%
mutate(Alter = as.integer(Alter))
qx.data %>% qx.data %>%
write.csv(file = file.path("inst", "extdata", paste0("Austria_Population_Observation_", g, ".csv"))) write.csv(file = file.path("inst", "extdata", paste0("Austria_Population_Observation_", g, ".csv")), row.names = FALSE)
addWorksheet(wb, sheetName = g, gridLines = FALSE) addWorksheet(wb, sheetName = g, gridLines = FALSE)
writeData(wb, sheet = g, startCol = 1, startRow = 1, writeData(wb, sheet = g, startCol = 1, startRow = 1,
x = paste0("Jährliche Sterbetafeln Österreich ", c("M"= "Männer", "F"="Frauen", "U" = "Unisex")[g], ", ", min(Jahre), "-", max(Jahre))) x = paste0("Jährliche Sterbetafeln Österreich ", c("M"= "Männer", "F"="Frauen", "U" = "Unisex")[g], ", ", min(Jahre), "-", max(Jahre)))
writeData(wb, sheet = g, startCol = 1, startRow = 2, writeData(wb, sheet = g, startCol = 1, startRow = 2,
x = "Quelle: Statistik Austria, https://www.statistik.at/statistiken/bevoelkerung-und-soziales/bevoelkerung/demographische-indikatoren-und-tafeln/sterbetafeln") x = "Quelle: Statistik Austria, https://www.statistik.at/statistiken/bevoelkerung-und-soziales/bevoelkerung/demographische-indikatoren-und-tafeln/sterbetafeln")
writeDataTable(wb, sheet = g, startRow = 4, x = qx.data, colNames = TRUE, rowName = TRUE, tableStyle = "TableStyleLight9") writeDataTable(wb, sheet = g, startRow = 4, x = qx.data, colNames = TRUE, rowNames = FALSE, tableStyle = "TableStyleLight9")
freezePane(wb, sheet = g, firstActiveRow = 4, firstActiveCol = 2) freezePane(wb, sheet = g, firstActiveRow = 4, firstActiveCol = 2)
} }
saveWorkbook(wb, filename.StT.yearlyTable, overwrite = TRUE) saveWorkbook(wb, filename.StT.yearlyTable, overwrite = TRUE)
openXL(filename.StT.yearlyTable)
# url.StT.official = "https://www.statistik.at/fileadmin/pages/413/Ausfuehrliche_allgemeine_und_ausgeglichene_Sterbetafeln_186871_bis_202022.ods"
# filename.StT.official = here("data-raw", "Austria", basename(url.StT.official))
# download.file(url.StT.official, filename.StT.official, method = "curl")
# => Downloaded manually and pasted into Austria_Census.xlsx
Source diff could not be displayed: it is too large. Options to address this: view the blob.
Source diff could not be displayed: it is too large. Options to address this: view the blob.
"","2002","2003","2004","2005","2006","2007","2008","2009","2010","2011","2012","2013","2014","2015","2016","2017","2018","2019","2020","2021","2022" "Alter","2002","2003","2004","2005","2006","2007","2008","2009","2010","2011","2012","2013","2014","2015","2016","2017","2018","2019","2020","2021","2022"
"1",0.00405617418589523,0.00445778748180495,0.00447016513017931,0.00418212047576416,0.00360654054470313,0.00367213114754098,0.00369122337689063,0.00378549722309546,0.00389880876787483,0.00359753677553163,0.00319181274698551,0.00308836505735535,0.00304691515136683,0.00306941136037734,0.0030681494154548,0.00292127394931133,0.00270064885719296,0.002942838,0.003133858832817,0.00273008201863426,0.00244472145908722 0,0.00405617418589523,0.00445778748180495,0.00447016513017931,0.00418212047576416,0.00360654054470313,0.00367213114754098,0.00369122337689063,0.00378549722309546,0.00389880876787483,0.00359753677553163,0.00319181274698551,0.00308836505735535,0.00304691515136683,0.00306941136037734,0.0030681494154548,0.00292127394931133,0.00270064885719296,0.002942838,0.003133858832817,0.00273008201863426,0.00244472145908722
"2",0.000410425447660334,0.000473552265931594,0.000214034695653679,0.000352098285721471,0.000448748412630398,0.000327707684745207,0.000369297967746916,0.000344194036200926,0.000346327564948444,0.000241619614425963,0.000237022621626131,0.000262998464276825,0.000186061800427012,0.000193956144697345,0.000280835602933562,0.000229495311123925,0.000179614586388301,0.000284506,0.000198199301055994,0.000176382656293407,0.000197848686488389 1,0.000410425447660334,0.000473552265931594,0.000214034695653679,0.000352098285721471,0.000448748412630398,0.000327707684745207,0.000369297967746916,0.000344194036200926,0.000346327564948444,0.000241619614425963,0.000237022621626131,0.000262998464276825,0.000186061800427012,0.000193956144697345,0.000280835602933562,0.000229495311123925,0.000179614586388301,0.000284506,0.000198199301055994,0.000176382656293407,0.000197848686488389
"3",0.000125292675860017,0.000241847588286303,0.00015206234556168,0.000249501776140769,0.000187461628947825,8.68627800742987e-05,0.000163150306926515,0.000253520367984814,0.000177883095864694,0.000178808623684479,0.000113683731857971,0.000185790725326992,0.000161338363780778,0.000183875638776308,0.000142740104467914,0.000162558201641838,0.000137052402557169,0.00021249,0.000169915113241343,0.000150937919523965,0.000162266162868866 2,0.000125292675860017,0.000241847588286303,0.00015206234556168,0.000249501776140769,0.000187461628947825,8.68627800742987e-05,0.000163150306926515,0.000253520367984814,0.000177883095864694,0.000178808623684479,0.000113683731857971,0.000185790725326992,0.000161338363780778,0.000183875638776308,0.000142740104467914,0.000162558201641838,0.000137052402557169,0.00021249,0.000169915113241343,0.000150937919523965,0.000162266162868866
"4",0.00012292619664811,0.000298446214396299,0.000113422264790578,0.000175819207620507,0.000111575665347388,0.00014950290284803,0.000123619326645528,0.000125131583680965,0.0001770717393504,0.000126679292369473,0.000101554256154743,0.000137993542529453,0.000159639215373256,4.90423710760356e-05,0.000120339115627839,7.08390890093153e-05,9.24582926420535e-05,0.000159329,8.91761102774074e-05,0.000101580422066654,0.000102972913833124 3,0.00012292619664811,0.000298446214396299,0.000113422264790578,0.000175819207620507,0.000111575665347388,0.00014950290284803,0.000123619326645528,0.000125131583680965,0.0001770717393504,0.000126679292369473,0.000101554256154743,0.000137993542529453,0.000159639215373256,4.90423710760356e-05,0.000120339115627839,7.08390890093153e-05,9.24582926420535e-05,0.000159329,8.91761102774074e-05,0.000101580422066654,0.000102972913833124
"5",0.000131026083124138,0.000122039214250519,0.000147827399192493,7.49621675310742e-05,0.000124829140114468,0.000123506535811492,0.000111783710939744,0.000110978553394557,6.24124275625763e-05,0.000163892574720831,0.000126039828585833,8.83415916946284e-05,7.46810884146294e-05,0.000109242192976334,4.81277551259819e-05,0.000215031284065286,8.22485580799662e-05,8.05937e-05,0.000113465037876048,8.88818524089065e-05,8.89449736361539e-05 4,0.000131026083124138,0.000122039214250519,0.000147827399192493,7.49621675310742e-05,0.000124829140114468,0.000123506535811492,0.000111783710939744,0.000110978553394557,6.24124275625763e-05,0.000163892574720831,0.000126039828585833,8.83415916946284e-05,7.46810884146294e-05,0.000109242192976334,4.81277551259819e-05,0.000215031284065286,8.22485580799662e-05,8.05937e-05,0.000113465037876048,8.88818524089065e-05,8.89449736361539e-05
"6",0.000123662026061772,0.000106460999787078,0.000169432552229097,0.00014663809260501,9.93606761494012e-05,7.46453181056884e-05,9.84719916421897e-05,9.91289047495137e-05,9.85085194477366e-05,9.96558758038648e-05,6.27987848435133e-05,6.26951386189515e-05,8.77329034421065e-05,9.85576700966789e-05,0.00011927320870277,8.36239015029903e-05,7.14162436246124e-05,9.37099e-05,4.5935629827727e-05,0.000113174822563098,8.75908412826584e-05 5,0.000123662026061772,0.000106460999787078,0.000169432552229097,0.00014663809260501,9.93606761494012e-05,7.46453181056884e-05,9.84719916421897e-05,9.91289047495137e-05,9.85085194477366e-05,9.96558758038648e-05,6.27987848435133e-05,6.26951386189515e-05,8.77329034421065e-05,9.85576700966789e-05,0.00011927320870277,8.36239015029903e-05,7.14162436246124e-05,9.37099e-05,4.5935629827727e-05,0.000113174822563098,8.75908412826584e-05
"7",8.88776557407328e-05,0.000145322637214612,0.00011738260272445,0.000120198808829805,0.000109461752239405,9.90744281160843e-05,7.446617063923e-05,6.14383642649898e-05,3.71246925611397e-05,8.60721438265523e-05,9.93697782346027e-05,0.000112629347766576,8.72579954033735e-05,6.20670821023362e-05,2.42452895948309e-05,5.93229765303474e-05,3.57431674701433e-05,5.93859e-05,7.01415983516724e-05,4.58341748201367e-05,8.9272388189821e-05 6,8.88776557407328e-05,0.000145322637214612,0.00011738260272445,0.000120198808829805,0.000109461752239405,9.90744281160843e-05,7.446617063923e-05,6.14383642649898e-05,3.71246925611397e-05,8.60721438265523e-05,9.93697782346027e-05,0.000112629347766576,8.72579954033735e-05,6.20670821023362e-05,2.42452895948309e-05,5.93229765303474e-05,3.57431674701433e-05,5.93859e-05,7.01415983516724e-05,4.58341748201367e-05,8.9272388189821e-05
"8",6.5594291110197e-05,7.73628122487435e-05,8.87975014603027e-05,0.000174954402508846,9.56999328605159e-05,6.06443768259643e-05,7.41334494757375e-05,8.67234188849536e-05,6.13666349605719e-05,9.88733077601642e-05,4.90537982202669e-05,6.18874113269435e-05,0.000112057373375168,3.70380087131916e-05,0.000109893464391465,6.02209204466586e-05,5.91562835064887e-05,7.13494e-05,2.36975247935353e-05,5.830742297225e-05,0.000101606798623792 7,6.5594291110197e-05,7.73628122487435e-05,8.87975014603027e-05,0.000174954402508846,9.56999328605159e-05,6.06443768259643e-05,7.41334494757375e-05,8.67234188849536e-05,6.13666349605719e-05,9.88733077601642e-05,4.90537982202669e-05,6.18874113269435e-05,0.000112057373375168,3.70380087131916e-05,0.000109893464391465,6.02209204466586e-05,5.91562835064887e-05,7.13494e-05,2.36975247935353e-05,5.830742297225e-05,0.000101606798623792
"9",0.000115840687461825,5.43864729964363e-05,0.000120756539721354,0.000110285805665382,6.96305086073463e-05,9.53969481920043e-05,6.04066272110713e-05,9.85505371774202e-05,0.000136033179729201,7.34853970737503e-05,7.39267909150135e-05,9.76815885468337e-05,0.000110714044076491,4.93004725142163e-05,6.06800719058852e-05,6.05888937528306e-05,9.59157859399447e-05,3.53601e-05,8.29628400550518e-05,3.54120710897327e-05,5.72963294538944e-05 8,0.000115840687461825,5.43864729964363e-05,0.000120756539721354,0.000110285805665382,6.96305086073463e-05,9.53969481920043e-05,6.04066272110713e-05,9.85505371774202e-05,0.000136033179729201,7.34853970737503e-05,7.39267909150135e-05,9.76815885468337e-05,0.000110714044076491,4.93004725142163e-05,6.06800719058852e-05,6.05888937528306e-05,9.59157859399447e-05,3.53601e-05,8.29628400550518e-05,3.54120710897327e-05,5.72963294538944e-05
"10",0.000113472543512852,6.28880553310074e-05,0.000140471064311435,9.81750351793876e-05,0.000109708668630452,8.0910474005343e-05,7.12618695551478e-05,0.000132512558576574,7.37199226555145e-05,8.6292844011816e-05,0.000134166793718555,0.000110372230346845,7.28529993428052e-05,6.09043998861088e-05,9.69276949685439e-05,4.81602774031978e-05,0.000108435531311513,0.000107446,9.38825265548193e-05,3.54073169220419e-05,5.79771483069948e-05 9,0.000113472543512852,6.28880553310074e-05,0.000140471064311435,9.81750351793876e-05,0.000109708668630452,8.0910474005343e-05,7.12618695551478e-05,0.000132512558576574,7.37199226555145e-05,8.6292844011816e-05,0.000134166793718555,0.000110372230346845,7.28529993428052e-05,6.09043998861088e-05,9.69276949685439e-05,4.81602774031978e-05,0.000108435531311513,0.000107446,9.38825265548193e-05,3.54073169220419e-05,5.79771483069948e-05
"11",0.000132776353552789,7.18414766502372e-05,0.000114520704822883,0.000128851969220486,8.68374741692435e-05,7.65224900964867e-05,6.90829383852151e-05,0.000106540711869523,6.00560923902925e-05,4.89826907416592e-05,6.14025257928985e-05,7.28551003123662e-05,8.53055156109094e-05,6.01115068451978e-05,7.19228268068363e-05,7.21271963106939e-05,3.5919432712426e-05,0.000119846,5.93975896458122e-05,3.50490321355813e-05,0.000115738731387765 10,0.000132776353552789,7.18414766502372e-05,0.000114520704822883,0.000128851969220486,8.68374741692435e-05,7.65224900964867e-05,6.90829383852151e-05,0.000106540711869523,6.00560923902925e-05,4.89826907416592e-05,6.14025257928985e-05,7.28551003123662e-05,8.53055156109094e-05,6.01115068451978e-05,7.19228268068363e-05,7.21271963106939e-05,3.5919432712426e-05,0.000119846,5.93975896458122e-05,3.50490321355813e-05,0.000115738731387765
"12",7.19411521375515e-05,7.11434531507657e-05,9.17902541697635e-05,8.28258095575808e-05,9.6152947288153e-05,8.64950191032359e-05,7.62473245358444e-05,4.59242909361236e-05,5.9001314254275e-05,9.57302799362795e-05,9.75682634830955e-05,0.000146622191268649,0.000120710441302285,0.000156881911666433,8.2855312431108e-05,5.94692960024739e-05,5.97705408935098e-05,8.33832e-05,0.000119276587496832,3.54690111683049e-05,0.000137627305257363 11,7.19411521375515e-05,7.11434531507657e-05,9.17902541697635e-05,8.28258095575808e-05,9.6152947288153e-05,8.64950191032359e-05,7.62473245358444e-05,4.59242909361236e-05,5.9001314254275e-05,9.57302799362795e-05,9.75682634830955e-05,0.000146622191268649,0.000120710441302285,0.000156881911666433,8.2855312431108e-05,5.94692960024739e-05,5.97705408935098e-05,8.33832e-05,0.000119276587496832,3.54690111683049e-05,0.000137627305257363
"13",0.000135912535056286,9.20407740629099e-05,0.000111074226614142,7.09847357466453e-05,9.27685617651796e-05,9.58571090028464e-05,6.46521244284011e-05,9.77892831094819e-05,6.86807290459388e-05,8.23235226235331e-05,0.000178704925405586,6.06815447700852e-05,7.28607403561979e-05,0.000119589330239956,9.51606356135705e-05,0.000117442398173771,7.09742097465333e-05,5.94717e-05,9.4866394024603e-05,9.50086324249617e-05,8.12008444887827e-05 12,0.000135912535056286,9.20407740629099e-05,0.000111074226614142,7.09847357466453e-05,9.27685617651796e-05,9.58571090028464e-05,6.46521244284011e-05,9.77892831094819e-05,6.86807290459388e-05,8.23235226235331e-05,0.000178704925405586,6.06815447700852e-05,7.28607403561979e-05,0.000119589330239956,9.51606356135705e-05,0.000117442398173771,7.09742097465333e-05,5.94717e-05,9.4866394024603e-05,9.50086324249617e-05,8.12008444887827e-05
"14",0.000114974065509087,0.000218333801191479,0.000132109793400608,0.000120508243517033,0.000191739073395699,9.24729580814944e-05,0.000106163874556766,0.000118215695282925,8.66825765312342e-05,9.12240991263867e-05,8.19844932187112e-05,0.000154096218271366,9.6473879697072e-05,0.000108294778386769,7.06913615156228e-05,0.000106266004472028,0.000116746905842161,0.000129491,0.000106593235770913,5.90457323958839e-05,0.000116446800551376 13,0.000114974065509087,0.000218333801191479,0.000132109793400608,0.000120508243517033,0.000191739073395699,9.24729580814944e-05,0.000106163874556766,0.000118215695282925,8.66825765312342e-05,9.12240991263867e-05,8.19844932187112e-05,0.000154096218271366,9.6473879697072e-05,0.000108294778386769,7.06913615156228e-05,0.000106266004472028,0.000116746905842161,0.000129491,0.000106593235770913,5.90457323958839e-05,0.000116446800551376
"15",0.000157586613542468,0.000207743374609345,0.000175463720940434,0.000171698527685125,9.99653869847565e-05,0.000161010542416844,0.00013321617141847,0.000264737611934372,0.000171551644416329,8.64278556978914e-05,0.000181680115253323,0.00012820998464394,0.000129512517826368,9.54170021170647e-05,7.09166419197135e-05,0.000116879094420776,0.000105694744769211,9.2965e-05,7.03215305481124e-05,0.000117902803876055,8.10531114986865e-05 14,0.000157586613542468,0.000207743374609345,0.000175463720940434,0.000171698527685125,9.99653869847565e-05,0.000161010542416844,0.00013321617141847,0.000264737611934372,0.000171551644416329,8.64278556978914e-05,0.000181680115253323,0.00012820998464394,0.000129512517826368,9.54170021170647e-05,7.09166419197135e-05,0.000116879094420776,0.000105694744769211,9.2965e-05,7.03215305481124e-05,0.000117902803876055,8.10531114986865e-05
"16",0.000276768356860861,0.000229553140899979,0.000278368092830604,0.000266498909020091,0.00019092119476474,0.00024898166499019,0.000311171951361816,0.000265999961634621,0.000296072675267754,0.000128505798824172,0.000204538328733464,0.000158195665438767,0.000138899137523168,0.000151071006278162,0.000175081266888047,0.0001523412208977,0.000174315991313253,0.000198634,0.000208252888424176,0.000326633458931675,0.00024283422228004 15,0.000276768356860861,0.000229553140899979,0.000278368092830604,0.000266498909020091,0.00019092119476474,0.00024898166499019,0.000311171951361816,0.000265999961634621,0.000296072675267754,0.000128505798824172,0.000204538328733464,0.000158195665438767,0.000138899137523168,0.000151071006278162,0.000175081266888047,0.0001523412208977,0.000174315991313253,0.000198634,0.000208252888424176,0.000326633458931675,0.00024283422228004
"17",0.000413100584696212,0.000485625229286368,0.000372306113188815,0.00041958220869098,0.000427940979806535,0.000299994375105467,0.000376895324762271,0.000300046882325363,0.000275136103206609,0.000337175287685595,0.000223669863281796,0.00024640635085586,0.000292074939689333,0.000422230432258405,0.00022667962518524,0.00024342781133765,0.000222020002249413,0.000243404,0.00019795812021298,0.000172898455296384,0.000263195913597359 16,0.000413100584696212,0.000485625229286368,0.000372306113188815,0.00041958220869098,0.000427940979806535,0.000299994375105467,0.000376895324762271,0.000300046882325363,0.000275136103206609,0.000337175287685595,0.000223669863281796,0.00024640635085586,0.000292074939689333,0.000422230432258405,0.00022667962518524,0.00024342781133765,0.000222020002249413,0.000243404,0.00019795812021298,0.000172898455296384,0.000263195913597359
"18",0.000551319526073253,0.000649687468890973,0.000584496237305472,0.000532840797160574,0.000497870081310313,0.000425763777132937,0.000288329491011452,0.000365071984548575,0.000358604579928354,0.000385840663036718,0.000282806540686827,0.000253930298778093,0.000329787234042553,0.000231871576271257,0.000243715666901612,0.000235901713236192,0.000322926172445459,0.000221064,0.000334361398553022,0.0003124773960217,0.000383271333558787 17,0.000551319526073253,0.000649687468890973,0.000584496237305472,0.000532840797160574,0.000497870081310313,0.000425763777132937,0.000288329491011452,0.000365071984548575,0.000358604579928354,0.000385840663036718,0.000282806540686827,0.000253930298778093,0.000329787234042553,0.000231871576271257,0.000243715666901612,0.000235901713236192,0.000322926172445459,0.000221064,0.000334361398553022,0.0003124773960217,0.000383271333558787
"19",0.000649775930443034,0.000659372359934887,0.000880458356261936,0.000628793052352176,0.000710929654780177,0.000484300589232384,0.000634000543429037,0.000542793734679955,0.000333364790550089,0.000425771029251955,0.0004324405865604,0.000321011081354304,0.000229798012769458,0.000290890579690383,0.000403567322729071,0.000348976381387563,0.000388983973860277,0.000399286,0.000299008671251466,0.000340874712919578,0.000325417642685818 18,0.000649775930443034,0.000659372359934887,0.000880458356261936,0.000628793052352176,0.000710929654780177,0.000484300589232384,0.000634000543429037,0.000542793734679955,0.000333364790550089,0.000425771029251955,0.0004324405865604,0.000321011081354304,0.000229798012769458,0.000290890579690383,0.000403567322729071,0.000348976381387563,0.000388983973860277,0.000399286,0.000299008671251466,0.000340874712919578,0.000325417642685818
"20",0.000674796113375819,0.000598784923306054,0.000748377146685713,0.000600012712133732,0.000640802325197009,0.000792906000491802,0.000547591964336829,0.000545357643063423,0.000544837181245926,0.000464035440706784,0.000428012961983451,0.000314319847456649,0.000544362384055223,0.000271825649015198,0.000425901760311404,0.000392775007106127,0.000245352307245094,0.000260627,0.00035701983273063,0.000347642757816355,0.000348911219812706 19,0.000674796113375819,0.000598784923306054,0.000748377146685713,0.000600012712133732,0.000640802325197009,0.000792906000491802,0.000547591964336829,0.000545357643063423,0.000544837181245926,0.000464035440706784,0.000428012961983451,0.000314319847456649,0.000544362384055223,0.000271825649015198,0.000425901760311404,0.000392775007106127,0.000245352307245094,0.000260627,0.00035701983273063,0.000347642757816355,0.000348911219812706
"21",0.000599521856748675,0.000592933712481502,0.000576056175409105,0.000791822453610339,0.000669763071313523,0.000591011368203839,0.000502807960633094,0.000586306804579056,0.000643977831551011,0.000565142896141822,0.000351241508202557,0.00039867535367606,0.000382814042097582,0.000496188590581173,0.000491642084562438,0.000309011549306655,0.000273274857574458,0.000334055,0.000382362976642667,0.000445743018278182,0.000397250383158731 20,0.000599521856748675,0.000592933712481502,0.000576056175409105,0.000791822453610339,0.000669763071313523,0.000591011368203839,0.000502807960633094,0.000586306804579056,0.000643977831551011,0.000565142896141822,0.000351241508202557,0.00039867535367606,0.000382814042097582,0.000496188590581173,0.000491642084562438,0.000309011549306655,0.000273274857574458,0.000334055,0.000382362976642667,0.000445743018278182,0.000397250383158731
"22",0.000634450147336177,0.000868614776585041,0.000629105822858318,0.000554185620584593,0.00050632726511466,0.000650077381370112,0.000709098496982023,0.000514103283834725,0.000693707614284114,0.000576330813887171,0.000460645914881566,0.000287134410164558,0.000324244828005489,0.000417757962640834,0.000374405631060691,0.0003307675224095,0.000474987739378977,0.000438288,0.000349552842237292,0.000385457822319571,0.000334309272642271 21,0.000634450147336177,0.000868614776585041,0.000629105822858318,0.000554185620584593,0.00050632726511466,0.000650077381370112,0.000709098496982023,0.000514103283834725,0.000693707614284114,0.000576330813887171,0.000460645914881566,0.000287134410164558,0.000324244828005489,0.000417757962640834,0.000374405631060691,0.0003307675224095,0.000474987739378977,0.000438288,0.000349552842237292,0.000385457822319571,0.000334309272642271
"23",0.000673377128745822,0.000670076124046628,0.000604853476608001,0.000634446415910401,0.000602885236488911,0.000528067381397866,0.000484738610763378,0.000436756982348952,0.000660732048017983,0.000560611351429678,0.000433945377125654,0.00044116177195383,0.000325924215829732,0.000342196677540416,0.00038619054461848,0.000295005306638426,0.000382470268183954,0.000384753,0.000246056634855645,0.000343891128114617,0.000422082449284156 22,0.000673377128745822,0.000670076124046628,0.000604853476608001,0.000634446415910401,0.000602885236488911,0.000528067381397866,0.000484738610763378,0.000436756982348952,0.000660732048017983,0.000560611351429678,0.000433945377125654,0.00044116177195383,0.000325924215829732,0.000342196677540416,0.00038619054461848,0.000295005306638426,0.000382470268183954,0.000384753,0.000246056634855645,0.000343891128114617,0.000422082449284156
"24",0.00063205381938272,0.000617815364359143,0.000559827402365271,0.000536300244918151,0.000512716535341318,0.00056647729016147,0.000501218172941548,0.000592993589452366,0.000527646898695393,0.000396511173708477,0.000428577750758746,0.000460077891186978,0.000403323384689844,0.000429757176232236,0.00026947968688199,0.000291402950675635,0.000372805222910245,0.000229706,0.000332439901099129,0.000395600631513691,0.000458404654270234 23,0.00063205381938272,0.000617815364359143,0.000559827402365271,0.000536300244918151,0.000512716535341318,0.00056647729016147,0.000501218172941548,0.000592993589452366,0.000527646898695393,0.000396511173708477,0.000428577750758746,0.000460077891186978,0.000403323384689844,0.000429757176232236,0.00026947968688199,0.000291402950675635,0.000372805222910245,0.000229706,0.000332439901099129,0.000395600631513691,0.000458404654270234
"25",0.000580903331084533,0.000567038807362741,0.000841550829670112,0.000491687124639207,0.000546239143497023,0.000552200172562554,0.000586237379611967,0.000438882670087461,0.000416210451139021,0.000482897384305835,0.000342625903444316,0.000436253085865741,0.000367556834035763,0.000416790582269468,0.000271363516871179,0.00035926261348582,0.000261136662608168,0.00038535,0.000325567935175807,0.000380405063463113,0.000335462979680029 24,0.000580903331084533,0.000567038807362741,0.000841550829670112,0.000491687124639207,0.000546239143497023,0.000552200172562554,0.000586237379611967,0.000438882670087461,0.000416210451139021,0.000482897384305835,0.000342625903444316,0.000436253085865741,0.000367556834035763,0.000416790582269468,0.000271363516871179,0.00035926261348582,0.000261136662608168,0.00038535,0.000325567935175807,0.000380405063463113,0.000335462979680029
"26",0.000697135112848746,0.000579076218322075,0.000574671359816105,0.000513406073932896,0.000484315709876614,0.000530617888792833,0.000508719197222938,0.000423322784773724,0.000480669239479583,0.000439302117179166,0.000492995166554464,0.000352731293370687,0.000390075244628154,0.000347593728105669,0.000361292924540192,0.000375604880359412,0.000337883497769969,0.000455747,0.000238429544069727,0.000337814937420894,0.000377636871410254 25,0.000697135112848746,0.000579076218322075,0.000574671359816105,0.000513406073932896,0.000484315709876614,0.000530617888792833,0.000508719197222938,0.000423322784773724,0.000480669239479583,0.000439302117179166,0.000492995166554464,0.000352731293370687,0.000390075244628154,0.000347593728105669,0.000361292924540192,0.000375604880359412,0.000337883497769969,0.000455747,0.000238429544069727,0.000337814937420894,0.000377636871410254
"27",0.000550344653339154,0.000654048136409914,0.000588318828231189,0.000553320043771568,0.00045814477613543,0.00043372285561321,0.000587224529970138,0.000522377809750902,0.000475067520113285,0.000512358358074447,0.000580188630374947,0.000501050497918932,0.000291712384848194,0.000362063113203989,0.000420822286748306,0.0004723631312289,0.00038000433700602,0.000326213,0.00037373492850196,0.000460850029183546,0.000233454203526672 26,0.000550344653339154,0.000654048136409914,0.000588318828231189,0.000553320043771568,0.00045814477613543,0.00043372285561321,0.000587224529970138,0.000522377809750902,0.000475067520113285,0.000512358358074447,0.000580188630374947,0.000501050497918932,0.000291712384848194,0.000362063113203989,0.000420822286748306,0.0004723631312289,0.00038000433700602,0.000326213,0.00037373492850196,0.000460850029183546,0.000233454203526672
"28",0.000674180775402847,0.000472565365389017,0.000622454806141721,0.000627212042471215,0.000517070017865745,0.000463096413838077,0.000474399224849568,0.000371112431603758,0.000528024450216915,0.000507086189937735,0.00049661455599837,0.000307769946491027,0.000374665895033335,0.000353612507533132,0.000276617636889057,0.000266053358248122,0.000476904560502641,0.000450409,0.000314844178023669,0.000386077297291059,0.000475772253769274 27,0.000674180775402847,0.000472565365389017,0.000622454806141721,0.000627212042471215,0.000517070017865745,0.000463096413838077,0.000474399224849568,0.000371112431603758,0.000528024450216915,0.000507086189937735,0.00049661455599837,0.000307769946491027,0.000374665895033335,0.000353612507533132,0.000276617636889057,0.000266053358248122,0.000476904560502641,0.000450409,0.000314844178023669,0.000386077297291059,0.000475772253769274
"29",0.000651211252930451,0.000534520531566602,0.000591543832428239,0.00055225122499923,0.000511641064115021,0.000406603433378754,0.000403152559256981,0.000543266501163347,0.000430892342867193,0.00051561169994066,0.000402780978892039,0.000408963411110469,0.00041711549107029,0.000444187512451948,0.000487496349030576,0.00054737998849258,0.00032179047520821,0.000408157,0.000381856921461375,0.000303562656460398,0.000518047372554179 28,0.000651211252930451,0.000534520531566602,0.000591543832428239,0.00055225122499923,0.000511641064115021,0.000406603433378754,0.000403152559256981,0.000543266501163347,0.000430892342867193,0.00051561169994066,0.000402780978892039,0.000408963411110469,0.00041711549107029,0.000444187512451948,0.000487496349030576,0.00054737998849258,0.00032179047520821,0.000408157,0.000381856921461375,0.000303562656460398,0.000518047372554179
"30",0.000570958932217584,0.000469245446421486,0.000517958595684757,0.000524941898476237,0.000507191512345115,0.000488133475217463,0.000365295486798293,0.000606514431544349,0.000470550110812332,0.00044575841205121,0.000598730559141702,0.000494669603767439,0.000602864260524732,0.000399414770531873,0.000356700393962846,0.00037451586022652,0.000477674876360447,0.00036038,0.000324088374848717,0.000443099034648331,0.000484134020400197 29,0.000570958932217584,0.000469245446421486,0.000517958595684757,0.000524941898476237,0.000507191512345115,0.000488133475217463,0.000365295486798293,0.000606514431544349,0.000470550110812332,0.00044575841205121,0.000598730559141702,0.000494669603767439,0.000602864260524732,0.000399414770531873,0.000356700393962846,0.00037451586022652,0.000477674876360447,0.00036038,0.000324088374848717,0.000443099034648331,0.000484134020400197
"31",0.000587742010644428,0.000512529354456023,0.000490655957040345,0.000647556159535949,0.000538919820312786,0.000591126799121062,0.000485290246030022,0.000555276321773055,0.000465386852821408,0.000450308262494399,0.000493903647630075,0.000391562694081856,0.000417177727489514,0.000411166599566562,0.000407707800915431,0.000370277255614381,0.000404961606127317,0.000449802,0.000495760637011782,0.000490310834965191,0.000451423021980143 30,0.000587742010644428,0.000512529354456023,0.000490655957040345,0.000647556159535949,0.000538919820312786,0.000591126799121062,0.000485290246030022,0.000555276321773055,0.000465386852821408,0.000450308262494399,0.000493903647630075,0.000391562694081856,0.000417177727489514,0.000411166599566562,0.000407707800915431,0.000370277255614381,0.000404961606127317,0.000449802,0.000495760637011782,0.000490310834965191,0.000451423021980143
"32",0.000509921720945338,0.000708124584106977,0.00063835461910779,0.00054803320092941,0.000506735166402554,0.000441927131387522,0.000539887178041053,0.0004938965044717,0.000496584193104403,0.000518438712559294,0.000534127227354319,0.000419849903659442,0.000523355826194388,0.000452371375561063,0.000570450057831472,0.000387371275367292,0.000476486538732817,0.000525328,0.000479209223559225,0.000556752438817748,0.000379684505905874 31,0.000509921720945338,0.000708124584106977,0.00063835461910779,0.00054803320092941,0.000506735166402554,0.000441927131387522,0.000539887178041053,0.0004938965044717,0.000496584193104403,0.000518438712559294,0.000534127227354319,0.000419849903659442,0.000523355826194388,0.000452371375561063,0.000570450057831472,0.000387371275367292,0.000476486538732817,0.000525328,0.000479209223559225,0.000556752438817748,0.000379684505905874
"33",0.000599526143759452,0.000635417912953778,0.000652432219828365,0.000528596187175043,0.000571285112555441,0.000585768968213022,0.000449577116524769,0.000538734790963686,0.000570002874167035,0.000542092405356729,0.000459342978770316,0.000511150554414251,0.000549898533145663,0.000497849858186624,0.000495209997366574,0.00042493271898616,0.000443790853093714,0.000531808,0.000522144217864675,0.000435994142337958,0.000524209441528309 32,0.000599526143759452,0.000635417912953778,0.000652432219828365,0.000528596187175043,0.000571285112555441,0.000585768968213022,0.000449577116524769,0.000538734790963686,0.000570002874167035,0.000542092405356729,0.000459342978770316,0.000511150554414251,0.000549898533145663,0.000497849858186624,0.000495209997366574,0.00042493271898616,0.000443790853093714,0.000531808,0.000522144217864675,0.000435994142337958,0.000524209441528309
"34",0.000750815053477349,0.000810571070259689,0.00051926420262488,0.000622950819672131,0.00067214145992572,0.000613453979282592,0.000547799429076251,0.00061691395802882,0.00052841871899293,0.000567952782908472,0.000434426916525104,0.000591331086275205,0.000573630750889074,0.000499955733086133,0.000556481871772457,0.00049180857393227,0.000521894726378051,0.000615753,0.000545812594005365,0.000502926301017615,0.000452871113476987 33,0.000750815053477349,0.000810571070259689,0.00051926420262488,0.000622950819672131,0.00067214145992572,0.000613453979282592,0.000547799429076251,0.00061691395802882,0.00052841871899293,0.000567952782908472,0.000434426916525104,0.000591331086275205,0.000573630750889074,0.000499955733086133,0.000556481871772457,0.00049180857393227,0.000521894726378051,0.000615753,0.000545812594005365,0.000502926301017615,0.000452871113476987
"35",0.000792070729775437,0.000697183578058689,0.000684368361270454,0.000737569865909005,0.000701672080488315,0.000687195191351649,0.000629642644543448,0.000547454672323698,0.000737660239762922,0.000699107321353539,0.000573541114533771,0.000505221794706866,0.000629201464691124,0.000523365748244192,0.000541980940336932,0.000618953597048829,0.000680076052407324,0.000527597,0.000571299644593663,0.000665601840676695,0.000654037886340977 34,0.000792070729775437,0.000697183578058689,0.000684368361270454,0.000737569865909005,0.000701672080488315,0.000687195191351649,0.000629642644543448,0.000547454672323698,0.000737660239762922,0.000699107321353539,0.000573541114533771,0.000505221794706866,0.000629201464691124,0.000523365748244192,0.000541980940336932,0.000618953597048829,0.000680076052407324,0.000527597,0.000571299644593663,0.000665601840676695,0.000654037886340977
"36",0.000872188621513033,0.000754314849950943,0.000860494187596772,0.000710611834899924,0.000584233780357705,0.000708333502953425,0.000497707755445287,0.00053225522081384,0.000717710861208176,0.000568274448610755,0.000666810348420314,0.000616070677523728,0.000674725632757467,0.000841940140271659,0.000566025171472331,0.000522015387219187,0.000730595106654572,0.000561623,0.00058226192355557,0.000600917015829636,0.00056675974346025 35,0.000872188621513033,0.000754314849950943,0.000860494187596772,0.000710611834899924,0.000584233780357705,0.000708333502953425,0.000497707755445287,0.00053225522081384,0.000717710861208176,0.000568274448610755,0.000666810348420314,0.000616070677523728,0.000674725632757467,0.000841940140271659,0.000566025171472331,0.000522015387219187,0.000730595106654572,0.000561623,0.00058226192355557,0.000600917015829636,0.00056675974346025
"37",0.00071088552343834,0.000976768766927465,0.000822050075959907,0.000841859862712084,0.000798615231325306,0.000717334668153888,0.000634301693809155,0.000746886096650924,0.000691999312436581,0.000581941244078468,0.000769737269194743,0.000604958533164607,0.000553158275927536,0.000601926163723917,0.000690775307843142,0.000728068488078913,0.000576460128851018,0.000629292,0.000583173593735401,0.000741631936627144,0.00077787118534199 36,0.00071088552343834,0.000976768766927465,0.000822050075959907,0.000841859862712084,0.000798615231325306,0.000717334668153888,0.000634301693809155,0.000746886096650924,0.000691999312436581,0.000581941244078468,0.000769737269194743,0.000604958533164607,0.000553158275927536,0.000601926163723917,0.000690775307843142,0.000728068488078913,0.000576460128851018,0.000629292,0.000583173593735401,0.000741631936627144,0.00077787118534199
"38",0.000884912588752552,0.00080145325461833,0.000846310238487025,0.00100948510082938,0.000832589415886488,0.000790050629077813,0.000827353080806787,0.000756678142273798,0.000858646408335739,0.000646416704116036,0.000632967111340921,0.000792427708248389,0.000551899610396292,0.000786990582731807,0.000657300879477581,0.000712664681489947,0.000634251865946338,0.000598215,0.000708294577272292,0.000727396065114207,0.000738525017033237 37,0.000884912588752552,0.00080145325461833,0.000846310238487025,0.00100948510082938,0.000832589415886488,0.000790050629077813,0.000827353080806787,0.000756678142273798,0.000858646408335739,0.000646416704116036,0.000632967111340921,0.000792427708248389,0.000551899610396292,0.000786990582731807,0.000657300879477581,0.000712664681489947,0.000634251865946338,0.000598215,0.000708294577272292,0.000727396065114207,0.000738525017033237
"39",0.00121566319143027,0.00106434597505048,0.00100443418789816,0.000836405617739596,0.000803060788707838,0.000746148858490896,0.000797604177639995,0.000977642344528258,0.000928281122609447,0.000771923429484259,0.000741024996361038,0.000797372215565149,0.000629707836098002,0.000739468068266768,0.000677057362312608,0.000671121421524654,0.000536288107811209,0.000656025,0.000651886547596772,0.00089160964924279,0.00079774616563104 38,0.00121566319143027,0.00106434597505048,0.00100443418789816,0.000836405617739596,0.000803060788707838,0.000746148858490896,0.000797604177639995,0.000977642344528258,0.000928281122609447,0.000771923429484259,0.000741024996361038,0.000797372215565149,0.000629707836098002,0.000739468068266768,0.000677057362312608,0.000671121421524654,0.000536288107811209,0.000656025,0.000651886547596772,0.00089160964924279,0.00079774616563104
"40",0.00124273317044401,0.00112385531235412,0.000985587517742311,0.00117762892877196,0.00118093705941369,0.000992459769305894,0.000968659384381085,0.000889049621023763,0.000884051164461143,0.000952356726782489,0.000803964227868265,0.00077246173900449,0.000878673817607086,0.000785486555878453,0.000685678238629741,0.000727908820321394,0.000926222792205479,0.000835694,0.000783909442127987,0.000745282631408654,0.000792006336050688 39,0.00124273317044401,0.00112385531235412,0.000985587517742311,0.00117762892877196,0.00118093705941369,0.000992459769305894,0.000968659384381085,0.000889049621023763,0.000884051164461143,0.000952356726782489,0.000803964227868265,0.00077246173900449,0.000878673817607086,0.000785486555878453,0.000685678238629741,0.000727908820321394,0.000926222792205479,0.000835694,0.000783909442127987,0.000745282631408654,0.000792006336050688
"41",0.00150303483588873,0.00118604398187949,0.00114986985563907,0.00098968187437442,0.000922199128134641,0.00106858587520545,0.00104207005808836,0.000955024966183679,0.00082231335985734,0.000797134262862916,0.000909407393197917,0.000792044635547687,0.000958346764708445,0.000869845080591147,0.000866734054494787,0.000863735496914987,0.00100447602661861,0.000895703,0.000763147684082583,0.000797084946481439,0.000949352067214126 40,0.00150303483588873,0.00118604398187949,0.00114986985563907,0.00098968187437442,0.000922199128134641,0.00106858587520545,0.00104207005808836,0.000955024966183679,0.00082231335985734,0.000797134262862916,0.000909407393197917,0.000792044635547687,0.000958346764708445,0.000869845080591147,0.000866734054494787,0.000863735496914987,0.00100447602661861,0.000895703,0.000763147684082583,0.000797084946481439,0.000949352067214126
"42",0.00150348522461116,0.00123004547931312,0.00119127391854665,0.00116824460816867,0.0011603161516181,0.00111283769209436,0.00110476500727658,0.00114179388505942,0.00114972469482893,0.00107082226141448,0.000937095496133989,0.000962297546040176,0.00114171059962006,0.00095849128291036,0.000990904146179903,0.000827051705182746,0.00114019926339508,0.001090212,0.000997433594534417,0.00108490445152527,0.000915725169991526 41,0.00150348522461116,0.00123004547931312,0.00119127391854665,0.00116824460816867,0.0011603161516181,0.00111283769209436,0.00110476500727658,0.00114179388505942,0.00114972469482893,0.00107082226141448,0.000937095496133989,0.000962297546040176,0.00114171059962006,0.00095849128291036,0.000990904146179903,0.000827051705182746,0.00114019926339508,0.001090212,0.000997433594534417,0.00108490445152527,0.000915725169991526
"43",0.0015279747999332,0.00154142005192939,0.00132179753689494,0.00141247135287835,0.00120111780327357,0.0012579724870358,0.00109269393114266,0.00141801104453352,0.00115056928474119,0.00111402594602365,0.00112210307721707,0.0011537374815559,0.00114906854133583,0.00117486871891056,0.000865866740108169,0.00106354350825694,0.00115987710615089,0.000919457,0.00117475487640973,0.000905789135806812,0.00103854873368824 42,0.0015279747999332,0.00154142005192939,0.00132179753689494,0.00141247135287835,0.00120111780327357,0.0012579724870358,0.00109269393114266,0.00141801104453352,0.00115056928474119,0.00111402594602365,0.00112210307721707,0.0011537374815559,0.00114906854133583,0.00117486871891056,0.000865866740108169,0.00106354350825694,0.00115987710615089,0.000919457,0.00117475487640973,0.000905789135806812,0.00103854873368824
"44",0.001726078874213,0.00175918386160063,0.00144236787480546,0.00147706780529952,0.00147373898406301,0.00145197371163385,0.00140406573863455,0.00137634469317659,0.00142722357972171,0.00127741975324979,0.00129197111726791,0.00107364712484996,0.00121832763055777,0.00127765422683952,0.00101707137631849,0.00116980036545588,0.00106803945337741,0.001014247,0.00121169419531164,0.00111711997533399,0.00116464899195936 43,0.001726078874213,0.00175918386160063,0.00144236787480546,0.00147706780529952,0.00147373898406301,0.00145197371163385,0.00140406573863455,0.00137634469317659,0.00142722357972171,0.00127741975324979,0.00129197111726791,0.00107364712484996,0.00121832763055777,0.00127765422683952,0.00101707137631849,0.00116980036545588,0.00106803945337741,0.001014247,0.00121169419531164,0.00111711997533399,0.00116464899195936
"45",0.00209397970529709,0.00191196558461948,0.00173424765018076,0.00173065876929274,0.00181249132484698,0.00155206496300737,0.0012930438931049,0.00143364459119486,0.00135738209068656,0.00147700260783273,0.00130435663930749,0.00125339648064174,0.00128613516383268,0.00132030246576194,0.00143667326795544,0.0011629379967147,0.00121652819442332,0.001097335,0.00129089905191368,0.00139504624444161,0.00114052557009701 44,0.00209397970529709,0.00191196558461948,0.00173424765018076,0.00173065876929274,0.00181249132484698,0.00155206496300737,0.0012930438931049,0.00143364459119486,0.00135738209068656,0.00147700260783273,0.00130435663930749,0.00125339648064174,0.00128613516383268,0.00132030246576194,0.00143667326795544,0.0011629379967147,0.00121652819442332,0.001097335,0.00129089905191368,0.00139504624444161,0.00114052557009701
"46",0.00206858494284588,0.00210485478565562,0.00192707885630669,0.00194684499971257,0.00179719477284782,0.00182922728597368,0.00157513388638034,0.0016985743983418,0.00173365810528506,0.00161951766308552,0.00165376217586838,0.00155524141868278,0.00148446839259907,0.00134697549118559,0.00132119405810357,0.00126657556558041,0.00144044057613484,0.001584232,0.00100847137138335,0.00142751111685229,0.00144393778665598 45,0.00206858494284588,0.00210485478565562,0.00192707885630669,0.00194684499971257,0.00179719477284782,0.00182922728597368,0.00157513388638034,0.0016985743983418,0.00173365810528506,0.00161951766308552,0.00165376217586838,0.00155524141868278,0.00148446839259907,0.00134697549118559,0.00132119405810357,0.00126657556558041,0.00144044057613484,0.001584232,0.00100847137138335,0.00142751111685229,0.00144393778665598
"47",0.00231683856055517,0.00245913115611798,0.00237777277821696,0.00222028546242137,0.00206950866415132,0.00197916831986348,0.00208969157301354,0.00206812545459325,0.00196686666631793,0.00192934971198556,0.00163324177280971,0.00158092819271727,0.00162092182034432,0.00166363473975047,0.0015400990328104,0.00135598835467956,0.00142131679078513,0.00162586,0.00146970165689857,0.00157196327437415,0.00148418657787586 46,0.00231683856055517,0.00245913115611798,0.00237777277821696,0.00222028546242137,0.00206950866415132,0.00197916831986348,0.00208969157301354,0.00206812545459325,0.00196686666631793,0.00192934971198556,0.00163324177280971,0.00158092819271727,0.00162092182034432,0.00166363473975047,0.0015400990328104,0.00135598835467956,0.00142131679078513,0.00162586,0.00146970165689857,0.00157196327437415,0.00148418657787586
"48",0.00284365237970633,0.00260033485855771,0.00240960810167535,0.00235256243576885,0.00195741621060201,0.00222619696469559,0.00209507526370825,0.00216669321045807,0.00224063861712561,0.00219949027685647,0.00195784387236524,0.00186476070228725,0.00176723406661766,0.00166446952027611,0.00159415053032074,0.00172147718257725,0.00159850294051533,0.001638158,0.0015641287648425,0.00176095833206071,0.00160101761014593 47,0.00284365237970633,0.00260033485855771,0.00240960810167535,0.00235256243576885,0.00195741621060201,0.00222619696469559,0.00209507526370825,0.00216669321045807,0.00224063861712561,0.00219949027685647,0.00195784387236524,0.00186476070228725,0.00176723406661766,0.00166446952027611,0.00159415053032074,0.00172147718257725,0.00159850294051533,0.001638158,0.0015641287648425,0.00176095833206071,0.00160101761014593
"49",0.00293070662325236,0.00294335435618766,0.00277687422637201,0.002544263980025,0.00230263090023377,0.00247338262088507,0.00236863633261268,0.00265381490578114,0.00223539422258758,0.00225789405658627,0.00203330852836675,0.00221409961539563,0.00209398613527362,0.00199571063253625,0.0019795544782628,0.00181744089118249,0.00188957256724452,0.001926076,0.00181439201667513,0.00182364453717832,0.00159805054566942 48,0.00293070662325236,0.00294335435618766,0.00277687422637201,0.002544263980025,0.00230263090023377,0.00247338262088507,0.00236863633261268,0.00265381490578114,0.00223539422258758,0.00225789405658627,0.00203330852836675,0.00221409961539563,0.00209398613527362,0.00199571063253625,0.0019795544782628,0.00181744089118249,0.00188957256724452,0.001926076,0.00181439201667513,0.00182364453717832,0.00159805054566942
"50",0.00302376443994305,0.00315220255318737,0.00293831855650452,0.00277834507176845,0.00278165875369044,0.00287777220737739,0.00265697792842013,0.00281436017641797,0.00281032116748556,0.00233245625516205,0.00260440954692073,0.00269662528872142,0.00228838505892592,0.00226664191193357,0.00220847590545754,0.00202517374477069,0.00205444817151465,0.001835321,0.00190730424758188,0.0020624579715373,0.00194445437323516 49,0.00302376443994305,0.00315220255318737,0.00293831855650452,0.00277834507176845,0.00278165875369044,0.00287777220737739,0.00265697792842013,0.00281436017641797,0.00281032116748556,0.00233245625516205,0.00260440954692073,0.00269662528872142,0.00228838505892592,0.00226664191193357,0.00220847590545754,0.00202517374477069,0.00205444817151465,0.001835321,0.00190730424758188,0.0020624579715373,0.00194445437323516
"51",0.00345248864793046,0.00351223149333608,0.00322483803178354,0.00326527954304692,0.00272761248669524,0.00294085335451649,0.00296804173497792,0.00300246516073854,0.00296938976720448,0.00287762738868497,0.00292155815229526,0.00270514452974338,0.00256245325224717,0.00235445038731574,0.00232493412832969,0.00203785849180904,0.00218296401672331,0.002130115,0.00228962463223825,0.00233435636820071,0.00210734791240847 50,0.00345248864793046,0.00351223149333608,0.00322483803178354,0.00326527954304692,0.00272761248669524,0.00294085335451649,0.00296804173497792,0.00300246516073854,0.00296938976720448,0.00287762738868497,0.00292155815229526,0.00270514452974338,0.00256245325224717,0.00235445038731574,0.00232493412832969,0.00203785849180904,0.00218296401672331,0.002130115,0.00228962463223825,0.00233435636820071,0.00210734791240847
"52",0.00406411882226701,0.00367608537304313,0.00352990339470515,0.00373081898744604,0.00368885959743922,0.00327908737913023,0.00344961297800342,0.00330203195568457,0.00309228513210335,0.00329534319545553,0.0029873433955005,0.00275018794458733,0.00266856305976455,0.00272174833947181,0.0023368988902323,0.0026125567765825,0.00238130151474308,0.002237098,0.00236728288237827,0.00250913793452327,0.00230980772565888 51,0.00406411882226701,0.00367608537304313,0.00352990339470515,0.00373081898744604,0.00368885959743922,0.00327908737913023,0.00344961297800342,0.00330203195568457,0.00309228513210335,0.00329534319545553,0.0029873433955005,0.00275018794458733,0.00266856305976455,0.00272174833947181,0.0023368988902323,0.0026125567765825,0.00238130151474308,0.002237098,0.00236728288237827,0.00250913793452327,0.00230980772565888
"53",0.0044328945680854,0.00414219325061669,0.00389843315895861,0.00393967374576793,0.00379728241802398,0.00388937713868995,0.00343935443932915,0.00358866042832193,0.00377152643562591,0.00358706631821651,0.00294531067101987,0.00357283474789515,0.00298985314065793,0.00289366315930285,0.00270650625269212,0.00282879806341453,0.002670266842225,0.002739906,0.00263160178796164,0.00298751181309027,0.002551541785621 52,0.0044328945680854,0.00414219325061669,0.00389843315895861,0.00393967374576793,0.00379728241802398,0.00388937713868995,0.00343935443932915,0.00358866042832193,0.00377152643562591,0.00358706631821651,0.00294531067101987,0.00357283474789515,0.00298985314065793,0.00289366315930285,0.00270650625269212,0.00282879806341453,0.002670266842225,0.002739906,0.00263160178796164,0.00298751181309027,0.002551541785621
"54",0.00489924609501619,0.00451507381419871,0.00438970919452665,0.00408975126599621,0.00375128950576761,0.00430930998636279,0.00387460538598293,0.00447586772354234,0.00410431443656338,0.00360878206745115,0.00404297897732116,0.00344700138113486,0.0036679346880743,0.00332411777805539,0.00318126152503484,0.00335742336951638,0.00315026322872555,0.002812959,0.00300161503759927,0.0031183072939048,0.00292560626332918 53,0.00489924609501619,0.00451507381419871,0.00438970919452665,0.00408975126599621,0.00375128950576761,0.00430930998636279,0.00387460538598293,0.00447586772354234,0.00410431443656338,0.00360878206745115,0.00404297897732116,0.00344700138113486,0.0036679346880743,0.00332411777805539,0.00318126152503484,0.00335742336951638,0.00315026322872555,0.002812959,0.00300161503759927,0.0031183072939048,0.00292560626332918
"55",0.005270852752057,0.00522355844096501,0.00535553250119947,0.00496681323886147,0.00456835877386878,0.00441090832496995,0.00477810687097643,0.00451343902381569,0.0043622822183801,0.00420582412417032,0.00414901167014517,0.00404316094648201,0.00382440080655133,0.00393871137861526,0.00367278193310031,0.00350242950215466,0.00353639966907406,0.003161959,0.00325109139384386,0.00346722531426125,0.003190445309872 54,0.005270852752057,0.00522355844096501,0.00535553250119947,0.00496681323886147,0.00456835877386878,0.00441090832496995,0.00477810687097643,0.00451343902381569,0.0043622822183801,0.00420582412417032,0.00414901167014517,0.00404316094648201,0.00382440080655133,0.00393871137861526,0.00367278193310031,0.00350242950215466,0.00353639966907406,0.003161959,0.00325109139384386,0.00346722531426125,0.003190445309872
"56",0.00552551469755238,0.00526506834234845,0.00557537750958419,0.00555696328597056,0.00477074218970897,0.00498068960050932,0.00422453292881438,0.0049011949123038,0.00415597202055739,0.00470921802722489,0.00431741608667514,0.00423642270739416,0.00440984675578741,0.00454133138258961,0.00366994737720083,0.00379560692970416,0.00391059283599157,0.003675821,0.00353359036905713,0.00367035169507197,0.00345801880824864 55,0.00552551469755238,0.00526506834234845,0.00557537750958419,0.00555696328597056,0.00477074218970897,0.00498068960050932,0.00422453292881438,0.0049011949123038,0.00415597202055739,0.00470921802722489,0.00431741608667514,0.00423642270739416,0.00440984675578741,0.00454133138258961,0.00366994737720083,0.00379560692970416,0.00391059283599157,0.003675821,0.00353359036905713,0.00367035169507197,0.00345801880824864
"57",0.00613136178338057,0.00594503054063235,0.00641901789504523,0.00603697403955577,0.00560254596709137,0.00542027846163394,0.00504978434284025,0.00510482405873551,0.00552687616559371,0.00498223178312079,0.00477149434222739,0.00493429388162655,0.00481251253258472,0.00436190764028148,0.00464395377155109,0.00453770255055747,0.00471319859258653,0.004062232,0.00467805496013221,0.00401231509537941,0.00424015699850415 56,0.00613136178338057,0.00594503054063235,0.00641901789504523,0.00603697403955577,0.00560254596709137,0.00542027846163394,0.00504978434284025,0.00510482405873551,0.00552687616559371,0.00498223178312079,0.00477149434222739,0.00493429388162655,0.00481251253258472,0.00436190764028148,0.00464395377155109,0.00453770255055747,0.00471319859258653,0.004062232,0.00467805496013221,0.00401231509537941,0.00424015699850415
"58",0.00649076726572019,0.00678629169078462,0.00627826483961921,0.00681949616042648,0.0060194975134207,0.00598392648027636,0.00602401804084159,0.00592833235907278,0.00538725963444674,0.00570834721469452,0.00532013328987444,0.00522251784584599,0.00483029059651492,0.00514575586223678,0.00532048776594765,0.00487819224547816,0.00497273385958891,0.004626437,0.00461876150145223,0.00441043415870705,0.00468450502514093 57,0.00649076726572019,0.00678629169078462,0.00627826483961921,0.00681949616042648,0.0060194975134207,0.00598392648027636,0.00602401804084159,0.00592833235907278,0.00538725963444674,0.00570834721469452,0.00532013328987444,0.00522251784584599,0.00483029059651492,0.00514575586223678,0.00532048776594765,0.00487819224547816,0.00497273385958891,0.004626437,0.00461876150145223,0.00441043415870705,0.00468450502514093
"59",0.00741433046171413,0.00794028196889365,0.00706100669589772,0.00697985844191787,0.0067949758800135,0.00657208851689624,0.00650078371415037,0.00653819052433878,0.00657168447582745,0.0060560488332232,0.00554029086527043,0.0059004125491701,0.00566840931953179,0.00549992397419467,0.00539267827154046,0.00539274671456566,0.00512694303068487,0.004639106,0.00482506397419799,0.00537271904059605,0.0047599516259354 58,0.00741433046171413,0.00794028196889365,0.00706100669589772,0.00697985844191787,0.0067949758800135,0.00657208851689624,0.00650078371415037,0.00653819052433878,0.00657168447582745,0.0060560488332232,0.00554029086527043,0.0059004125491701,0.00566840931953179,0.00549992397419467,0.00539267827154046,0.00539274671456566,0.00512694303068487,0.004639106,0.00482506397419799,0.00537271904059605,0.0047599516259354
"60",0.00762832962811893,0.00728170025596439,0.00740582581676852,0.00734847974111778,0.00757628761906666,0.00738702342964763,0.00723043418509664,0.00691351252750722,0.00664674401858978,0.00642577016865026,0.00682614720026082,0.00641550984700316,0.00627653638354362,0.0062015784601526,0.00611144228076236,0.00557990126390309,0.00614322000922721,0.005392338,0.00567501696649609,0.00577449707326301,0.00534676917017251 59,0.00762832962811893,0.00728170025596439,0.00740582581676852,0.00734847974111778,0.00757628761906666,0.00738702342964763,0.00723043418509664,0.00691351252750722,0.00664674401858978,0.00642577016865026,0.00682614720026082,0.00641550984700316,0.00627653638354362,0.0062015784601526,0.00611144228076236,0.00557990126390309,0.00614322000922721,0.005392338,0.00567501696649609,0.00577449707326301,0.00534676917017251
"61",0.00710684700290937,0.00880511197775837,0.0083870223817394,0.00893659886037316,0.00771419452536653,0.00765226070617058,0.00764806122386205,0.0077895425391412,0.00803004488221515,0.00679025136681703,0.00730236073609274,0.00696797961942927,0.00699525141711966,0.00697853615511735,0.00639630233674303,0.00644952110553204,0.00634466083929574,0.006059223,0.00633893020623368,0.0066637422813098,0.00617902057006982 60,0.00710684700290937,0.00880511197775837,0.0083870223817394,0.00893659886037316,0.00771419452536653,0.00765226070617058,0.00764806122386205,0.0077895425391412,0.00803004488221515,0.00679025136681703,0.00730236073609274,0.00696797961942927,0.00699525141711966,0.00697853615511735,0.00639630233674303,0.00644952110553204,0.00634466083929574,0.006059223,0.00633893020623368,0.0066637422813098,0.00617902057006982
"62",0.00860869575257389,0.00938393660120882,0.0085555734254872,0.00833845578213112,0.00872934925429231,0.0086877431223461,0.00805350701249971,0.00898316525053601,0.00853975694925239,0.00859038103386866,0.00872690281951239,0.00781741288836123,0.00770598466292128,0.00741905445219595,0.00714228294840845,0.00699246296694597,0.00682383227831361,0.006907971,0.00703631674276127,0.00769254579930484,0.00744765182421067 61,0.00860869575257389,0.00938393660120882,0.0085555734254872,0.00833845578213112,0.00872934925429231,0.0086877431223461,0.00805350701249971,0.00898316525053601,0.00853975694925239,0.00859038103386866,0.00872690281951239,0.00781741288836123,0.00770598466292128,0.00741905445219595,0.00714228294840845,0.00699246296694597,0.00682383227831361,0.006907971,0.00703631674276127,0.00769254579930484,0.00744765182421067
"63",0.00899045901625132,0.00913171732717712,0.00933812288668489,0.00909153904788303,0.00934983377923675,0.00925889070896036,0.00940575999059424,0.00936567551729842,0.00905390230207749,0.00880687668592959,0.00888506735454285,0.00876472495406895,0.00830464306263219,0.00805983437769279,0.00838484168229855,0.00791011324171112,0.00757815840148797,0.007387733,0.00778548683703748,0.00763366800690225,0.00787417359265184 62,0.00899045901625132,0.00913171732717712,0.00933812288668489,0.00909153904788303,0.00934983377923675,0.00925889070896036,0.00940575999059424,0.00936567551729842,0.00905390230207749,0.00880687668592959,0.00888506735454285,0.00876472495406895,0.00830464306263219,0.00805983437769279,0.00838484168229855,0.00791011324171112,0.00757815840148797,0.007387733,0.00778548683703748,0.00763366800690225,0.00787417359265184
"64",0.00964128358982136,0.0103501947228893,0.0101296210217879,0.00985925483083221,0.0094631137111681,0.00964197633308349,0.00985323812250014,0.010506938841093,0.0103280208425055,0.00975089895846122,0.00927270136741539,0.00932428413344444,0.00948630823141685,0.00919489250765001,0.00915293376718799,0.0089372891600498,0.00852842602555065,0.008233856,0.00827097502500852,0.00893840090520988,0.00881508274166805 63,0.00964128358982136,0.0103501947228893,0.0101296210217879,0.00985925483083221,0.0094631137111681,0.00964197633308349,0.00985323812250014,0.010506938841093,0.0103280208425055,0.00975089895846122,0.00927270136741539,0.00932428413344444,0.00948630823141685,0.00919489250765001,0.00915293376718799,0.0089372891600498,0.00852842602555065,0.008233856,0.00827097502500852,0.00893840090520988,0.00881508274166805
"65",0.0112298048909685,0.0106216629303692,0.0104581987256835,0.00994016656431114,0.00988144314078499,0.00961617234531212,0.0101319853355739,0.0106721215846161,0.0109880409721168,0.0110526439735092,0.0105675857465467,0.0106384219674082,0.00989666636471919,0.0105317603556808,0.00928436223195632,0.00887144477247735,0.00908133582175142,0.008434133,0.00963294861608276,0.0099370480790365,0.00938114758602499 64,0.0112298048909685,0.0106216629303692,0.0104581987256835,0.00994016656431114,0.00988144314078499,0.00961617234531212,0.0101319853355739,0.0106721215846161,0.0109880409721168,0.0110526439735092,0.0105675857465467,0.0106384219674082,0.00989666636471919,0.0105317603556808,0.00928436223195632,0.00887144477247735,0.00908133582175142,0.008434133,0.00963294861608276,0.0099370480790365,0.00938114758602499
"66",0.0123107308661134,0.0118756136777023,0.0114648074296341,0.0114227234436204,0.0109476138447497,0.011194275724934,0.0111075436831553,0.0114516812708031,0.0111023824916187,0.0116396354580429,0.0113802827338615,0.0113228179339993,0.0108462569279156,0.0117650271731709,0.010500641705882,0.01037740655721,0.0101864260261582,0.010220811,0.0100396879842205,0.0106209923014357,0.0104890460984495 65,0.0123107308661134,0.0118756136777023,0.0114648074296341,0.0114227234436204,0.0109476138447497,0.011194275724934,0.0111075436831553,0.0114516812708031,0.0111023824916187,0.0116396354580429,0.0113802827338615,0.0113228179339993,0.0108462569279156,0.0117650271731709,0.010500641705882,0.01037740655721,0.0101864260261582,0.010220811,0.0100396879842205,0.0106209923014357,0.0104890460984495
"67",0.0134965180433866,0.0127627232159654,0.0133998011759231,0.0123589132698839,0.0121412242250421,0.0124520189643375,0.011983380255157,0.0123361247473289,0.0122618811581853,0.0128628886464209,0.01265003849226,0.0120202963024465,0.0124734853484904,0.0115949401970292,0.0116443180091972,0.0106608251186564,0.0113479284323238,0.010889851,0.01154192583303,0.0118759134951134,0.0116456926661679 66,0.0134965180433866,0.0127627232159654,0.0133998011759231,0.0123589132698839,0.0121412242250421,0.0124520189643375,0.011983380255157,0.0123361247473289,0.0122618811581853,0.0128628886464209,0.01265003849226,0.0120202963024465,0.0124734853484904,0.0115949401970292,0.0116443180091972,0.0106608251186564,0.0113479284323238,0.010889851,0.01154192583303,0.0118759134951134,0.0116456926661679
"68",0.0147917072352502,0.0145821105706742,0.0139228827839666,0.0133119783955544,0.0127491740416707,0.0133148963837327,0.0125601358304431,0.0134295412810002,0.0125416971946435,0.0125558468858908,0.0131911105922867,0.0133023482380432,0.0136178886580389,0.0132436659864864,0.0128365127473703,0.0121203481245746,0.0126171132385913,0.01261028,0.0124463490027226,0.0135067560664799,0.0125386055037392 67,0.0147917072352502,0.0145821105706742,0.0139228827839666,0.0133119783955544,0.0127491740416707,0.0133148963837327,0.0125601358304431,0.0134295412810002,0.0125416971946435,0.0125558468858908,0.0131911105922867,0.0133023482380432,0.0136178886580389,0.0132436659864864,0.0128365127473703,0.0121203481245746,0.0126171132385913,0.01261028,0.0124463490027226,0.0135067560664799,0.0125386055037392
"69",0.0171136395325073,0.0158378269246978,0.0145995449441406,0.0143922983426055,0.0148981334543838,0.0135683587241642,0.0136493260645256,0.0139377685612594,0.0146116562876455,0.0137724639613612,0.014166955316938,0.0137238647876946,0.0142149472323929,0.0142382599636897,0.0142986245752917,0.0144841318349374,0.0134453591139882,0.01330534,0.0139704027039857,0.0140740074823487,0.0142353588383513 68,0.0171136395325073,0.0158378269246978,0.0145995449441406,0.0143922983426055,0.0148981334543838,0.0135683587241642,0.0136493260645256,0.0139377685612594,0.0146116562876455,0.0137724639613612,0.014166955316938,0.0137238647876946,0.0142149472323929,0.0142382599636897,0.0142986245752917,0.0144841318349374,0.0134453591139882,0.01330534,0.0139704027039857,0.0140740074823487,0.0142353588383513
"70",0.0167537526933093,0.0173955023983056,0.0163489692261727,0.0162410769894122,0.0159072235502209,0.0142806626741827,0.0144166849717331,0.0144748792287603,0.0150088116085674,0.0149392683302505,0.0149955731793291,0.0161056530842326,0.0150832834172313,0.0162930643421694,0.0156464111811061,0.0140876336888382,0.0147738274860495,0.014343606,0.0144809580069721,0.0155184085819924,0.0145351647043167 69,0.0167537526933093,0.0173955023983056,0.0163489692261727,0.0162410769894122,0.0159072235502209,0.0142806626741827,0.0144166849717331,0.0144748792287603,0.0150088116085674,0.0149392683302505,0.0149955731793291,0.0161056530842326,0.0150832834172313,0.0162930643421694,0.0156464111811061,0.0140876336888382,0.0147738274860495,0.014343606,0.0144809580069721,0.0155184085819924,0.0145351647043167
"71",0.0211071618617466,0.0194233079695635,0.0176768077112101,0.018340597203545,0.0171314894540352,0.0174111836133792,0.0157428261755233,0.0162591365928891,0.016428165645089,0.015894712928701,0.0163254004513298,0.0165250142364891,0.0162380952380952,0.0167827712245967,0.0164666363145954,0.0168721866705193,0.0166735540902312,0.015458872,0.0173484739255874,0.0174839421844556,0.0156358592538071 70,0.0211071618617466,0.0194233079695635,0.0176768077112101,0.018340597203545,0.0171314894540352,0.0174111836133792,0.0157428261755233,0.0162591365928891,0.016428165645089,0.015894712928701,0.0163254004513298,0.0165250142364891,0.0162380952380952,0.0167827712245967,0.0164666363145954,0.0168721866705193,0.0166735540902312,0.015458872,0.0173484739255874,0.0174839421844556,0.0156358592538071
"72",0.0217392907445781,0.0215616245568847,0.0198572026578465,0.0198690339893749,0.0185414882309843,0.0176769816843154,0.0169983306663305,0.017354393123908,0.0174483178675074,0.0168483345723007,0.0183956286891418,0.0171972289599308,0.0177108947756274,0.0185545766896783,0.0179322749937113,0.0182600066159444,0.0176176153093388,0.01784936,0.0187385090021118,0.0183527079444314,0.0179198574118873 71,0.0217392907445781,0.0215616245568847,0.0198572026578465,0.0198690339893749,0.0185414882309843,0.0176769816843154,0.0169983306663305,0.017354393123908,0.0174483178675074,0.0168483345723007,0.0183956286891418,0.0171972289599308,0.0177108947756274,0.0185545766896783,0.0179322749937113,0.0182600066159444,0.0176176153093388,0.01784936,0.0187385090021118,0.0183527079444314,0.0179198574118873
"73",0.0243776515746706,0.0243928242175102,0.0231577681157733,0.0218185758924002,0.0207048893870957,0.0204972001464086,0.0193769117098354,0.0194505307890802,0.018698988066465,0.0183043276790666,0.0190189867931958,0.0177543275508549,0.0181969918849318,0.0187693736906466,0.0188899095577764,0.0198524404883083,0.0198190127753356,0.019437402,0.0208045593701382,0.0211059139200116,0.0195894424612934 72,0.0243776515746706,0.0243928242175102,0.0231577681157733,0.0218185758924002,0.0207048893870957,0.0204972001464086,0.0193769117098354,0.0194505307890802,0.018698988066465,0.0183043276790666,0.0190189867931958,0.0177543275508549,0.0181969918849318,0.0187693736906466,0.0188899095577764,0.0198524404883083,0.0198190127753356,0.019437402,0.0208045593701382,0.0211059139200116,0.0195894424612934
"74",0.0273584814575227,0.0278774575850941,0.0256003967131694,0.0234376086960843,0.0234154665966555,0.0224328993384739,0.0206612992017616,0.0230962371878654,0.0210853814222064,0.0200245645467922,0.0211917084808635,0.0203673854239902,0.0198049284927302,0.0214128077179461,0.0213326806426212,0.0216370142554733,0.020797686597783,0.021047689,0.0225410449324547,0.0237078643467831,0.0219131726032098 73,0.0273584814575227,0.0278774575850941,0.0256003967131694,0.0234376086960843,0.0234154665966555,0.0224328993384739,0.0206612992017616,0.0230962371878654,0.0210853814222064,0.0200245645467922,0.0211917084808635,0.0203673854239902,0.0198049284927302,0.0214128077179461,0.0213326806426212,0.0216370142554733,0.020797686597783,0.021047689,0.0225410449324547,0.0237078643467831,0.0219131726032098
"75",0.029406810251474,0.0297020247039348,0.0276010423545508,0.0285244670046726,0.0269525317872949,0.0246008458117186,0.0255182311618521,0.0254031921116403,0.0239040844211995,0.0219192763872953,0.0239046627749854,0.0220591494184464,0.0217066282739908,0.0225590918887851,0.0224492715610768,0.0220185419300464,0.0233507639893457,0.022709345,0.023958778995145,0.0243111185994149,0.0244392847739187 74,0.029406810251474,0.0297020247039348,0.0276010423545508,0.0285244670046726,0.0269525317872949,0.0246008458117186,0.0255182311618521,0.0254031921116403,0.0239040844211995,0.0219192763872953,0.0239046627749854,0.0220591494184464,0.0217066282739908,0.0225590918887851,0.0224492715610768,0.0220185419300464,0.0233507639893457,0.022709345,0.023958778995145,0.0243111185994149,0.0244392847739187
"76",0.0322274571391179,0.0325047682357838,0.0308717999244626,0.0304799451002592,0.0286607522833666,0.0289466855291685,0.0269715727225997,0.0276594989709744,0.0259478199632993,0.0260569285282794,0.0249483560183485,0.0247130311626743,0.0235903411665696,0.0239094727718892,0.0241730082201224,0.0238226293632509,0.024853761759711,0.025629303,0.0273119354880997,0.0264447409101497,0.0267089024447616 75,0.0322274571391179,0.0325047682357838,0.0308717999244626,0.0304799451002592,0.0286607522833666,0.0289466855291685,0.0269715727225997,0.0276594989709744,0.0259478199632993,0.0260569285282794,0.0249483560183485,0.0247130311626743,0.0235903411665696,0.0239094727718892,0.0241730082201224,0.0238226293632509,0.024853761759711,0.025629303,0.0273119354880997,0.0264447409101497,0.0267089024447616
"77",0.0370451565401909,0.0369584704618325,0.0349997643257789,0.0341378353239302,0.0334032033806461,0.0314884892359485,0.0313592157607242,0.0328054675779297,0.0299944775840115,0.0287949979823093,0.028362684821749,0.0282961292474255,0.0259625646944769,0.0275932024722502,0.0267422402159244,0.0257735542936609,0.0258807871708276,0.026018688,0.0306803923420445,0.0303054242624518,0.0308558323777755 76,0.0370451565401909,0.0369584704618325,0.0349997643257789,0.0341378353239302,0.0334032033806461,0.0314884892359485,0.0313592157607242,0.0328054675779297,0.0299944775840115,0.0287949979823093,0.028362684821749,0.0282961292474255,0.0259625646944769,0.0275932024722502,0.0267422402159244,0.0257735542936609,0.0258807871708276,0.026018688,0.0306803923420445,0.0303054242624518,0.0308558323777755
"78",0.0408670908470684,0.0401419001532659,0.0376997846355761,0.0383309935493043,0.0379951211807445,0.036807761636693,0.0352609678010311,0.0346351229038572,0.0325936677522036,0.033416246414225,0.0313752499019523,0.0315684877483862,0.029392884737035,0.0309759891450136,0.0298314651741845,0.0297625985934647,0.0291781015491942,0.028321968,0.0326240682255612,0.0341273652198724,0.0336384935010224 77,0.0408670908470684,0.0401419001532659,0.0376997846355761,0.0383309935493043,0.0379951211807445,0.036807761636693,0.0352609678010311,0.0346351229038572,0.0325936677522036,0.033416246414225,0.0313752499019523,0.0315684877483862,0.029392884737035,0.0309759891450136,0.0298314651741845,0.0297625985934647,0.0291781015491942,0.028321968,0.0326240682255612,0.0341273652198724,0.0336384935010224
"79",0.0444657808157639,0.0449657176266322,0.0420675585599537,0.0411627374685283,0.0407563762667085,0.0404137204033158,0.0400161909995229,0.0391807174380446,0.0372007970279999,0.035181451852274,0.0356230253750722,0.0338786952845721,0.0333678042054464,0.0355282688870231,0.0324702383007917,0.0320221540451164,0.0323639224662041,0.030951546,0.0362431260191316,0.0356740779857054,0.0358777347317005 78,0.0444657808157639,0.0449657176266322,0.0420675585599537,0.0411627374685283,0.0407563762667085,0.0404137204033158,0.0400161909995229,0.0391807174380446,0.0372007970279999,0.035181451852274,0.0356230253750722,0.0338786952845721,0.0333678042054464,0.0355282688870231,0.0324702383007917,0.0320221540451164,0.0323639224662041,0.030951546,0.0362431260191316,0.0356740779857054,0.0358777347317005
"80",0.0510997222544477,0.047840580749487,0.0443934885836695,0.0462854519390231,0.0432545048811839,0.04442805388637,0.0440060770296851,0.0427581556655264,0.0408755821188182,0.0394359980617831,0.0413330905834363,0.0411386333572316,0.035837981604876,0.0377998027437478,0.0360964933054466,0.0368410776110447,0.0349054975795392,0.034429248,0.0390743844473335,0.039157731594666,0.0386951973371374 79,0.0510997222544477,0.047840580749487,0.0443934885836695,0.0462854519390231,0.0432545048811839,0.04442805388637,0.0440060770296851,0.0427581556655264,0.0408755821188182,0.0394359980617831,0.0413330905834363,0.0411386333572316,0.035837981604876,0.0377998027437478,0.0360964933054466,0.0368410776110447,0.0349054975795392,0.034429248,0.0390743844473335,0.039157731594666,0.0386951973371374
"81",0.0563087390118433,0.0567512185512873,0.0546923796677725,0.0527814418036417,0.0503732809430255,0.0514701473145576,0.0510114113780306,0.0506385917325867,0.0471406339262849,0.0453924411461149,0.0458191753949627,0.0460300139928367,0.0436956041296135,0.0446573347014072,0.0417167391062665,0.0415617226267547,0.0414492395202176,0.038413902,0.0430879053827768,0.0440375904977748,0.0441514027566068 80,0.0563087390118433,0.0567512185512873,0.0546923796677725,0.0527814418036417,0.0503732809430255,0.0514701473145576,0.0510114113780306,0.0506385917325867,0.0471406339262849,0.0453924411461149,0.0458191753949627,0.0460300139928367,0.0436956041296135,0.0446573347014072,0.0417167391062665,0.0415617226267547,0.0414492395202176,0.038413902,0.0430879053827768,0.0440375904977748,0.0441514027566068
"82",0.0630344347899958,0.0635688304738634,0.0587157459626554,0.0612049729040485,0.0570513364337259,0.0556234339083435,0.0556107877755421,0.0549167375066288,0.0541547894651191,0.0529309752170351,0.0521111463678273,0.0517655448701142,0.049628218785981,0.0505341998017403,0.0467871418868513,0.0490554884970956,0.0466488689054377,0.042978567,0.0492712932150301,0.0488919321912417,0.0480316816421605 81,0.0630344347899958,0.0635688304738634,0.0587157459626554,0.0612049729040485,0.0570513364337259,0.0556234339083435,0.0556107877755421,0.0549167375066288,0.0541547894651191,0.0529309752170351,0.0521111463678273,0.0517655448701142,0.049628218785981,0.0505341998017403,0.0467871418868513,0.0490554884970956,0.0466488689054377,0.042978567,0.0492712932150301,0.0488919321912417,0.0480316816421605
"83",0.0703001482970353,0.0731871751764395,0.0685182787345159,0.067855603535908,0.0667846485025698,0.0618834252137277,0.0639284422374955,0.0634133925549679,0.0621321549130144,0.0606395227856003,0.0593548950857992,0.0603495900222882,0.055737795602268,0.0585625353706848,0.0547537327482585,0.0541481292979639,0.0544279317734376,0.05205749,0.0570976951241149,0.0551117734110804,0.0549288075153697 82,0.0703001482970353,0.0731871751764395,0.0685182787345159,0.067855603535908,0.0667846485025698,0.0618834252137277,0.0639284422374955,0.0634133925549679,0.0621321549130144,0.0606395227856003,0.0593548950857992,0.0603495900222882,0.055737795602268,0.0585625353706848,0.0547537327482585,0.0541481292979639,0.0544279317734376,0.05205749,0.0570976951241149,0.0551117734110804,0.0549288075153697
"84",0.0830402263998383,0.0794981019828152,0.0757625028377193,0.0765504801776527,0.0725824503263129,0.0710074414955591,0.069726943641471,0.0716813563489578,0.0699563519686427,0.0663592694701612,0.0678086363179461,0.0655621336203762,0.0639247998008862,0.0660435479044551,0.0627194851815611,0.0639306947094589,0.0629619202890705,0.059549933,0.0644473318697074,0.0608189407558354,0.0607967050310536 83,0.0830402263998383,0.0794981019828152,0.0757625028377193,0.0765504801776527,0.0725824503263129,0.0710074414955591,0.069726943641471,0.0716813563489578,0.0699563519686427,0.0663592694701612,0.0678086363179461,0.0655621336203762,0.0639247998008862,0.0660435479044551,0.0627194851815611,0.0639306947094589,0.0629619202890705,0.059549933,0.0644473318697074,0.0608189407558354,0.0607967050310536
"85",0.0880088603149734,0.0904417501784597,0.0866054675823721,0.0848282991460662,0.0814724726356307,0.0823279010209487,0.0792224370884364,0.0795085337945799,0.0789524250528418,0.0782257365754097,0.0774490118730187,0.0740531678405282,0.0695896910618717,0.0738624580995212,0.0693466138956665,0.0718101061560227,0.0692915243021545,0.070560637,0.0745133453088476,0.0703835584007576,0.072442909522433 84,0.0880088603149734,0.0904417501784597,0.0866054675823721,0.0848282991460662,0.0814724726356307,0.0823279010209487,0.0792224370884364,0.0795085337945799,0.0789524250528418,0.0782257365754097,0.0774490118730187,0.0740531678405282,0.0695896910618717,0.0738624580995212,0.0693466138956665,0.0718101061560227,0.0692915243021545,0.070560637,0.0745133453088476,0.0703835584007576,0.072442909522433
"86",0.101129746677948,0.106642822547595,0.0985498434317332,0.0937504940477132,0.0951655605120952,0.0967326145221679,0.0902013790271528,0.0922346278483971,0.0899023378286773,0.0841989896395239,0.0896755984529078,0.0858645125808745,0.0835780036272799,0.0863937255953478,0.0803042433947158,0.0837292924104276,0.081745938593887,0.080506014,0.0841914612878464,0.0833109910113311,0.0823043566613969 85,0.101129746677948,0.106642822547595,0.0985498434317332,0.0937504940477132,0.0951655605120952,0.0967326145221679,0.0902013790271528,0.0922346278483971,0.0899023378286773,0.0841989896395239,0.0896755984529078,0.0858645125808745,0.0835780036272799,0.0863937255953478,0.0803042433947158,0.0837292924104276,0.081745938593887,0.080506014,0.0841914612878464,0.0833109910113311,0.0823043566613969
"87",0.114979483678698,0.118619301985771,0.111871823241188,0.111825461610594,0.108029260836336,0.106175619170151,0.104384748765644,0.102844515172885,0.101037287930565,0.0936726771803865,0.0964515441003132,0.094488188976378,0.0936640593623898,0.0994789483140684,0.0922320147571224,0.0975772813812548,0.0938478734824423,0.090619661,0.0963417335706483,0.096785054975676,0.0972905550550897 86,0.114979483678698,0.118619301985771,0.111871823241188,0.111825461610594,0.108029260836336,0.106175619170151,0.104384748765644,0.102844515172885,0.101037287930565,0.0936726771803865,0.0964515441003132,0.094488188976378,0.0936640593623898,0.0994789483140684,0.0922320147571224,0.0975772813812548,0.0938478734824423,0.090619661,0.0963417335706483,0.096785054975676,0.0972905550550897
"88",0.127683839638893,0.131629861898726,0.121473951715375,0.121836943560275,0.125498295355318,0.118500461970945,0.116425614716255,0.115914609683481,0.110576437729246,0.111043933897622,0.113634484013431,0.108607050659495,0.101899426245773,0.113111018092182,0.10417341203623,0.109512018774412,0.102866120163548,0.102591209,0.112621311252661,0.105457108165709,0.110609654794427 87,0.127683839638893,0.131629861898726,0.121473951715375,0.121836943560275,0.125498295355318,0.118500461970945,0.116425614716255,0.115914609683481,0.110576437729246,0.111043933897622,0.113634484013431,0.108607050659495,0.101899426245773,0.113111018092182,0.10417341203623,0.109512018774412,0.102866120163548,0.102591209,0.112621311252661,0.105457108165709,0.110609654794427
"89",0.140937488215404,0.144790369447904,0.139221916125131,0.138809993493282,0.128927317866621,0.126041150976663,0.130355687994554,0.128579754005337,0.130342897397331,0.121051958569541,0.126687149965204,0.125041420670665,0.11621888324117,0.12733728704718,0.119305320423808,0.119552052471724,0.118620739613894,0.118288692,0.126763236131318,0.124627310673822,0.126291771640443 88,0.140937488215404,0.144790369447904,0.139221916125131,0.138809993493282,0.128927317866621,0.126041150976663,0.130355687994554,0.128579754005337,0.130342897397331,0.121051958569541,0.126687149965204,0.125041420670665,0.11621888324117,0.12733728704718,0.119305320423808,0.119552052471724,0.118620739613894,0.118288692,0.126763236131318,0.124627310673822,0.126291771640443
"90",0.163222136466284,0.163534181627514,0.149129564011709,0.151276619467053,0.148930841611907,0.142806175801193,0.147761669587382,0.145510696477401,0.142426141922331,0.140199361036371,0.139013428662596,0.141064047628076,0.137002042900919,0.142385592437086,0.128992582602832,0.136798017294559,0.134734880963723,0.130164399,0.145545745982626,0.13940812798804,0.140582891708437 89,0.163222136466284,0.163534181627514,0.149129564011709,0.151276619467053,0.148930841611907,0.142806175801193,0.147761669587382,0.145510696477401,0.142426141922331,0.140199361036371,0.139013428662596,0.141064047628076,0.137002042900919,0.142385592437086,0.128992582602832,0.136798017294559,0.134734880963723,0.130164399,0.145545745982626,0.13940812798804,0.140582891708437
"91",0.173006024638072,0.17928214683125,0.172739636504937,0.171275373420146,0.169388480214762,0.161935574623716,0.16872735637472,0.166508277310431,0.163436983626258,0.155087349541868,0.163268424034477,0.160985253932075,0.15033367572643,0.158051180007539,0.147421352793279,0.154083742247241,0.156098296207444,0.148412834,0.166086541689489,0.156008876038859,0.162554707071927 90,0.173006024638072,0.17928214683125,0.172739636504937,0.171275373420146,0.169388480214762,0.161935574623716,0.16872735637472,0.166508277310431,0.163436983626258,0.155087349541868,0.163268424034477,0.160985253932075,0.15033367572643,0.158051180007539,0.147421352793279,0.154083742247241,0.156098296207444,0.148412834,0.166086541689489,0.156008876038859,0.162554707071927
"92",0.198981590285938,0.198963730569948,0.186864754529576,0.192752555188876,0.186020722874866,0.17653846761828,0.194935049658023,0.174511097988815,0.174965519182594,0.18007192115576,0.178941625750136,0.177710317610898,0.16291860822847,0.179443363002808,0.168441361972068,0.171336051117472,0.174721572435303,0.173409458,0.18085938340783,0.176683296182288,0.182410790338817 91,0.198981590285938,0.198963730569948,0.186864754529576,0.192752555188876,0.186020722874866,0.17653846761828,0.194935049658023,0.174511097988815,0.174965519182594,0.18007192115576,0.178941625750136,0.177710317610898,0.16291860822847,0.179443363002808,0.168441361972068,0.171336051117472,0.174721572435303,0.173409458,0.18085938340783,0.176683296182288,0.182410790338817
"93",0.215428554775158,0.215019395330592,0.204611466721729,0.205917405046894,0.20276692364558,0.208663092502766,0.200870490376245,0.207803011396722,0.189732001436084,0.191638881764555,0.205009195200981,0.193472869754985,0.190274880297029,0.194113714791595,0.191493000855201,0.192164409682374,0.192073064454282,0.189624266,0.200512572360521,0.203696214106104,0.206868490992356 92,0.215428554775158,0.215019395330592,0.204611466721729,0.205917405046894,0.20276692364558,0.208663092502766,0.200870490376245,0.207803011396722,0.189732001436084,0.191638881764555,0.205009195200981,0.193472869754985,0.190274880297029,0.194113714791595,0.191493000855201,0.192164409682374,0.192073064454282,0.189624266,0.200512572360521,0.203696214106104,0.206868490992356
"94",0.242012826837691,0.230447059715352,0.242718804079679,0.230119621807038,0.224409769114369,0.209861228270398,0.218920027828817,0.219428571428571,0.219744809126582,0.216086057528725,0.215923963183076,0.2202157147954,0.20688470692151,0.228750454050127,0.215035511680886,0.220793405925209,0.216496417136759,0.212191757,0.227378695775323,0.217247937697649,0.229731522844885 93,0.242012826837691,0.230447059715352,0.242718804079679,0.230119621807038,0.224409769114369,0.209861228270398,0.218920027828817,0.219428571428571,0.219744809126582,0.216086057528725,0.215923963183076,0.2202157147954,0.20688470692151,0.228750454050127,0.215035511680886,0.220793405925209,0.216496417136759,0.212191757,0.227378695775323,0.217247937697649,0.229731522844885
"95",0.258408258408258,0.265889580215799,0.240897892143444,0.239378313603021,0.249651763648618,0.239044494911263,0.24758545393466,0.237735153080044,0.24209452567154,0.218940631354378,0.252454417952314,0.231051679728174,0.232140350877193,0.226783723085138,0.219662798335888,0.241945410565789,0.249154550972628,0.238257733,0.252094223067002,0.241192373565089,0.248275065677416 94,0.258408258408258,0.265889580215799,0.240897892143444,0.239378313603021,0.249651763648618,0.239044494911263,0.24758545393466,0.237735153080044,0.24209452567154,0.218940631354378,0.252454417952314,0.231051679728174,0.232140350877193,0.226783723085138,0.219662798335888,0.241945410565789,0.249154550972628,0.238257733,0.252094223067002,0.241192373565089,0.248275065677416
"96",0.285075202468184,0.293572311495674,0.26475108109074,0.275029523684556,0.258655804480652,0.260401721664275,0.259031130347927,0.272467982775013,0.274102249243763,0.255822490516784,0.263254113345521,0.274203458263846,0.25083826781765,0.256980932932565,0.247865490583937,0.26187994010273,0.26097334571011,0.256168943,0.27416902020421,0.263851665481595,0.272713687985655 95,0.285075202468184,0.293572311495674,0.26475108109074,0.275029523684556,0.258655804480652,0.260401721664275,0.259031130347927,0.272467982775013,0.274102249243763,0.255822490516784,0.263254113345521,0.274203458263846,0.25083826781765,0.256980932932565,0.247865490583937,0.26187994010273,0.26097334571011,0.256168943,0.27416902020421,0.263851665481595,0.272713687985655
"97",0.305273949196947,0.323567307153661,0.294922833615095,0.277742362575394,0.288362145785065,0.279935905764151,0.289683664789987,0.285779641631719,0.271032631300337,0.275952050884775,0.29500221141088,0.285241248817408,0.28178157119673,0.295245398773006,0.271765863256272,0.30023897458179,0.27338611920666,0.285263426,0.30935635394185,0.299100994165227,0.313294196329048 96,0.305273949196947,0.323567307153661,0.294922833615095,0.277742362575394,0.288362145785065,0.279935905764151,0.289683664789987,0.285779641631719,0.271032631300337,0.275952050884775,0.29500221141088,0.285241248817408,0.28178157119673,0.295245398773006,0.271765863256272,0.30023897458179,0.27338611920666,0.285263426,0.30935635394185,0.299100994165227,0.313294196329048
"98",0.30940791220462,0.325197720894634,0.302910052910053,0.302825552825553,0.309578961711405,0.323428642621317,0.297708524289643,0.311489657569963,0.295293495505024,0.294139060793593,0.320144290384399,0.328416452040896,0.293450360188789,0.302845528455285,0.2992,0.30496209510682,0.31376125869342,0.306067095,0.30896512374295,0.318070863229529,0.358314981885345 97,0.30940791220462,0.325197720894634,0.302910052910053,0.302825552825553,0.309578961711405,0.323428642621317,0.297708524289643,0.311489657569963,0.295293495505024,0.294139060793593,0.320144290384399,0.328416452040896,0.293450360188789,0.302845528455285,0.2992,0.30496209510682,0.31376125869342,0.306067095,0.30896512374295,0.318070863229529,0.358314981885345
"99",0.357548083575481,0.324353160842891,0.340892100672813,0.343347639484978,0.325847644209599,0.356818630353266,0.342614004254926,0.356665494196272,0.304628002343292,0.315420734888574,0.34088200238379,0.330281338438488,0.331166609647622,0.366426858513189,0.322160834868017,0.33110303957178,0.31703832536182,0.317467249,0.34048582995951,0.345424567188788,0.376744697219475 98,0.357548083575481,0.324353160842891,0.340892100672813,0.343347639484978,0.325847644209599,0.356818630353266,0.342614004254926,0.356665494196272,0.304628002343292,0.315420734888574,0.34088200238379,0.330281338438488,0.331166609647622,0.366426858513189,0.322160834868017,0.33110303957178,0.31703832536182,0.317467249,0.34048582995951,0.345424567188788,0.376744697219475
"100",0.367473167182099,0.388099705172876,0.351031450794724,0.387810770789494,0.375564605701592,0.384904609385879,0.379592366610412,0.384481203007519,0.404049393703415,0.362227805695142,0.382373777924715,0.385873001535543,0.381453588603575,0.389773077318,0.373917008663931,0.3534016775396,0.35678889990089,0.340441042,0.37743655024266,0.351763437548129,0.390623783194455 99,0.367473167182099,0.388099705172876,0.351031450794724,0.387810770789494,0.375564605701592,0.384904609385879,0.379592366610412,0.384481203007519,0.404049393703415,0.362227805695142,0.382373777924715,0.385873001535543,0.381453588603575,0.389773077318,0.373917008663931,0.3534016775396,0.35678889990089,0.340441042,0.37743655024266,0.351763437548129,0.390623783194455
"101",NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,0.42321712309561,0.39333669863705,0.425795551,0.42634519259041,0.406501983873032,0.444571363298875 100,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,0.42321712309561,0.39333669863705,0.425795551,0.42634519259041,0.406501983873032,0.444571363298875
"Jahr","Alter","Geschlecht","qx"
"2020-2022",0,"M",0.00278253094698546
"2020-2022",0,"F",0.00275760789752794
"2020-2022",0,"U",0.00277042345070311
"2020-2022",1,"M",0.000221309910424717
"2020-2022",1,"F",0.000173818982979879
"2020-2022",1,"U",0.000198142562963314
"2020-2022",2,"M",0.000169867168785589
"2020-2022",2,"F",0.000113591205762109
"2020-2022",2,"U",0.00014247061354492
"2020-2022",3,"M",0.000132301788715943
"2020-2022",3,"F",8.54032978299536e-05
"2020-2022",3,"U",0.000109473343284479
"2020-2022",4,"M",0.000105696806385667
"2020-2022",4,"F",7.8229219399297e-05
"2020-2022",4,"U",9.23073950013176e-05
"2020-2022",5,"M",8.71352579648467e-05
"2020-2022",5,"F",8.10429306852882e-05
"2020-2022",5,"U",8.41294115143883e-05
"2020-2022",6,"M",7.37002793204118e-05
"2020-2022",6,"F",7.37002793204118e-05
"2020-2022",6,"U",7.80962541984004e-05
"2020-2022",7,"M",6.33977774118485e-05
"2020-2022",7,"F",6.33977774118485e-05
"2020-2022",7,"U",6.9387838490248e-05
"2020-2022",8,"M",5.741187146357e-05
"2020-2022",8,"F",5.741187146357e-05
"2020-2022",8,"U",6.01518915173955e-05
"2020-2022",9,"M",5.76104105283527e-05
"2020-2022",9,"F",5.01033737650335e-05
"2020-2022",9,"U",5.40351279744517e-05
"2020-2022",10,"M",6.58612436623568e-05
"2020-2022",10,"F",4.26919941868709e-05
"2020-2022",10,"U",5.46842625585828e-05
"2020-2022",11,"M",8.40316616893976e-05
"2020-2022",11,"F",4.62982731287259e-05
"2020-2022",11,"U",6.57448377426488e-05
"2020-2022",12,"M",0.000113248192186473
"2020-2022",12,"F",6.40412462335456e-05
"2020-2022",12,"U",8.93068643490436e-05
"2020-2022",13,"M",0.000152436285424073
"2020-2022",13,"F",9.17817963365813e-05
"2020-2022",13,"U",0.000122838302415217
"2020-2022",14,"M",0.000200114446387976
"2020-2022",14,"F",0.000124038885576516
"2020-2022",14,"U",0.000162952565964918
"2020-2022",15,"M",0.000254801180054207
"2020-2022",15,"F",0.000155331476082395
"2020-2022",15,"U",0.000206263069012604
"2020-2022",16,"M",0.000315012599350857
"2020-2022",16,"F",0.000180182959579788
"2020-2022",16,"U",0.00024938408897171
"2020-2022",17,"M",0.000378196456837694
"2020-2022",17,"F",0.000195095115635104
"2020-2022",17,"U",0.000289315521725032
"2020-2022",18,"M",0.000439053988785843
"2020-2022",18,"F",0.000201655717789562
"2020-2022",18,"U",0.000324048602242213
"2020-2022",19,"M",0.000491851166979565
"2020-2022",19,"F",0.000202258561602552
"2020-2022",19,"U",0.000351731671687048
"2020-2022",20,"M",0.000530853963201142
"2020-2022",20,"F",0.000199297442630103
"2020-2022",20,"U",0.000370513071220075
"2020-2022",21,"M",0.000550347763588801
"2020-2022",21,"F",0.000195163982734008
"2020-2022",21,"U",0.000378550257541298
"2020-2022",22,"M",0.00054873379821431
"2020-2022",22,"F",0.000191788980758652
"2020-2022",22,"U",0.000375933181921031
"2020-2022",23,"M",0.000533596288557285
"2020-2022",23,"F",0.000190075078525532
"2020-2022",23,"U",0.000367063446243159
"2020-2022",24,"M",0.000513761975019867
"2020-2022",24,"F",0.000190785801472963
"2020-2022",24,"U",0.000356926046978228
"2020-2022",25,"M",0.0004980575980045
"2020-2022",25,"F",0.000194684675039576
"2020-2022",25,"U",0.000350505980597076
"2020-2022",26,"M",0.000495274594417591
"2020-2022",26,"F",0.000202532105379172
"2020-2022",26,"U",0.000352768122588819
"2020-2022",27,"M",0.000509932678188506
"2020-2022",27,"F",0.00021471106522645
"2020-2022",27,"U",0.000366242709699051
"2020-2022",28,"M",0.00053825524176188
"2020-2022",28,"F",0.000230871495468589
"2020-2022",28,"U",0.000388731548055195
"2020-2022",29,"M",0.000575512483199146
"2020-2022",29,"F",0.000250579116312599
"2020-2022",29,"U",0.000417493177288309
"2020-2022",30,"M",0.000616974600561528
"2020-2022",30,"F",0.000273399647965289
"2020-2022",30,"U",0.000449786137029259
"2020-2022",31,"M",0.000657945999763365
"2020-2022",31,"F",0.00029889698342756
"2020-2022",31,"U",0.000482886634892742
"2020-2022",32,"M",0.000696377760986881
"2020-2022",32,"F",0.000326493644106275
"2020-2022",32,"U",0.000515437856949014
"2020-2022",33,"M",0.000734707261006527
"2020-2022",33,"F",0.000355372516742961
"2020-2022",33,"U",0.000548400112633578
"2020-2022",34,"M",0.000775806443027713
"2020-2022",34,"F",0.000384693275797526
"2020-2022",34,"U",0.00058295816021418
"2020-2022",35,"M",0.000822547250255816
"2020-2022",35,"F",0.000413615595729788
"2020-2022",35,"U",0.000620296757958584
"2020-2022",36,"M",0.000877773481050526
"2020-2022",36,"F",0.00044132725124311
"2020-2022",36,"U",0.000661597978854065
"2020-2022",37,"M",0.000942826425713166
"2020-2022",37,"F",0.000468516144047996
"2020-2022",37,"U",0.000707900542637704
"2020-2022",38,"M",0.00101681966490106
"2020-2022",38,"F",0.000498094355206469
"2020-2022",38,"U",0.000760030624815977
"2020-2022",39,"M",0.00109868650456192
"2020-2022",39,"F",0.000533153954805256
"2020-2022",39,"U",0.000818797201010459
"2020-2022",40,"M",0.00118736025064364
"2020-2022",40,"F",0.000576787012931267
"2020-2022",40,"U",0.000885009246842793
"2020-2022",41,"M",0.00128181764065685
"2020-2022",41,"F",0.000632035541824943
"2020-2022",41,"U",0.000959476419688908
"2020-2022",42,"M",0.00138272381411315
"2020-2022",42,"F",0.000699995554945584
"2020-2022",42,"U",0.00104303488011783
"2020-2022",43,"M",0.00149293720444077
"2020-2022",43,"F",0.000779235144505474
"2020-2022",43,"U",0.0011365552172832
"2020-2022",44,"M",0.00161546282659291
"2020-2022",44,"F",0.000868153457485661
"2020-2022",44,"U",0.00124091032125955
"2020-2022",45,"M",0.00175330569552253
"2020-2022",45,"F",0.000965149640867112
"2020-2022",45,"U",0.00135697308212129
"2020-2022",46,"M",0.00190951618158414
"2020-2022",46,"F",0.00106866648983477
"2020-2022",46,"U",0.00148565953602828
"2020-2022",47,"M",0.00208848061747348
"2020-2022",47,"F",0.00117843247569814
"2020-2022",47,"U",0.00162915660515194
"2020-2022",48,"M",0.00229610757267523
"2020-2022",48,"F",0.00129564100888597
"2020-2022",48,"U",0.00179109929847095
"2020-2022",49,"M",0.00253838842605736
"2020-2022",49,"F",0.00142156519222829
"2020-2022",49,"U",0.00197520140060286
"2020-2022",50,"M",0.0028213145564872
"2020-2022",50,"F",0.00155747812855449
"2020-2022",50,"U",0.00218517669616457
"2020-2022",51,"M",0.0031507085123552
"2020-2022",51,"F",0.00170472365392057
"2020-2022",51,"U",0.00242468061260009
"2020-2022",52,"M",0.00352850974106049
"2020-2022",52,"F",0.00186627246857357
"2020-2022",52,"U",0.00269602636235533
"2020-2022",53,"M",0.00395277458901309
"2020-2022",53,"F",0.00204672213695345
"2020-2022",53,"U",0.00300018494288005
"2020-2022",54,"M",0.0044213905721444
"2020-2022",54,"F",0.00225074095672521
"2020-2022",54,"U",0.00333806899444962
"2020-2022",55,"M",0.00493224520638632
"2020-2022",55,"F",0.00248299722555434
"2020-2022",55,"U",0.0037105911573398
"2020-2022",56,"M",0.00548383317458657
"2020-2022",56,"F",0.00274822667025248
"2020-2022",56,"U",0.00411899609247267
"2020-2022",57,"M",0.0060858103563914
"2020-2022",57,"F",0.00305240452847172
"2020-2022",57,"U",0.0045706318034924
"2020-2022",58,"M",0.0067576280448144
"2020-2022",58,"F",0.00340259387112044
"2020-2022",58,"U",0.00507820277739925
"2020-2022",59,"M",0.00751907008334331
"2020-2022",59,"F",0.00380589470062236
"2020-2022",59,"U",0.00565459535171989
"2020-2022",60,"M",0.00838992031546653
"2020-2022",60,"F",0.00426940701940197
"2020-2022",60,"U",0.00631269586398162
"2020-2022",61,"M",0.00938824219936506
"2020-2022",61,"F",0.00479937657423386
"2020-2022",61,"U",0.00706410609422891
"2020-2022",62,"M",0.0105063571315905
"2020-2022",62,"F",0.00538926691625154
"2020-2022",62,"U",0.00790120703647388
"2020-2022",63,"M",0.0117167702186774
"2020-2022",63,"F",0.00602270183707226
"2020-2022",63,"U",0.0088015834855797
"2020-2022",64,"M",0.0129914768233659
"2020-2022",64,"F",0.00668305201552852
"2020-2022",64,"U",0.00974243962678531
"2020-2022",65,"M",0.0143024723083959
"2020-2022",65,"F",0.0073536881304526
"2020-2022",65,"U",0.0107009796453294
"2020-2022",66,"M",0.0156263188649238
"2020-2022",66,"F",0.00802177793555013
"2020-2022",66,"U",0.0116586745842483
"2020-2022",67,"M",0.0169960123776353
"2020-2022",67,"F",0.00872141079842554
"2020-2022",67,"U",0.0126497223515517
"2020-2022",68,"M",0.0184826111777966
"2020-2022",68,"F",0.00951832298609476
"2020-2022",68,"U",0.0137438831825742
"2020-2022",69,"M",0.020157886578989
"2020-2022",69,"F",0.0104788435724376
"2020-2022",69,"U",0.0150115834629567
"2020-2022",70,"M",0.0220936098947935
"2020-2022",70,"F",0.0116693016313341
"2020-2022",70,"U",0.0165232495783405
"2020-2022",71,"M",0.0243537041848234
"2020-2022",71,"F",0.0131476970519972
"2020-2022",71,"U",0.0183407463117382
"2020-2022",72,"M",0.0269210701550426
"2020-2022",72,"F",0.0148860424265381
"2020-2022",72,"U",0.0204375517554728
"2020-2022",73,"M",0.0297308096701913
"2020-2022",73,"F",0.0168056224556115
"2020-2022",73,"U",0.0227350005969383
"2020-2022",74,"M",0.0327174068024238
"2020-2022",74,"F",0.0188270661897678
"2020-2022",74,"U",0.0251537535781327
"2020-2022",75,"M",0.0358153456238934
"2020-2022",75,"F",0.0208710026795566
"2020-2022",75,"U",0.0276144714410533
"2020-2022",76,"M",0.038977689363643
"2020-2022",76,"F",0.0228812370626781
"2020-2022",76,"U",0.0300600708109623
"2020-2022",77,"M",0.0423192087273373
"2020-2022",77,"F",0.0250032922723969
"2020-2022",77,"U",0.0326271769267151
"2020-2022",78,"M",0.046037936568179
"2020-2022",78,"F",0.027486554447354
"2020-2022",78,"U",0.0355521543558693
"2020-2022",79,"M",0.0503325938562931
"2020-2022",79,"F",0.0305812680997889
"2020-2022",79,"U",0.0390721919579556
"2020-2022",80,"M",0.0554019015618034
"2020-2022",80,"F",0.03453767774194
"2020-2022",80,"U",0.0434244785925036
"2020-2022",81,"M",0.0614470972654435
"2020-2022",81,"F",0.0395905518653644
"2020-2022",81,"U",0.04883430015398
"2020-2022",82,"M",0.0686880178732279
"2020-2022",82,"F",0.0458602814962635
"2020-2022",82,"U",0.0554389721856764
"2020-2022",83,"M",0.0773528365638126
"2020-2022",83,"F",0.0534159933423287
"2020-2022",83,"U",0.0633363816591104
"2020-2022",84,"M",0.0876697658378948
"2020-2022",84,"F",0.0623265722984281
"2020-2022",84,"U",0.0726242295619705
"2020-2022",85,"M",0.0998670181961714
"2020-2022",85,"F",0.0726609032594301
"2020-2022",85,"U",0.0834002168819455
"2020-2022",86,"M",0.114114847284691
"2020-2022",86,"F",0.0844897598331453
"2020-2022",86,"U",0.095750282245884
"2020-2022",87,"M",0.130217786730578
"2020-2022",87,"F",0.0978958333945183
"2020-2022",87,"U",0.109686143855558
"2020-2022",88,"M",0.147838109662645
"2020-2022",88,"F",0.112966451180365
"2020-2022",88,"U",0.125190649098702
"2020-2022",89,"M",0.16663777068964
"2020-2022",89,"F",0.129788950807156
"2020-2022",89,"U",0.142246580721539
"2020-2022",90,"M",0.186278724420311
"2020-2022",90,"F",0.148450669891364
"2020-2022",90,"U",0.160836721470292
"2020-2022",91,"M",0.206530216711736
"2020-2022",91,"F",0.168994151966152
"2020-2022",91,"U",0.180933330428756
"2020-2022",92,"M",0.227741808087889
"2020-2022",92,"F",0.191219659260859
"2020-2022",92,"U",0.202451746514806
"2020-2022",93,"M",0.250458361523406
"2020-2022",93,"F",0.214845915255099
"2020-2022",93,"U",0.22528815240483
"2020-2022",94,"M",0.275224887168848
"2020-2022",94,"F",0.239591581982555
"2020-2022",94,"U",0.249338716339468
"2020-2022",95,"M",0.302586395174776
"2020-2022",95,"F",0.265175321476909
"2020-2022",95,"U",0.274499606559357
"2020-2022",96,"M",0.330798926647359
"2020-2022",96,"F",0.292497384507409
"2020-2022",96,"U",0.301103077476578
"2020-2022",97,"M",0.36106144084243
"2020-2022",97,"F",0.320938853882133
"2020-2022",97,"U",0.32892070540729
"2020-2022",98,"M",0.393101448453564
"2020-2022",98,"F",0.350640392000743
"2020-2022",98,"U",0.358004404684483
"2020-2022",99,"M",0.426918949480761
"2020-2022",99,"F",0.381601998863241
"2020-2022",99,"U",0.388354175308156
"2020-2022",100,"M",0.462513943924016
"2020-2022",100,"F",0.413823674469623
"2020-2022",100,"U",0.419970017278312
"2020-2022",101,"M",0.499886431783331
"2020-2022",101,"F",0.447305418819894
"2020-2022",101,"U",0.45285193059495
"2020-2022",102,"M",0.539036413058705
"2020-2022",102,"F",0.482047231914052
"2020-2022",102,"U",0.486999915258069
"2020-2022",103,"M",0.579963887750141
"2020-2022",103,"F",0.518049113752097
"2020-2022",103,"U",0.522413971267668
"2020-2022",104,"M",0.62266885585764
"2020-2022",104,"F",0.555311064334027
"2020-2022",104,"U",0.559094098623751
"2020-2022",105,"M",0.667151317381194
"2020-2022",105,"F",0.593833083659844
"2020-2022",105,"U",0.597040297326315
"2020-2022",106,"M",0.71341127232081
"2020-2022",106,"F",0.63361517172955
"2020-2022",106,"U",0.636252567375361
"2020-2022",107,"M",0.761448720676487
"2020-2022",107,"F",0.674657328543142
"2020-2022",107,"U",0.676730908770888
"2020-2022",108,"M",NA
"2020-2022",108,"F",0.716959554100619
"2020-2022",108,"U",0.718475321512894
"2020-2022",109,"M",NA
"2020-2022",109,"F",0.760521848401984
"2020-2022",109,"U",0.761485805601385
"2020-2022",110,"M",NA
"2020-2022",110,"F",0.805344211447236
"2020-2022",110,"U",0.805762361036357
"2019-2021",0,"M",0.00307454627498069
"2019-2021",0,"F",0.00278490821911174
"2019-2021",0,"U",0.00293363389662769
"2019-2021",1,"M",0.000257866267496858
"2019-2021",1,"F",0.000194603000962478
"2019-2021",1,"U",0.000227067647077736
"2019-2021",2,"M",0.000191421852629119
"2019-2021",2,"F",0.000132690057717511
"2019-2021",2,"U",0.000162870628304971
"2019-2021",3,"M",0.000144377622748922
"2019-2021",3,"F",9.63712690491524e-05
"2019-2021",3,"U",0.000121059562148506
"2019-2021",4,"M",0.000112413902402148
"2019-2021",4,"F",7.81922935409679e-05
"2019-2021",4,"U",9.58000701160525e-05
"2019-2021",5,"M",9.12110161337541e-05
"2019-2021",5,"F",7.06987897760298e-05
"2019-2021",5,"U",8.1257773713675e-05
"2019-2021",6,"M",7.64494197792032e-05
"2019-2021",6,"F",6.64366264301929e-05
"2019-2021",6,"U",7.15984636878652e-05
"2019-2021",7,"M",6.50247920448406e-05
"2019-2021",7,"F",5.9896394000523e-05
"2019-2021",7,"U",6.25544716460715e-05
"2019-2021",8,"M",5.80182876003322e-05
"2019-2021",8,"F",5.22667024226183e-05
"2019-2021",8,"U",5.52536161148899e-05
"2019-2021",9,"M",5.74114839065059e-05
"2019-2021",9,"F",4.6177108705605e-05
"2019-2021",9,"U",5.19844484563944e-05
"2019-2021",10,"M",6.51859584269753e-05
"2019-2021",10,"F",4.42571698612757e-05
"2019-2021",10,"U",5.50355200352823e-05
"2019-2021",11,"M",8.33226888293354e-05
"2019-2021",11,"F",4.91355119847495e-05
"2019-2021",11,"U",6.66946277912327e-05
"2019-2021",12,"M",0.000113006734009625
"2019-2021",12,"F",6.22054445404803e-05
"2019-2021",12,"U",8.82484565479622e-05
"2019-2021",13,"M",0.000153058188417771
"2019-2021",13,"F",8.11897015851025e-05
"2019-2021",13,"U",0.000118009022577199
"2019-2021",14,"M",0.000201859901010549
"2019-2021",14,"F",0.00010313238431077
"2019-2021",14,"U",0.000153738371752339
"2019-2021",15,"M",0.00025779472073466
"2019-2021",15,"F",0.000125077593900885
"2019-2021",15,"U",0.000193198549936814
"2019-2021",16,"M",0.000319243003798272
"2019-2021",16,"F",0.000144071602936994
"2019-2021",16,"U",0.000234151320625038
"2019-2021",17,"M",0.000383471774743164
"2019-2021",17,"F",0.000158130493822116
"2019-2021",17,"U",0.000274232331700789
"2019-2021",18,"M",0.000444885930640203
"2019-2021",18,"F",0.00016776351374604
"2019-2021",18,"U",0.000310753015925016
"2019-2021",19,"M",0.000497436782158489
"2019-2021",19,"F",0.000173875023565175
"2019-2021",19,"U",0.000340973424854627
"2019-2021",20,"M",0.000535075639963491
"2019-2021",20,"F",0.000177369384132631
"2019-2021",20,"U",0.000362153610043372
"2019-2021",21,"M",0.000551775038214258
"2019-2021",21,"F",0.000179151534006007
"2019-2021",21,"U",0.000371565028411198
"2019-2021",22,"M",0.000546006891923735
"2019-2021",22,"F",0.000180248885327161
"2019-2021",22,"U",0.000368897074792457
"2019-2021",23,"M",0.000526281829039018
"2019-2021",23,"F",0.000181962104971523
"2019-2021",23,"U",0.000359233882849457
"2019-2021",24,"M",0.000502468781160495
"2019-2021",24,"F",0.000185628832971384
"2019-2021",24,"U",0.000348389529765258
"2019-2021",25,"M",0.000484436679888868
"2019-2021",25,"F",0.000192586709359295
"2019-2021",25,"U",0.000342178092723148
"2019-2021",26,"M",0.000482013089920327
"2019-2021",26,"F",0.000204165593346468
"2019-2021",26,"U",0.000346388064547503
"2019-2021",27,"M",0.000500020180543566
"2019-2021",27,"F",0.000220753864803407
"2019-2021",27,"U",0.000363712230675315
"2019-2021",28,"M",0.000533558898561264
"2019-2021",28,"F",0.000240911410665706
"2019-2021",28,"U",0.000390831052278332
"2019-2021",29,"M",0.000576613284363
"2019-2021",29,"F",0.000262988035702146
"2019-2021",29,"U",0.000423734212846957
"2019-2021",30,"M",0.000623167378338088
"2019-2021",30,"F",0.000285333544681295
"2019-2021",30,"U",0.000458411395871371
"2019-2021",31,"M",0.000667244105774524
"2019-2021",31,"F",0.000306313729726288
"2019-2021",31,"U",0.000490881298657231
"2019-2021",32,"M",0.00070587493097009
"2019-2021",32,"F",0.000325531330505108
"2019-2021",32,"U",0.000519407428161019
"2019-2021",33,"M",0.000741191000669891
"2019-2021",33,"F",0.000344685798631781
"2019-2021",33,"U",0.000546058399511664
"2019-2021",34,"M",0.000775817443850118
"2019-2021",34,"F",0.000365679684336054
"2019-2021",34,"U",0.00057327141075372
"2019-2021",35,"M",0.000812379389486926
"2019-2021",35,"F",0.000390415537847616
"2019-2021",35,"U",0.000603483659931605
"2019-2021",36,"M",0.000853500991391839
"2019-2021",36,"F",0.000420780998364195
"2019-2021",36,"U",0.000639121537723913
"2019-2021",37,"M",0.000901754344385411
"2019-2021",37,"F",0.000457867682046484
"2019-2021",37,"U",0.000682034485326417
"2019-2021",38,"M",0.000959634357467422
"2019-2021",38,"F",0.000501586972984441
"2019-2021",38,"U",0.000733216523612583
"2019-2021",39,"M",0.0010296296934684
"2019-2021",39,"F",0.000551754746414597
"2019-2021",39,"U",0.0007935924496005
"2019-2021",40,"M",0.00111422901521899
"2019-2021",40,"F",0.00060818687757366
"2019-2021",40,"U",0.000864087060308346
"2019-2021",41,"M",0.00121587039004985
"2019-2021",41,"F",0.000670707427338997
"2019-2021",41,"U",0.000945609166374635
"2019-2021",42,"M",0.00133502498522899
"2019-2021",42,"F",0.0007394586733685
"2019-2021",42,"U",0.0010384461079241
"2019-2021",43,"M",0.00146960889527303
"2019-2021",43,"F",0.000814996268172368
"2019-2021",43,"U",0.00114207791290209
"2019-2021",44,"M",0.00161736745488692
"2019-2021",44,"F",0.000897903490798611
"2019-2021",44,"U",0.00125593065522282
"2019-2021",45,"M",0.00177604599877533
"2019-2021",45,"F",0.000988763620295156
"2019-2021",45,"U",0.00137943040880038
"2019-2021",46,"M",0.00194355725391296
"2019-2021",46,"F",0.00108816190135098
"2019-2021",46,"U",0.00151208313552454
"2019-2021",47,"M",0.00212274455663465
"2019-2021",47,"F",0.00119674147744948
"2019-2021",47,"U",0.00165574793104592
"2019-2021",48,"M",0.00232206933199951
"2019-2021",48,"F",0.00131521146374869
"2019-2021",48,"U",0.00181496512436369
"2019-2021",49,"M",0.00255029862799182
"2019-2021",49,"F",0.00144428456425339
"2019-2021",49,"U",0.0019944209030458
"2019-2021",50,"M",0.00281619949259519
"2019-2021",50,"F",0.00158467348296775
"2019-2021",50,"U",0.00219880145465955
"2019-2021",51,"M",0.00312834027598718
"2019-2021",51,"F",0.00173715505557697
"2019-2021",51,"U",0.00243271957234548
"2019-2021",52,"M",0.00349071927878444
"2019-2021",52,"F",0.00190398114640896
"2019-2021",52,"U",0.00269909997740809
"2019-2021",53,"M",0.00390276475204459
"2019-2021",53,"F",0.00208887864843629
"2019-2021",53,"U",0.00299917931931759
"2019-2021",54,"M",0.00436370624901776
"2019-2021",54,"F",0.00229563858631101
"2019-2021",54,"U",0.00333412085311596
"2019-2021",55,"M",0.0048727733229544
"2019-2021",55,"F",0.00252805198468558
"2019-2021",55,"U",0.0037050878338456
"2019-2021",56,"M",0.00542955917728283
"2019-2021",56,"F",0.00278996803564463
"2019-2021",56,"U",0.00411345059210307
"2019-2021",57,"M",0.00604034178546056
"2019-2021",57,"F",0.00308630518940176
"2019-2021",57,"U",0.00456438600814065
"2019-2021",58,"M",0.00671726588298563
"2019-2021",58,"F",0.00342292031035346
"2019-2021",58,"U",0.00506641170855318
"2019-2021",59,"M",0.00747267537964526
"2019-2021",59,"F",0.00380570212169209
"2019-2021",59,"U",0.00562815873697407
"2019-2021",60,"M",0.00831891418522747
"2019-2021",60,"F",0.00424053934661075
"2019-2021",60,"U",0.00625825813703745
"2019-2021",61,"M",0.00926746571695393
"2019-2021",61,"F",0.00473290069569896
"2019-2021",61,"U",0.00696471257743448
"2019-2021",62,"M",0.0103169378736551
"2019-2021",62,"F",0.00528197024652313
"2019-2021",62,"U",0.00774612237586647
"2019-2021",63,"M",0.0114560269546075
"2019-2021",63,"F",0.00588209415370322
"2019-2021",63,"U",0.00859384990162375
"2019-2021",64,"M",0.0126731742983276
"2019-2021",64,"F",0.00652749412368075
"2019-2021",64,"U",0.0094990713388287
"2019-2021",65,"M",0.0139568212433317
"2019-2021",65,"F",0.00721239186289705
"2019-2021",65,"U",0.0104529628716036
"2019-2021",66,"M",0.0152980013761703
"2019-2021",66,"F",0.00793327683028758
"2019-2021",66,"U",0.0114491586461649
"2019-2021",67,"M",0.0167197814840685
"2019-2021",67,"F",0.00871466179496683
"2019-2021",67,"U",0.0125116665970304
"2019-2021",68,"M",0.0182668335676138
"2019-2021",68,"F",0.00959996021604559
"2019-2021",68,"U",0.0136849806595873
"2019-2021",69,"M",0.0199842343343003
"2019-2021",69,"F",0.0106329395986538
"2019-2021",69,"U",0.0150139785111423
"2019-2021",70,"M",0.0219170604916224
"2019-2021",70,"F",0.0118573674479214
"2019-2021",70,"U",0.016543537829002
"2019-2021",71,"M",0.0241047347292269
"2019-2021",71,"F",0.0133099695239925
"2019-2021",71,"U",0.0183118705700941
"2019-2021",72,"M",0.0265283098323942
"2019-2021",72,"F",0.0149547753217195
"2019-2021",72,"U",0.0202883743593868
"2019-2021",73,"M",0.0291344034747911
"2019-2021",73,"F",0.0167129274401076
"2019-2021",73,"U",0.0224018500583735
"2019-2021",74,"M",0.0318691882616243
"2019-2021",74,"F",0.0185050141717054
"2019-2021",74,"U",0.0245805738216958
"2019-2021",75,"M",0.0346788367981003
"2019-2021",75,"F",0.020251623809061
"2019-2021",75,"U",0.0267528218039948
"2019-2021",76,"M",0.0375318512909088
"2019-2021",76,"F",0.0219020529748955
"2019-2021",76,"U",0.0288732317639758
"2019-2021",77,"M",0.0405910841818685
"2019-2021",77,"F",0.0236554670915757
"2019-2021",77,"U",0.031125885051268
"2019-2021",78,"M",0.0441194576083332
"2019-2021",78,"F",0.0258396874314999
"2019-2021",78,"U",0.0338130020559346
"2019-2021",79,"M",0.0483807207299343
"2019-2021",79,"F",0.0287835985385544
"2019-2021",79,"U",0.0372377795237448
"2019-2021",80,"M",0.0536386227063018
"2019-2021",80,"F",0.0328160849566245
"2019-2021",80,"U",0.0417034142004671
"2019-2021",81,"M",0.060135066045196
"2019-2021",81,"F",0.0382271086456415
"2019-2021",81,"U",0.04747917387163
"2019-2021",82,"M",0.0679504928428915
"2019-2021",82,"F",0.0450189693434942
"2019-2021",82,"U",0.0545835701009817
"2019-2021",83,"M",0.0770929781613399
"2019-2021",83,"F",0.0530650357287204
"2019-2021",83,"U",0.0629227247714722
"2019-2021",84,"M",0.0875702557085576
"2019-2021",84,"F",0.0622380683144841
"2019-2021",84,"U",0.0724022296260484
"2019-2021",85,"M",0.0993900591925608
"2019-2021",85,"F",0.0724108276139487
"2019-2021",85,"U",0.0829276764076566
"2019-2021",86,"M",0.112568142495346
"2019-2021",86,"F",0.0835118905404669
"2019-2021",86,"U",0.0944475768411406
"2019-2021",87,"M",0.127170866747751
"2019-2021",87,"F",0.0958220351517519
"2019-2021",87,"U",0.107181267475034
"2019-2021",88,"M",0.143284278665394
"2019-2021",88,"F",0.10975904133126
"2019-2021",88,"U",0.121453432315979
"2019-2021",89,"M",0.160994469039752
"2019-2021",89,"F",0.125740995708388
"2019-2021",89,"U",0.137588991242697
"2019-2021",90,"M",0.180387528662304
"2019-2021",90,"F",0.144185984912533
"2019-2021",90,"U",0.155912864133907
"2019-2021",91,"M",0.201486110324266
"2019-2021",91,"F",0.165333865663654
"2019-2021",91,"U",0.17660189580488
"2019-2021",92,"M",0.223969744683764
"2019-2021",92,"F",0.188460488463724
"2019-2021",92,"U",0.199032025755137
"2019-2021",93,"M",0.247402486093919
"2019-2021",93,"F",0.212517271592738
"2019-2021",93,"U",0.222309652182147
"2019-2021",94,"M",0.271348301887278
"2019-2021",94,"F",0.236455388845218
"2019-2021",94,"U",0.245540970162576
"2019-2021",95,"M",0.295371159396389
"2019-2021",95,"F",0.259226014015684
"2019-2021",95,"U",0.267832174773091
"2019-2021",96,"M",0.320866319646814
"2019-2021",96,"F",0.284185268718931
"2019-2021",96,"U",0.292043340207957
"2019-2021",97,"M",0.346874548064687
"2019-2021",97,"F",0.309025840082395
"2019-2021",97,"U",0.316208182687613
"2019-2021",98,"M",0.373613851660104
"2019-2021",98,"F",0.334272115013944
"2019-2021",98,"U",0.340773582910783
"2019-2021",99,"M",0.401084230433062
"2019-2021",99,"F",0.359924093513577
"2019-2021",99,"U",0.365739540877468
"2019-2021",100,"M",0.429285684383563
"2019-2021",100,"F",0.385981775581294
"2019-2021",100,"U",0.391106056587666
"2019-2021",101,"M",0.458218213511608
"2019-2021",101,"F",0.412445161217096
"2019-2021",101,"U",0.416873130041379
"2019-2021",102,"M",0.487881817817194
"2019-2021",102,"F",0.439314250420982
"2019-2021",102,"U",0.443040761238605
"2019-2021",103,"M",0.518276497300322
"2019-2021",103,"F",0.466589043192952
"2019-2021",103,"U",0.469608950179345
"2019-2021",104,"M",0.549402251960994
"2019-2021",104,"F",0.494269539533006
"2019-2021",104,"U",0.496577696863599
"2019-2021",105,"M",0.581259081799208
"2019-2021",105,"F",0.522355739441144
"2019-2021",105,"U",0.523947001291367
"2019-2021",106,"M",0.613846986814965
"2019-2021",106,"F",0.550847642917367
"2019-2021",106,"U",0.551716863462649
"2019-2021",107,"M",0.647165967008265
"2019-2021",107,"F",0.579745249961675
"2019-2021",107,"U",0.579887283377446
"2019-2021",108,"M",NA
"2019-2021",108,"F",0.609048560574066
"2019-2021",108,"U",0.608458261035756
"2019-2021",109,"M",NA
"2019-2021",109,"F",0.638757574754542
"2019-2021",109,"U",0.63742979643758
"2019-2021",110,"M",NA
"2019-2021",110,"F",0.668872292503101
"2019-2021",110,"U",0.666801889582918
"2019-2021",111,"M",NA
"2019-2021",111,"F",0.699392713819745
"2019-2021",111,"U",0.69657454047177
"2018-2020",0,"M",0.00318471337579618
"2018-2020",0,"F",0.00264986265955728
"2018-2020",0,"U",0.00292416073044984
"2018-2020",1,"M",0.000241230563313373
"2018-2020",1,"F",0.000216298649615192
"2018-2020",1,"U",0.000229150211296554
"2018-2020",2,"M",0.000177213572504314
"2018-2020",2,"F",0.000136232952511661
"2018-2020",2,"U",0.000157308599675055
"2018-2020",3,"M",0.000133677520293199
"2018-2020",3,"F",9.14912447899265e-05
"2018-2020",3,"U",0.00011319473098192
"2018-2020",4,"M",0.000106110726788564
"2018-2020",4,"F",7.16671461130519e-05
"2018-2020",4,"U",8.94154125230496e-05
"2018-2020",5,"M",9.00015120979245e-05
"2018-2020",5,"F",6.63542761434906e-05
"2018-2020",5,"U",7.85774516033276e-05
"2018-2020",6,"M",8.08383093909775e-05
"2018-2020",6,"F",6.51465401608381e-05
"2018-2020",6,"U",7.32878530365489e-05
"2018-2020",7,"M",7.51560409570951e-05
"2018-2020",7,"F",6.02816902198101e-05
"2018-2020",7,"U",6.79818477361158e-05
"2018-2020",8,"M",7.30939515167393e-05
"2018-2020",8,"F",5.31034270501997e-05
"2018-2020",8,"U",6.33914509802424e-05
"2018-2020",9,"M",7.55666848371945e-05
"2018-2020",9,"F",4.69144170425279e-05
"2018-2020",9,"U",6.16033072905866e-05
"2018-2020",10,"M",8.34888846883592e-05
"2018-2020",10,"F",4.50173265895132e-05
"2018-2020",10,"U",6.47040611914292e-05
"2018-2020",11,"M",9.77751597187299e-05
"2018-2020",11,"F",5.07136414321242e-05
"2018-2020",11,"U",7.47797652654258e-05
"2018-2020",12,"M",0.00011929352315948
"2018-2020",12,"F",6.57381314951913e-05
"2018-2020",12,"U",9.31309749743214e-05
"2018-2020",13,"M",0.000148773536217669
"2018-2020",13,"F",8.71702836932653e-05
"2018-2020",13,"U",0.00011872424785864
"2018-2020",14,"M",0.000186919162478482
"2018-2020",14,"F",0.000111228894799403
"2018-2020",14,"U",0.00015009462119637
"2018-2020",15,"M",0.000234434365516987
"2018-2020",15,"F",0.000134132761578476
"2018-2020",15,"U",0.000185777132257439
"2018-2020",16,"M",0.000292017969727298
"2018-2020",16,"F",0.000152103964086877
"2018-2020",16,"U",0.000224305731777054
"2018-2020",17,"M",0.000358073488183799
"2018-2020",17,"F",0.000162830996939027
"2018-2020",17,"U",0.000263729091539208
"2018-2020",18,"M",0.000425103700367499
"2018-2020",18,"F",0.000167772179575359
"2018-2020",18,"U",0.000300848339341172
"2018-2020",19,"M",0.000484676244830808
"2018-2020",19,"F",0.000168983268601693
"2018-2020",19,"U",0.000332266893763569
"2018-2020",20,"M",0.000528358760123061
"2018-2020",20,"F",0.000168520020620652
"2018-2020",20,"U",0.000354588173384462
"2018-2020",21,"M",0.000547746026905051
"2018-2020",21,"F",0.000168436230007162
"2018-2020",21,"U",0.000364428794697304
"2018-2020",22,"M",0.000540186953826856
"2018-2020",22,"F",0.000170369699114378
"2018-2020",22,"U",0.000361203332546776
"2018-2020",23,"M",0.000515868669051562
"2018-2020",23,"F",0.00017503009714413
"2018-2020",23,"U",0.00035056897639342
"2018-2020",24,"M",0.000486715395983639
"2018-2020",24,"F",0.000183001510800412
"2018-2020",24,"U",0.000339027582369105
"2018-2020",25,"M",0.000464651358027841
"2018-2020",25,"F",0.000194868026787529
"2018-2020",25,"U",0.000333081006606009
"2018-2020",26,"M",0.000461547776749705
"2018-2020",26,"F",0.000211207416401448
"2018-2020",26,"U",0.000339200282666388
"2018-2020",27,"M",0.00048286265121747
"2018-2020",27,"F",0.000231833286574366
"2018-2020",27,"U",0.000360126913195435
"2018-2020",28,"M",0.000521598548376031
"2018-2020",28,"F",0.000255075123366243
"2018-2020",28,"U",0.000391359096990576
"2018-2020",29,"M",0.000569326985522256
"2018-2020",29,"F",0.00027909189682209
"2018-2020",29,"U",0.000427562823471163
"2018-2020",30,"M",0.000617619479952758
"2018-2020",30,"F",0.00030204257698668
"2018-2020",30,"U",0.00046340408205634
"2018-2020",31,"M",0.000658110724677604
"2018-2020",31,"F",0.000322108883839736
"2018-2020",31,"U",0.000493593624151161
"2018-2020",32,"M",0.00068732334105422
"2018-2020",32,"F",0.000339232708249681
"2018-2020",32,"U",0.00051630545258695
"2018-2020",33,"M",0.000710065328265193
"2018-2020",33,"F",0.000356339552916553
"2018-2020",33,"U",0.000535584021750628
"2018-2020",34,"M",0.000731947251038108
"2018-2020",34,"F",0.000376643928972685
"2018-2020",34,"U",0.000556042429035148
"2018-2020",35,"M",0.000758579674100573
"2018-2020",35,"F",0.000403360347550423
"2018-2020",35,"U",0.000582293771833381
"2018-2020",36,"M",0.000795538668726245
"2018-2020",36,"F",0.000439659502888105
"2018-2020",36,"U",0.000618908445775598
"2018-2020",37,"M",0.000846558878701593
"2018-2020",37,"F",0.000486372931377964
"2018-2020",37,"U",0.000668177219753411
"2018-2020",38,"M",0.000912644735652631
"2018-2020",38,"F",0.00054086399201191
"2018-2020",38,"U",0.00072901094969143
"2018-2020",39,"M",0.000994579732087229
"2018-2020",39,"F",0.000600215385718927
"2018-2020",39,"U",0.000800046976143815
"2018-2020",40,"M",0.0010931473605135
"2018-2020",40,"F",0.000661509813428117
"2018-2020",40,"U",0.000879922639664877
"2018-2020",41,"M",0.00120906879394679
"2018-2020",41,"F",0.000721896603410945
"2018-2020",41,"U",0.000967285352616034
"2018-2020",42,"M",0.00134064253512395
"2018-2020",42,"F",0.000781115221870396
"2018-2020",42,"U",0.00106117406885696
"2018-2020",43,"M",0.00148301995239969
"2018-2020",43,"F",0.000842269815794375
"2018-2020",43,"U",0.00116113636850159
"2018-2020",44,"M",0.00163114208584165
"2018-2020",44,"F",0.000908689399451651
"2018-2020",44,"U",0.00126675382401318
"2018-2020",45,"M",0.00177994997551716
"2018-2020",45,"F",0.000983702987110807
"2018-2020",45,"U",0.00137760800785486
"2018-2020",46,"M",0.00192473779941858
"2018-2020",46,"F",0.00107060867118691
"2018-2020",46,"U",0.00149342806755827
"2018-2020",47,"M",0.00207120156087469
"2018-2020",47,"F",0.00117179372797357
"2018-2020",47,"U",0.00161829003605294
"2018-2020",48,"M",0.00223688942455526
"2018-2020",48,"F",0.00128860762171796
"2018-2020",48,"U",0.00176122292186569
"2018-2020",49,"M",0.00243999431038256
"2018-2020",49,"F",0.00142234335989609
"2018-2020",49,"U",0.00193152517442473
"2018-2020",50,"M",0.00269870913827809
"2018-2020",50,"F",0.00157429394998341
"2018-2020",50,"U",0.00213849524315761
"2018-2020",51,"M",0.00303054999159634
"2018-2020",51,"F",0.00174571522380341
"2018-2020",51,"U",0.00239108906756403
"2018-2020",52,"M",0.00343746571262729
"2018-2020",52,"F",0.00193700797316537
"2018-2020",52,"U",0.00269038485878073
"2018-2020",53,"M",0.00390583790259838
"2018-2020",53,"F",0.00214771794986618
"2018-2020",53,"U",0.00302958309958341
"2018-2020",54,"M",0.00442137132616837
"2018-2020",54,"F",0.00237735373004934
"2018-2020",54,"U",0.00340154176281838
"2018-2020",55,"M",0.00496977074799653
"2018-2020",55,"F",0.00262542388985873
"2018-2020",55,"U",0.00379911882133236
"2018-2020",56,"M",0.00553768649920424
"2018-2020",56,"F",0.00289163854290152
"2018-2020",56,"U",0.00421569636129823
"2018-2020",57,"M",0.00612915071004048
"2018-2020",57,"F",0.00317941254893038
"2018-2020",57,"U",0.00465429093978316
"2018-2020",58,"M",0.00676345031815501
"2018-2020",58,"F",0.00349541216811457
"2018-2020",58,"U",0.00512637462509471
"2018-2020",59,"M",0.00746039015597603
"2018-2020",59,"F",0.00384641404440259
"2018-2020",59,"U",0.00564370654685833
"2018-2020",60,"M",0.00823977505593264
"2018-2020",60,"F",0.00423919482174348
"2018-2020",60,"U",0.00621804583470021
"2018-2020",61,"M",0.00912044120928823
"2018-2020",61,"F",0.00468044366431532
"2018-2020",61,"U",0.00686076117164881
"2018-2020",62,"M",0.0101067310654302
"2018-2020",62,"F",0.0051755407797302
"2018-2020",62,"U",0.00757737900275961
"2018-2020",63,"M",0.0111918297625491
"2018-2020",63,"F",0.00572885873824325
"2018-2020",63,"U",0.0083689284067275
"2018-2020",64,"M",0.0123686354340456
"2018-2020",64,"F",0.00634474419017792
"2018-2020",64,"U",0.0092363227743669
"2018-2020",65,"M",0.0136300462133207
"2018-2020",65,"F",0.00702754378585734
"2018-2020",65,"U",0.010180475496492
"2018-2020",66,"M",0.0149707127405043
"2018-2020",66,"F",0.00778206514534956
"2018-2020",66,"U",0.0112030725482761
"2018-2020",67,"M",0.0164069419166242
"2018-2020",67,"F",0.00861881223264835
"2018-2020",67,"U",0.012315346965778
"2018-2020",68,"M",0.017969646992604
"2018-2020",68,"F",0.0095521309858032
"2018-2020",68,"U",0.0135349709257945
"2018-2020",69,"M",0.019690014824195
"2018-2020",69,"F",0.0105964393103744
"2018-2020",69,"U",0.0148797372225249
"2018-2020",70,"M",0.0215992322671487
"2018-2020",70,"F",0.0117661551119223
"2018-2020",70,"U",0.0163674386501689
"2018-2020",71,"M",0.0237237285156266
"2018-2020",71,"F",0.0130731422028238
"2018-2020",71,"U",0.0180128854363492
"2018-2020",72,"M",0.0260408164964731
"2018-2020",72,"F",0.0145028969203461
"2018-2020",72,"U",0.0198000969391582
"2018-2020",73,"M",0.0284988331742543
"2018-2020",73,"F",0.0160253602062451
"2018-2020",73,"U",0.0216949275558159
"2018-2020",74,"M",0.0310457410037321
"2018-2020",74,"F",0.0176102719512101
"2018-2020",74,"U",0.0236629969042494
"2018-2020",75,"M",0.033629502439668
"2018-2020",75,"F",0.0192273720459297
"2018-2020",75,"U",0.0256699246023852
"2018-2020",76,"M",0.0362247808210843
"2018-2020",76,"F",0.0208687346949513
"2018-2020",76,"U",0.027704071864222
"2018-2020",77,"M",0.039038636072231
"2018-2020",77,"F",0.0227208253530666
"2018-2020",77,"U",0.0299517360177134
"2018-2020",78,"M",0.0423977876357102
"2018-2020",78,"F",0.0250702002890235
"2018-2020",78,"U",0.0327011304324672
"2018-2020",79,"M",0.0466299438757636
"2018-2020",79,"F",0.02820424296838
"2018-2020",79,"U",0.0362413107594274
"2018-2020",80,"M",0.0520628131566317
"2018-2020",80,"F",0.032410336856693
"2018-2020",80,"U",0.040861332649537
"2018-2020",81,"M",0.0589816571157824
"2018-2020",81,"F",0.0379411057011143
"2018-2020",81,"U",0.0468144350609256
"2018-2020",82,"M",0.0673580295506196
"2018-2020",82,"F",0.0447922772049512
"2018-2020",82,"U",0.0540891492063892
"2018-2020",83,"M",0.0770228794761087
"2018-2020",83,"F",0.0528444375042911
"2018-2020",83,"U",0.0625553635037757
"2018-2020",84,"M",0.0878064926771097
"2018-2020",84,"F",0.0619776296146216
"2018-2020",84,"U",0.0720824067351079
"2018-2020",85,"M",0.0995391549384823
"2018-2020",85,"F",0.0720718965514299
"2018-2020",85,"U",0.0825396076824084
"2018-2020",86,"M",0.112110592509771
"2018-2020",86,"F",0.0830655712591807
"2018-2020",86,"U",0.0938519092533102
"2018-2020",87,"M",0.125785600609724
"2018-2020",87,"F",0.0952647957782493
"2018-2020",87,"U",0.106295179148453
"2018-2020",88,"M",0.140974871579751
"2018-2020",88,"F",0.109118785272059
"2018-2020",88,"U",0.120281790409556
"2018-2020",89,"M",0.158089424423696
"2018-2020",89,"F",0.125077075243556
"2018-2020",89,"U",0.136224421712656
"2018-2020",90,"M",0.177540278145405
"2018-2020",90,"F",0.143589201195689
"2018-2020",90,"U",0.15453575173379
"2018-2020",91,"M",0.199552758316481
"2018-2020",91,"F",0.164904354484759
"2018-2020",91,"U",0.175442199190979
"2018-2020",92,"M",0.223347815744014
"2018-2020",92,"F",0.188188109223969
"2018-2020",92,"U",0.198162743824946
"2018-2020",93,"M",0.247808383149242
"2018-2020",93,"F",0.212241352719116
"2018-2020",93,"U",0.221577316042691
"2018-2020",94,"M",0.271817138529905
"2018-2020",94,"F",0.235864697455495
"2018-2020",94,"U",0.244565590750585
"2018-2020",95,"M",0.294256759883741
"2018-2020",95,"F",0.2578587559184
"2018-2020",95,"U",0.266007242854998
"2018-2020",96,"M",0.318702550256235
"2018-2020",96,"F",0.282061430744636
"2018-2020",96,"U",0.289487184905229
"2018-2020",97,"M",0.342696510409627
"2018-2020",97,"F",0.305834187182068
"2018-2020",97,"U",0.312540811195564
"2018-2020",98,"M",0.366797274053245
"2018-2020",98,"F",0.329776689542994
"2018-2020",98,"U",0.335728256897749
"2018-2020",99,"M",0.391004841187089
"2018-2020",99,"F",0.353888937827415
"2018-2020",99,"U",0.359049522011785
"2018-2020",100,"M",0.415319211811157
"2018-2020",100,"F",0.37817093203533
"2018-2020",100,"U",0.382504606537672
"2018-2020",101,"M",0.439740385925451
"2018-2020",101,"F",0.402622672166739
"2018-2020",101,"U",0.40609351047541
"2018-2020",102,"M",0.464268363529971
"2018-2020",102,"F",0.427244158221642
"2018-2020",102,"U",0.429816233824998
"2018-2020",103,"M",0.488903144624716
"2018-2020",103,"F",0.45203539020004
"2018-2020",103,"U",0.453672776586438
"2018-2020",104,"M",0.513644729209686
"2018-2020",104,"F",0.476996368101932
"2018-2020",104,"U",0.477663138759728
"2018-2020",105,"M",0.538493117284882
"2018-2020",105,"F",0.502127091927319
"2018-2020",105,"U",0.501787320344869
"2018-2020",106,"M",0.563448308850304
"2018-2020",106,"F",0.527427561676199
"2018-2020",106,"U",0.52604532134186
"2018-2020",107,"M",0.58851030390595
"2018-2020",107,"F",0.552897777348574
"2018-2020",107,"U",0.550437141750702
"2018-2020",108,"M",NA
"2018-2020",108,"F",0.578537738944443
"2018-2020",108,"U",0.574962781571396
"2018-2020",109,"M",NA
"2018-2020",109,"F",0.604347446463807
"2018-2020",109,"U",0.599622240803939
"2018-2020",110,"M",NA
"2018-2020",110,"F",0.630326899906665
"2018-2020",110,"U",0.624415519448334
"2018-2020",111,"M",NA
"2018-2020",111,"F",0.656476099273017
"2018-2020",111,"U",0.649342617504579
"2017-2019",0,"M",0.00311394943790574
"2017-2019",0,"F",0.00258185845996924
"2017-2019",0,"U",0.00285526111885945
"2017-2019",1,"M",0.000264467973672408
"2017-2019",1,"F",0.000199881757354868
"2017-2019",1,"U",0.000233214388599793
"2017-2019",2,"M",0.000188978955680685
"2017-2019",2,"F",0.000137553692160302
"2017-2019",2,"U",0.000163997245116311
"2017-2019",3,"M",0.00014108270856273
"2017-2019",3,"F",0.000101408691158462
"2017-2019",3,"U",0.00012180232399466
"2017-2019",4,"M",0.000113311416196638
"2017-2019",4,"F",8.36477294524909e-05
"2017-2019",4,"U",9.89488425721647e-05
"2017-2019",5,"M",9.81972624596356e-05
"2017-2019",5,"F",7.64717821450855e-05
"2017-2019",5,"U",8.77560181850957e-05
"2017-2019",6,"M",8.82726488585801e-05
"2017-2019",6,"F",7.20820529446024e-05
"2017-2019",6,"U",8.05432930391017e-05
"2017-2019",7,"M",7.80844438537342e-05
"2017-2019",7,"F",6.47958406751539e-05
"2017-2019",7,"U",7.17116102273928e-05
"2017-2019",8,"M",6.9117751838354e-05
"2017-2019",8,"F",5.62187082538586e-05
"2017-2019",8,"U",6.28310273460266e-05
"2017-2019",9,"M",6.43503021311983e-05
"2017-2019",9,"F",4.95241451926194e-05
"2017-2019",9,"U",5.70138958956027e-05
"2017-2019",10,"M",6.67598240543855e-05
"2017-2019",10,"F",4.78856410055429e-05
"2017-2019",10,"U",5.73725673798467e-05
"2017-2019",11,"M",7.9323263286152e-05
"2017-2019",11,"F",5.44754417864607e-05
"2017-2019",11,"U",6.70183762892342e-05
"2017-2019",12,"M",0.000103977681657539
"2017-2019",12,"F",7.08157837441729e-05
"2017-2019",12,"U",8.77130904264538e-05
"2017-2019",13,"M",0.000139570267511995
"2017-2019",13,"F",9.35261230832106e-05
"2017-2019",13,"U",0.000117208423681587
"2017-2019",14,"M",0.000184376939178503
"2017-2019",14,"F",0.000118319467482691
"2017-2019",14,"U",0.000152514692731133
"2017-2019",15,"M",0.000236673614975749
"2017-2019",15,"F",0.000140908824613057
"2017-2019",15,"U",0.000190642214242628
"2017-2019",16,"M",0.000294734396150763
"2017-2019",16,"F",0.000157011385001019
"2017-2019",16,"U",0.000228602388838039
"2017-2019",17,"M",0.000356021825104425
"2017-2019",17,"F",0.000164212525884704
"2017-2019",17,"U",0.000263890742453489
"2017-2019",18,"M",0.00041591210739821
"2017-2019",18,"F",0.000164900315944956
"2017-2019",18,"U",0.000295247379242502
"2017-2019",19,"M",0.000469450808527789
"2017-2019",19,"F",0.000162223948447041
"2017-2019",19,"U",0.000321609642575482
"2017-2019",20,"M",0.000511683493985133
"2017-2019",20,"F",0.000159332616653431
"2017-2019",20,"U",0.000341914875819675
"2017-2019",21,"M",0.000537670802633834
"2017-2019",21,"F",0.000159370097302857
"2017-2019",21,"U",0.000355105723387188
"2017-2019",22,"M",0.000545668928362054
"2017-2019",22,"F",0.000164331864431488
"2017-2019",22,"U",0.000361248651325179
"2017-2019",23,"M",0.000541063770362593
"2017-2019",23,"F",0.000173651377073613
"2017-2019",23,"U",0.000362917520170997
"2017-2019",24,"M",0.000530205923684128
"2017-2019",24,"F",0.000186415436843186
"2017-2019",24,"U",0.000363025457370134
"2017-2019",25,"M",0.000519445983375692
"2017-2019",25,"F",0.000201710845354495
"2017-2019",25,"U",0.000364485590368401
"2017-2019",26,"M",0.000515114540373907
"2017-2019",26,"F",0.000218625231738022
"2017-2019",26,"U",0.000370200629890262
"2017-2019",27,"M",0.00052112168806925
"2017-2019",27,"F",0.000236346354629107
"2017-2019",27,"U",0.000381812863420781
"2017-2019",28,"M",0.000536676553542969
"2017-2019",28,"F",0.000254256439056427
"2017-2019",28,"U",0.000398516649012666
"2017-2019",29,"M",0.000560448152853775
"2017-2019",29,"F",0.000271760052996114
"2017-2019",29,"U",0.000419225093252091
"2017-2019",30,"M",0.000591105502060147
"2017-2019",30,"F",0.000288261764424108
"2017-2019",30,"U",0.000442851302725027
"2017-2019",31,"M",0.000627315969626455
"2017-2019",31,"F",0.000303183098264325
"2017-2019",31,"U",0.000468317051466757
"2017-2019",32,"M",0.000667619449052161
"2017-2019",32,"F",0.000317257544786116
"2017-2019",32,"U",0.000495214717274025
"2017-2019",33,"M",0.000710339754922508
"2017-2019",33,"F",0.000333442466583941
"2017-2019",33,"U",0.000524273397866267
"2017-2019",34,"M",0.000753779771275823
"2017-2019",34,"F",0.000354910642295265
"2017-2019",34,"U",0.000556332299670733
"2017-2019",35,"M",0.000796242382150351
"2017-2019",35,"F",0.000384834850557511
"2017-2019",35,"U",0.000592230629114588
"2017-2019",36,"M",0.000836095565658715
"2017-2019",36,"F",0.000426333695476037
"2017-2019",36,"U",0.000632811121154516
"2017-2019",37,"M",0.000875182336651266
"2017-2019",37,"F",0.000479633682461084
"2017-2019",37,"U",0.000679104880740863
"2017-2019",38,"M",0.000920498010364847
"2017-2019",38,"F",0.000540673315858694
"2017-2019",38,"U",0.000732422301609256
"2017-2019",39,"M",0.000979454845715515
"2017-2019",39,"F",0.000605044098713158
"2017-2019",39,"U",0.000794096378602416
"2017-2019",40,"M",0.00105946510161946
"2017-2019",40,"F",0.000668337534068964
"2017-2019",40,"U",0.000865460106563272
"2017-2019",41,"M",0.00116775575230093
"2017-2019",41,"F",0.000726260268431704
"2017-2019",41,"U",0.000947816530878132
"2017-2019",42,"M",0.00130435082958238
"2017-2019",42,"F",0.000778995150357933
"2017-2019",42,"U",0.0010413044118069
"2017-2019",43,"M",0.00145991748833899
"2017-2019",43,"F",0.0008325397731899
"2017-2019",43,"U",0.00114455006204902
"2017-2019",44,"M",0.0016244975476111
"2017-2019",44,"F",0.000893280339451679
"2017-2019",44,"U",0.0012560787148884
"2017-2019",45,"M",0.0017881328264389
"2017-2019",45,"F",0.000967603051667261
"2017-2019",45,"U",0.00137441560360881
"2017-2019",46,"M",0.00194134376182822
"2017-2019",46,"F",0.00106175894565064
"2017-2019",46,"U",0.00149824834084912
"2017-2019",47,"M",0.00208874868322153
"2017-2019",47,"F",0.00117801766523553
"2017-2019",47,"U",0.0016310474911016
"2017-2019",48,"M",0.00225102949451347
"2017-2019",48,"F",0.0013141123331542
"2017-2019",48,"U",0.00178173346205526
"2017-2019",49,"M",0.0024497419548982
"2017-2019",49,"F",0.00146752928628144
"2017-2019",49,"U",0.00195952313180047
"2017-2019",50,"M",0.00270644182356919
"2017-2019",50,"F",0.00163575486149161
"2017-2019",50,"U",0.002173633378427
"2017-2019",51,"M",0.00304190050008916
"2017-2019",51,"F",0.00181637310041835
"2017-2019",51,"U",0.00243294237027571
"2017-2019",52,"M",0.00345884911249181
"2017-2019",52,"F",0.00200921525414202
"2017-2019",52,"U",0.00273853795144154
"2017-2019",53,"M",0.0039419785172837
"2017-2019",53,"F",0.00221635978319139
"2017-2019",53,"U",0.00308371764177538
"2017-2019",54,"M",0.00447519521133911
"2017-2019",54,"F",0.00243998285285327
"2017-2019",54,"U",0.00346144025137775
"2017-2019",55,"M",0.00504240569153276
"2017-2019",55,"F",0.00268226062841481
"2017-2019",55,"U",0.00386466459034959
"2017-2019",56,"M",0.00562838318135772
"2017-2019",56,"F",0.00294545269634364
"2017-2019",56,"U",0.00428680567464882
"2017-2019",57,"M",0.006233833436374
"2017-2019",57,"F",0.00323335212622552
"2017-2019",57,"U",0.00472966468756027
"2017-2019",58,"M",0.00687344509770495
"2017-2019",58,"F",0.00355109782011448
"2017-2019",58,"U",0.0052024027735824
"2017-2019",59,"M",0.00756238152000069
"2017-2019",59,"F",0.00390387437055288
"2017-2019",59,"U",0.00571443094503425
"2017-2019",60,"M",0.00831580605791205
"2017-2019",60,"F",0.00429686637008365
"2017-2019",60,"U",0.0062751602142356
"2017-2019",61,"M",0.00914855125207859
"2017-2019",61,"F",0.00473531810428733
"2017-2019",61,"U",0.00689393507064336
"2017-2019",62,"M",0.0100704996853485
"2017-2019",62,"F",0.00522536704346114
"2017-2019",62,"U",0.00757910462459047
"2017-2019",63,"M",0.01108772345326
"2017-2019",63,"F",0.00577383823326548
"2017-2019",63,"U",0.00833825174158863
"2017-2019",64,"M",0.0122061966323855
"2017-2019",64,"F",0.00638757440618706
"2017-2019",64,"U",0.00917893957667213
"2017-2019",65,"M",0.0134318932992968
"2017-2019",65,"F",0.0070734182947124
"2017-2019",65,"U",0.010108731284875
"2017-2019",66,"M",0.0147710074182223
"2017-2019",66,"F",0.00783791965449105
"2017-2019",66,"U",0.0111349299368704
"2017-2019",67,"M",0.0162324501723122
"2017-2019",67,"F",0.00868400783691833
"2017-2019",67,"U",0.0122616246614491
"2017-2019",68,"M",0.0178269654087455
"2017-2019",68,"F",0.00961217036414062
"2017-2019",68,"U",0.013490736902044
"2017-2019",69,"M",0.0195653313039977
"2017-2019",69,"F",0.0106228490181784
"2017-2019",69,"U",0.0148241474972007
"2017-2019",70,"M",0.0214583260345444
"2017-2019",70,"F",0.0117164855810524
"2017-2019",70,"U",0.0162637372854649
"2017-2019",71,"M",0.0235133106685138
"2017-2019",71,"F",0.0128934114269883
"2017-2019",71,"U",0.0178102021499014
"2017-2019",72,"M",0.0257023693624959
"2017-2019",72,"F",0.0141528181226287
"2017-2019",72,"U",0.0194520049492089
"2017-2019",73,"M",0.0279767747881311
"2017-2019",73,"F",0.0154932248092998
"2017-2019",73,"U",0.0211703917140986
"2017-2019",74,"M",0.0302875306318553
"2017-2019",74,"F",0.0169131419373357
"2017-2019",74,"U",0.0229465151989034
"2017-2019",75,"M",0.0325856405801036
"2017-2019",75,"F",0.0184110799570702
"2017-2019",75,"U",0.0247615281579554
"2017-2019",76,"M",0.0348534751095819
"2017-2019",76,"F",0.0200053260799189
"2017-2019",76,"U",0.0266202443374214
"2017-2019",77,"M",0.0373464119456416
"2017-2019",77,"F",0.0218862985859682
"2017-2019",77,"U",0.0287334157457253
"2017-2019",78,"M",0.0404603985033634
"2017-2019",78,"F",0.0243330449438547
"2017-2019",78,"U",0.0314178306880282
"2017-2019",79,"M",0.044592543930801
"2017-2019",79,"F",0.0276253450948481
"2017-2019",79,"U",0.0349911538025227
"2017-2019",80,"M",0.0501399573760072
"2017-2019",80,"F",0.0320429789802172
"2017-2019",80,"U",0.0397710497274001
"2017-2019",81,"M",0.0574357581756202
"2017-2019",81,"F",0.037826217302676
"2017-2019",81,"U",0.0460268370885308
"2017-2019",82,"M",0.0663401409662859
"2017-2019",82,"F",0.0449233327987379
"2017-2019",82,"U",0.0536705272644663
"2017-2019",83,"M",0.0765013341343362
"2017-2019",83,"F",0.0531517238522009
"2017-2019",83,"U",0.0624539854679412
"2017-2019",84,"M",0.0875665662252999
"2017-2019",84,"F",0.0623281715150105
"2017-2019",84,"U",0.0721283215052477
"2017-2019",85,"M",0.0991830657847059
"2017-2019",85,"F",0.0722694568391123
"2017-2019",85,"U",0.0824446451826777
"2017-2019",86,"M",0.111096680644553
"2017-2019",86,"F",0.0828718564262662
"2017-2019",86,"U",0.0932409528784202
"2017-2019",87,"M",0.123675545732267
"2017-2019",87,"F",0.0945332633121391
"2017-2019",87,"U",0.10490349470878
"2017-2019",88,"M",0.13752985784695
"2017-2019",88,"F",0.107846693030914
"2017-2019",88,"U",0.11803178461471
"2017-2019",89,"M",0.153270355762207
"2017-2019",89,"F",0.123405597994413
"2017-2019",89,"U",0.133225814033082
"2017-2019",90,"M",0.171507778251643
"2017-2019",90,"F",0.14180343061446
"2017-2019",90,"U",0.151085574400768
"2017-2019",91,"M",0.19265278920371
"2017-2019",91,"F",0.163380538332512
"2017-2019",91,"U",0.171975201186665
"2017-2019",92,"M",0.216033891639711
"2017-2019",92,"F",0.187108279703679
"2017-2019",92,"U",0.19498313701781
"2017-2019",93,"M",0.240615391910719
"2017-2019",93,"F",0.211497285854164
"2017-2019",93,"U",0.218768495482149
"2017-2019",94,"M",0.265361321916663
"2017-2019",94,"F",0.235057840715422
"2017-2019",94,"U",0.24199006663406
"2017-2019",95,"M",0.28923571355747
"2017-2019",95,"F",0.256300228218906
"2017-2019",95,"U",0.263306640527924
"2017-2019",96,"M",0.315553527527797
"2017-2019",96,"F",0.279991366186587
"2017-2019",96,"U",0.287009927222941
"2017-2019",97,"M",0.342035751629406
"2017-2019",97,"F",0.302854028065415
"2017-2019",97,"U",0.310149403495991
"2017-2019",98,"M",0.369200340506854
"2017-2019",98,"F",0.325633034690226
"2017-2019",98,"U",0.333395639655572
"2017-2019",99,"M",0.39704729416014
"2017-2019",99,"F",0.34832838606102
"2017-2019",99,"U",0.356748635701685
"2017-2019",100,"M",0.425576612589263
"2017-2019",100,"F",0.370940082177796
"2017-2019",100,"U",0.38020839163433
"2017-2019",101,"M",0.454788295794225
"2017-2019",101,"F",0.393468123040554
"2017-2019",101,"U",0.403774907453506
"2017-2019",102,"M",0.484682343775025
"2017-2019",102,"F",0.415912508649295
"2017-2019",102,"U",0.427448183159214
"2017-2019",103,"M",0.515258756531663
"2017-2019",103,"F",0.438273239004018
"2017-2019",103,"U",0.451228218751453
"2017-2019",104,"M",0.54651753406414
"2017-2019",104,"F",0.460550314104724
"2017-2019",104,"U",0.475115014230224
"2017-2019",105,"M",0.578458676372454
"2017-2019",105,"F",0.482743733951412
"2017-2019",105,"U",0.499108569595527
"2017-2019",106,"M",0.611082183456607
"2017-2019",106,"F",0.504853498544082
"2017-2019",106,"U",0.523208884847361
"2017-2019",107,"M",NA
"2017-2019",107,"F",0.526879607882735
"2017-2019",107,"U",0.547415959985727
"2017-2019",108,"M",NA
"2017-2019",108,"F",0.548822061967371
"2017-2019",108,"U",0.571729795010624
"2017-2019",109,"M",NA
"2017-2019",109,"F",0.570680860797989
"2017-2019",109,"U",0.596150389922053
"2017-2019",110,"M",NA
"2017-2019",110,"F",0.592456004374589
"2017-2019",110,"U",0.620677744720014
"2017-2019",111,"M",NA
"2017-2019",111,"F",0.614147492697172
"2017-2019",111,"U",0.645311859404507
"2016-2018",0,"M",0.00313199105145414
"2016-2018",0,"F",0.00265103398215286
"2016-2018",0,"U",0.0028982951430554
"2016-2018",1,"M",0.000262335430215222
"2016-2018",1,"F",0.000191892173193435
"2016-2018",1,"U",0.000228269312344918
"2016-2018",2,"M",0.000182729500848257
"2016-2018",2,"F",0.000111396531187504
"2016-2018",2,"U",0.000148122514422758
"2016-2018",3,"M",0.00013228632645515
"2016-2018",3,"F",7.68901482230989e-05
"2016-2018",3,"U",0.000105403040465616
"2016-2018",4,"M",0.00010334160771794
"2016-2018",4,"F",7.24773160187941e-05
"2016-2018",4,"U",8.84060603245428e-05
"2016-2018",5,"M",8.82310453186253e-05
"2016-2018",5,"F",8.2262326292677e-05
"2016-2018",5,"U",8.54267438496829e-05
"2016-2018",6,"M",7.92905464751825e-05
"2016-2018",6,"F",9.03499539102335e-05
"2016-2018",6,"U",8.47606034104609e-05
"2016-2018",7,"M",7.07678032116523e-05
"2016-2018",7,"F",8.53173705906387e-05
"2016-2018",7,"U",7.78737472755538e-05
"2016-2018",8,"M",6.34950851828302e-05
"2016-2018",8,"F",7.114559692706e-05
"2016-2018",8,"U",6.71524640316273e-05
"2016-2018",9,"M",5.97212043455897e-05
"2016-2018",9,"F",5.5129488459487e-05
"2016-2018",9,"U",5.73323041595246e-05
"2016-2018",10,"M",6.16949726590025e-05
"2016-2018",10,"F",4.45639007299229e-05
"2016-2018",10,"U",5.31488181428426e-05
"2016-2018",11,"M",7.16648684273898e-05
"2016-2018",11,"F",4.67412796481301e-05
"2016-2018",11,"U",5.93362055160163e-05
"2016-2018",12,"M",9.14366202241822e-05
"2016-2018",12,"F",6.57564975175253e-05
"2016-2018",12,"U",7.88359657835795e-05
"2016-2018",13,"M",0.000121500385944801
"2016-2018",13,"F",9.62032715462667e-05
"2016-2018",13,"U",0.000109262834090417
"2016-2018",14,"M",0.000162103094743321
"2016-2018",14,"F",0.000130918701649682
"2016-2018",14,"U",0.000147246708874631
"2016-2018",15,"M",0.000213491675764613
"2016-2018",15,"F",0.000162739887735437
"2016-2018",15,"U",0.000189417488565941
"2016-2018",16,"M",0.000275908216241025
"2016-2018",16,"F",0.000184510606814891
"2016-2018",16,"U",0.000232405804492959
"2016-2018",17,"M",0.000347432261274142
"2016-2018",17,"F",0.000192056827722896
"2016-2018",17,"U",0.0002731696215487
"2016-2018",18,"M",0.00042058394235034
"2016-2018",18,"F",0.000188871069470797
"2016-2018",18,"U",0.000309508406218524
"2016-2018",19,"M",0.000487002341994508
"2016-2018",19,"F",0.000179660836431147
"2016-2018",19,"U",0.000339354985120812
"2016-2018",20,"M",0.000538326542727415
"2016-2018",20,"F",0.000169133632973849
"2016-2018",20,"U",0.000360642184872017
"2016-2018",21,"M",0.00056622027797685
"2016-2018",21,"F",0.000161989142672934
"2016-2018",21,"U",0.000371311916858951
"2016-2018",22,"M",0.00056757327366109
"2016-2018",22,"F",0.000161269040610717
"2016-2018",22,"U",0.000371232064240466
"2016-2018",23,"M",0.000550935135160584
"2016-2018",23,"F",0.000166315765934128
"2016-2018",23,"U",0.000364567607563239
"2016-2018",24,"M",0.00052643312596526
"2016-2018",24,"F",0.000175971226924056
"2016-2018",24,"U",0.000356064952813676
"2016-2018",25,"M",0.000504194509565489
"2016-2018",25,"F",0.00018907733186168
"2016-2018",25,"U",0.000350470505978474
"2016-2018",26,"M",0.000494308866920818
"2016-2018",26,"F",0.000204478275869557
"2016-2018",26,"U",0.000352511861112778
"2016-2018",27,"M",0.000502306192811589
"2016-2018",27,"F",0.000221294961915028
"2016-2018",27,"U",0.000364640368593005
"2016-2018",28,"M",0.000524861087372207
"2016-2018",28,"F",0.000239185700762812
"2016-2018",28,"U",0.000384886574956333
"2016-2018",29,"M",0.000557630722416194
"2016-2018",29,"F",0.000257870547903436
"2016-2018",29,"U",0.000410773104596809
"2016-2018",30,"M",0.000596272269756871
"2016-2018",30,"F",0.000277069558827225
"2016-2018",30,"U",0.000439822581908307
"2016-2018",31,"M",0.00063646226093086
"2016-2018",31,"F",0.000296513878968683
"2016-2018",31,"U",0.000469574183974559
"2016-2018",32,"M",0.000675375096438031
"2016-2018",32,"F",0.000316792686850277
"2016-2018",32,"U",0.000498847775621872
"2016-2018",33,"M",0.000712724168639428
"2016-2018",33,"F",0.00033994958663517
"2016-2018",33,"U",0.000528634076293952
"2016-2018",34,"M",0.000748468810085029
"2016-2018",34,"F",0.000368169065851588
"2016-2018",34,"U",0.000560134085901742
"2016-2018",35,"M",0.000782568353324744
"2016-2018",35,"F",0.000403635612027643
"2016-2018",35,"U",0.000594548804356141
"2016-2018",36,"M",0.000815037284513907
"2016-2018",36,"F",0.000448487178596972
"2016-2018",36,"U",0.000633081169885571
"2016-2018",37,"M",0.000848834456199855
"2016-2018",37,"F",0.000502377503830156
"2016-2018",37,"U",0.000677037597502358
"2016-2018",38,"M",0.000891284217252588
"2016-2018",38,"F",0.00056127707781515
"2016-2018",38,"U",0.000727877923178405
"2016-2018",39,"M",0.000950064189053707
"2016-2018",39,"F",0.000620858328233871
"2016-2018",39,"U",0.000787074398291228
"2016-2018",40,"M",0.00103285199298493
"2016-2018",40,"F",0.000676793682768435
"2016-2018",40,"U",0.000856099274218492
"2016-2018",41,"M",0.00114712466015144
"2016-2018",41,"F",0.000724895826042143
"2016-2018",41,"U",0.000936401455967934
"2016-2018",42,"M",0.00129256127465217
"2016-2018",42,"F",0.000766429931267015
"2016-2018",42,"U",0.00102852225841646
"2016-2018",43,"M",0.00145871111161263
"2016-2018",43,"F",0.000809744147184421
"2016-2018",43,"U",0.00113182400475902
"2016-2018",44,"M",0.00163444645397522
"2016-2018",44,"F",0.00086365998971276
"2016-2018",44,"U",0.00124559022419261
"2016-2018",45,"M",0.00180863958468205
"2016-2018",45,"F",0.000936998974770331
"2016-2018",45,"U",0.00136910444591409
"2016-2018",46,"M",0.00197067420315414
"2016-2018",46,"F",0.00103835400339733
"2016-2018",46,"U",0.00150177464867476
"2016-2018",47,"M",0.00212499799517464
"2016-2018",47,"F",0.00116958402976313
"2016-2018",47,"U",0.00164667452492951
"2016-2018",48,"M",0.00229322301826282
"2016-2018",48,"F",0.001324875140803
"2016-2018",48,"U",0.001811054594645
"2016-2018",49,"M",0.00249789506839378
"2016-2018",49,"F",0.0014979960209805
"2016-2018",49,"U",0.00200239259638561
"2016-2018",50,"M",0.0027615599415419
"2016-2018",50,"F",0.00168271535475865
"2016-2018",50,"U",0.00222816626871516
"2016-2018",51,"M",0.00310599943685883
"2016-2018",51,"F",0.00187306981696656
"2016-2018",51,"U",0.00249563207693232
"2016-2018",52,"M",0.00353542342655163
"2016-2018",52,"F",0.0020692598608364
"2016-2018",52,"U",0.00280695720121868
"2016-2018",53,"M",0.00403646985588466
"2016-2018",53,"F",0.00227764971800486
"2016-2018",53,"U",0.00315921953664031
"2016-2018",54,"M",0.004595012673298
"2016-2018",54,"F",0.00250487161047349
"2016-2018",54,"U",0.00354927570499679
"2016-2018",55,"M",0.00519692582723215
"2016-2018",55,"F",0.00275755776024419
"2016-2018",55,"U",0.00397398232808808
"2016-2018",56,"M",0.00582866205943687
"2016-2018",56,"F",0.00304203288503503
"2016-2018",56,"U",0.00443025954540344
"2016-2018",57,"M",0.00648731373292961
"2016-2018",57,"F",0.00335896902990814
"2016-2018",57,"U",0.00491619510523044
"2016-2018",58,"M",0.00717931087319076
"2016-2018",58,"F",0.00370407727863333
"2016-2018",58,"U",0.00543090148564503
"2016-2018",59,"M",0.00791140051570977
"2016-2018",59,"F",0.00407290029227318
"2016-2018",59,"U",0.00597352595390039
"2016-2018",60,"M",0.00869032969597672
"2016-2018",60,"F",0.00446098073189079
"2016-2018",60,"U",0.00654321577725037
"2016-2018",61,"M",0.00952336448693273
"2016-2018",61,"F",0.00486502252416467
"2016-2018",61,"U",0.00714016419566715
"2016-2018",62,"M",0.0104255372996836
"2016-2018",62,"F",0.00529910557017229
"2016-2018",62,"U",0.00778021530017551
"2016-2018",63,"M",0.0114178590878328
"2016-2018",63,"F",0.00579068583049105
"2016-2018",63,"U",0.00849126123793183
"2016-2018",64,"M",0.0125214945938586
"2016-2018",64,"F",0.00636756334439961
"2016-2018",64,"U",0.0093015040739354
"2016-2018",65,"M",0.0137576085602389
"2016-2018",65,"F",0.00705753815117629
"2016-2018",65,"U",0.0102391458731852
"2016-2018",66,"M",0.0151453890924172
"2016-2018",66,"F",0.00788511976610244
"2016-2018",66,"U",0.0113291751037109
"2016-2018",67,"M",0.016679598388302
"2016-2018",67,"F",0.00883415569444724
"2016-2018",67,"U",0.0125568688343039
"2016-2018",68,"M",0.0183385242713186
"2016-2018",68,"F",0.00986106841421127
"2016-2018",68,"U",0.013880720258422
"2016-2018",69,"M",0.0201001459683952
"2016-2018",69,"F",0.010921766680258
"2016-2018",69,"U",0.0152587208563862
"2016-2018",70,"M",0.0219424427064599
"2016-2018",70,"F",0.0119721592474509
"2016-2018",70,"U",0.0166488621085176
"2016-2018",71,"M",0.0238458225987761
"2016-2018",71,"F",0.0129762648324496
"2016-2018",71,"U",0.0180158970621163
"2016-2018",72,"M",0.0258157686463998
"2016-2018",72,"F",0.0139818262764592
"2016-2018",72,"U",0.0193943825798549
"2016-2018",73,"M",0.0278725566887369
"2016-2018",73,"F",0.0150859791617682
"2016-2018",73,"U",0.020860056030001
"2016-2018",74,"M",0.0300366537603282
"2016-2018",74,"F",0.0163864974641594
"2016-2018",74,"U",0.0224891870324507
"2016-2018",75,"M",0.0323285268957135
"2016-2018",75,"F",0.017981155159415
"2016-2018",75,"U",0.0243580452070994
"2016-2018",76,"M",0.0347882985743996
"2016-2018",76,"F",0.0199676082600222
"2016-2018",76,"U",0.0265482930966766
"2016-2018",77,"M",0.0376271664450394
"2016-2018",77,"F",0.0224424860608942
"2016-2018",77,"U",0.0291885316463487
"2016-2018",78,"M",0.0411444136689113
"2016-2018",78,"F",0.0255018892066191
"2016-2018",78,"U",0.0324315300850911
"2016-2018",79,"M",0.0456400513867373
"2016-2018",79,"F",0.0292419139727745
"2016-2018",79,"U",0.0364302573797619
"2016-2018",80,"M",0.0514140907392381
"2016-2018",80,"F",0.0337586566349372
"2016-2018",80,"U",0.0413376824972185
"2016-2018",81,"M",0.058718810400344
"2016-2018",81,"F",0.0391485095938754
"2016-2018",81,"U",0.0472927627256713
"2016-2018",82,"M",0.0674537162816034
"2016-2018",82,"F",0.0455100538005941
"2016-2018",82,"U",0.0543309002908227
"2016-2018",83,"M",0.0773602004983178
"2016-2018",83,"F",0.0529428511207924
"2016-2018",83,"U",0.0624410837328536
"2016-2018",84,"M",0.0881789093459949
"2016-2018",84,"F",0.0615464680471258
"2016-2018",84,"U",0.0716120826594664
"2016-2018",85,"M",0.0996504891201428
"2016-2018",85,"F",0.0714204710722496
"2016-2018",85,"U",0.0818326666783636
"2016-2018",86,"M",0.111590033913408
"2016-2018",86,"F",0.0826662978667637
"2016-2018",86,"U",0.0931130895894314
"2016-2018",87,"M",0.124282402963788
"2016-2018",87,"F",0.0953971932226728
"2016-2018",87,"U",0.105599170314049
"2016-2018",88,"M",0.138195188256215
"2016-2018",88,"F",0.109730994754052
"2016-2018",88,"U",0.119489460904787
"2016-2018",89,"M",0.153796390912713
"2016-2018",89,"F",0.125785550358268
"2016-2018",89,"U",0.134982631483256
"2016-2018",90,"M",0.171554012055303
"2016-2018",90,"F",0.143678707932686
"2016-2018",90,"U",0.152277352171066
"2016-2018",91,"M",0.191810712831292
"2016-2018",91,"F",0.163451039922374
"2016-2018",91,"U",0.171492640907608
"2016-2018",92,"M",0.214231218146129
"2016-2018",92,"F",0.184725152917241
"2016-2018",92,"U",0.192316694569871
"2016-2018",93,"M",0.238252096325771
"2016-2018",93,"F",0.206982988863574
"2016-2018",93,"U",0.21429271902551
"2016-2018",94,"M",0.263309743762052
"2016-2018",94,"F",0.229706383705671
"2016-2018",94,"U",0.236963810879925
"2016-2018",95,"M",0.288840556846806
"2016-2018",95,"F",0.252377173387828
"2016-2018",95,"U",0.25987306673852
"2016-2018",96,"M",0.316647981159103
"2016-2018",96,"F",0.2766534298873
"2016-2018",96,"U",0.284482522832882
"2016-2018",97,"M",0.34549216244703
"2016-2018",97,"F",0.301395237710965
"2016-2018",97,"U",0.309787038521574
"2016-2018",98,"M",0.375654884093159
"2016-2018",98,"F",0.326861667529319
"2016-2018",98,"U",0.336015053795228
"2016-2018",99,"M",0.407136146097486
"2016-2018",99,"F",0.353052719342359
"2016-2018",99,"U",0.363166568653841
"2016-2018",100,"M",0.439935948460014
"2016-2018",100,"F",0.379968393150089
"2016-2018",100,"U",0.391241583097414
"2016-2018",101,"M",0.474054291180744
"2016-2018",101,"F",0.407608688952506
"2016-2018",101,"U",0.420240097125947
"2016-2018",102,"M",0.509491174259672
"2016-2018",102,"F",0.435973606749612
"2016-2018",102,"U",0.45016211073944
"2016-2018",103,"M",0.546246597696802
"2016-2018",103,"F",0.465063146541406
"2016-2018",103,"U",0.481007623937893
"2016-2018",104,"M",0.584320561492132
"2016-2018",104,"F",0.494877308327887
"2016-2018",104,"U",0.512776636721305
"2016-2018",105,"M",0.623713065645661
"2016-2018",105,"F",0.525416092109058
"2016-2018",105,"U",0.545469149089678
"2016-2018",106,"M",0.664424110157392
"2016-2018",106,"F",0.556679497884915
"2016-2018",106,"U",0.579085161043011
"2016-2018",107,"M",0.706453695027322
"2016-2018",107,"F",0.588667525655461
"2016-2018",107,"U",0.613624672581304
"2016-2018",108,"M",NA
"2016-2018",108,"F",0.621380175420696
"2016-2018",108,"U",0.649087683704557
"2016-2018",109,"M",NA
"2016-2018",109,"F",0.654817447180618
"2016-2018",109,"U",0.68547419441277
"2016-2018",110,"M",NA
"2016-2018",110,"F",0.688979340935228
"2016-2018",110,"U",0.722784204705943
"2016-2018",111,"M",NA
"2016-2018",111,"F",0.723865856684528
"2016-2018",111,"U",0.761017714584076
...@@ -43,6 +43,35 @@ rm(AT.pop.obs.M, AT.pop.obs.F, AT.pop.obs.U) ...@@ -43,6 +43,35 @@ rm(AT.pop.obs.M, AT.pop.obs.F, AT.pop.obs.U)
############################################################################### ###############################################################################
AT.pop.obsGrad = utils::read.csv(system.file("extdata", "Austria_Population_YearlyGraduated.csv", package = "MortalityTables"));
mort.AT.observedGraduated = array(
data = c(mortalityTable.NA),
dim = c(length(unique(AT.pop.obsGrad$Geschlecht)), length(unique(AT.pop.obsGrad$Jahr))),
dimnames = list(Geschlecht = unique(AT.pop.obsGrad$Geschlecht), Jahr = unique(AT.pop.obsGrad$Jahr))
)
for (sx in dimnames(mort.AT.observedGraduated)$Geschlecht) {
for (y in dimnames(mort.AT.observedGraduated)$Jahr) {
qx = AT.pop.obsGrad %>%
filter(Geschlecht == sx, Jahr == y, !is.na(qx)) %>%
arrange(Alter)
mort.AT.observedGraduated[[sx,y]] = mortalityTable.period(
name = paste0("Österreich ", sx, " ", y),
deathProbs = qx$qx,
ages = qx$Alter,
data = list(
dim = list(sex = sx, collar = "Gesamtbevölkerung", type = "jährlich ausgeglichen", data = "official", year = y)
)
)
}
}
rm(AT.pop.obsGrad)
###############################################################################
# mortalityTables.load("Austria*") # mortalityTables.load("Austria*")
# plot(mort.AT.forecast.male, mort.AT.forecast.female, AVOe1996R.male, AVOe2005R.male, AVOe1996R.female, AVOe2005R.female, YOB = 2000) # plot(mort.AT.forecast.male, mort.AT.forecast.female, AVOe1996R.male, AVOe2005R.male, AVOe1996R.female, AVOe2005R.female, YOB = 2000)
# plotMortalityTrend(mort.AT.forecast.male, mort.AT.forecast.female, AVOe1996R.male, AVOe2005R.male, AVOe1996R.female, AVOe2005R.female, Period = 2002) # plotMortalityTrend(mort.AT.forecast.male, mort.AT.forecast.female, AVOe1996R.male, AVOe2005R.male, AVOe1996R.female, AVOe2005R.female, Period = 2002)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment