Rivi 128:
Rivi 128:
objects.latest("Op_fi4305", code_name = "alusta") # [[Pneumokokkirokote]]
objects.latest("Op_en6353 ", code_name = "initiate ") # [[:op_en:Epidemiological modelling ]] ovariables VacCar, VacIPD
objects.latest("Op_en6007", code_name = "answer") # [[OpasnetUtils/Drafts]]
objects.latest("Op_en6007", code_name = "answer") # [[OpasnetUtils/Drafts]]
Rivi 264:
Rivi 264:
=== Funktioiden alustus ===
=== Funktioiden alustus ===
<rcode name="alusta" label="Alusta funktiot" embed=1>
Mallissa käytetään samoja funktioita ja ovariableja kuin englanninkielisessä mallissa . Katso siis [[:op_en :Epidemiological modelling #Initiate functions ]].
library(OpasnetUtils)
#S1.4. The R-functions
###############################################################################
##
## R code for the core methods introduced in
## Markku Nurhonen and Kari Auranen:
## "Optimal serotype compositions for pneumococcal conjugate
## vaccination under serotype replacement",
## PLoS Computational Biology, 2014.
##
###############################################################################
## List of arguments common to most functions:
##
## IPD = matrix of IPD incidences by age class (columns) and serotype (rows)
## Car = corresponding matrix of carriage incidences
## VT_rows = vector of the row numbers in matrices IPD and Car
## corresponding to vaccine types (VT_rows=0 for no vaccination)
## p = proportion of lost VT carriage which is replaced by NVT carriage
## q = proportion of VT carriage lost either due to elimination or replacement
##
## This code includes 4 functions:
## Vaccination, NextVT, OptimalSequence and OptimalVacc.
##
Vaccination<-function(IPD,Car,VT_rows,p,q) {
##
## Result:
## A list of 2 matrices: IPD and carriage incidences
## after vaccination (corresponding to matrices IPD and Car).
## [Markku Nurhonen 2013]
##
if (VT_rows[1]>0) {
IPD<-as.matrix(IPD); Car<-as.matrix(Car)
# Post vaccination carriage incidences
Car_Total<-t(matrix(apply(Car,2,sum),dim(Car)[2],dim(Car)[1]))
Car2<-Car; Car2[VT_rows,]<-0
Car_NVT<-t(matrix(apply(Car2,2,sum),dim(Car2)[2],dim(Car2)[1]))
Car_VT<-Car_Total-Car_NVT
CarNew<-q*(1+p*Car_VT/Car_NVT)*Car2+(1-q)*Car
# Post vaccination IPD incidences
NVT_rows<-seq(dim(IPD)[1])[-1*VT_rows]
# CCR=Case-to-carrier ratios
CCR<-IPD/Car ; IPDNew<-0*IPD
# Apply the equation appearing above
# equation (1) in text for each serotype.
# First term applies to NVTs.
IPDNew[VT_rows,]<-(1-q)*IPD[VT_rows,]
# Second term applies to NVTs.
IPDNew[NVT_rows,]<-((Car_NVT+p*q*Car_VT)*(Car/Car_NVT)*CCR)[NVT_rows,]
}
else {
IPDNew<-IPD; CarNew<-Car
}
list(IPDNew,CarNew)
}
NextVT<-function(IPD,Car,VT_rows,p) {
##
## Result:
## A vector of decreases in IPD due to adding a serotype
## to the vaccine. If VT_rows=0, initially no vaccination.
## For row indexes incuded in VT_rows, the result is 0.
## [Markku Nurhonen 2013]
##
IPD<-as.matrix(IPD); Car<-as.matrix(Car)
## VaccMat = IPD and Car matrices after vaccination
VaccMat<-Vaccination(IPD,Car,VT_rows,p,1)
IPD<-VaccMat[[1]]; Car<-VaccMat[[2]]
## Total_IPD,Total_Car = Matrices corresponding to
## overall IPD and carriage in each age class.
Total_IPD<-t(matrix(apply(IPD,2,sum),dim(IPD)[2],dim(IPD)[1]))
Total_Car<-t(matrix(apply(Car,2,sum),dim(Car)[2],dim(Car)[1]))
## Effect = decrease in IPD when one serotype is added to the vaccine.
## See equation (3) in text.
Effect<-(Total_IPD-IPD)*((IPD/(Total_IPD-IPD))-(p*Car/(Total_Car-Car)))
## Special case when only one NVT remains.
IPD_nonzero<-which(apply(IPD,1,sum)!=0)
if (length(IPD_nonzero)==1) {Effect[IPD_nonzero,]<-IPD[IPD_nonzero,]}
## Result is obtained after summation over age classes.
apply(Effect,1,sum)
}
OptimalSequence<-function(IPD,Car,VT_rows,Excluded_rows,p,HowmanyAdded) {
##
## Starting from VTs indicated by the vector VT_rows
## (VT_rows=0, for no vaccination) sequentially add new VTs
## to the vaccine composition s.t. at each step the optimal
## serotype (corresponding to largest decrease in IPD) is added.
##
## Excluded_rows = Vector of indexes of the rows in matrices
## IPD and Car corresponding to serotypes that are not to
## be included in a vaccine composition, e.g. a row
## corresponding to a group of serotypes labelled "Other".
## Enter Excluded_rows=0 for no excluded serotypes.
## HowmanyAdded = number of VTs to be added.
##
## Result:
## Matrix of dimension 2*HowmanyAdded with 1st row indicating
## the row numbers of added serotypes in the order they appear
## in the sequence. The 2nd row lists the decreases in IPD
## due to addition of each type. [Markku Nurhonen 2013]
##
IPD<-as.matrix(IPD); Car<-as.matrix(Car)
## First check the maximum possible number of added VTs.
VT_howmany<-length(VT_rows)
if (VT_rows[1]==0) {VT_howmany<-0}
Excluded_howmany<-length(Excluded_rows)
if (Excluded_rows[1]==0) {Excluded_howmany<-0}
HowmanyAdded<-min(HowmanyAdded,dim(IPD)[1]-(VT_howmany+Excluded_howmany))
BestVTs<-BestEffects<-rep(0,HowmanyAdded)
## Sequential procedure: at each step find the best additional VT.
for (i in 1:HowmanyAdded) {
## Effects = Decrease in IPD after addition of each serotype
Effects<-NextVT(IPD,Car,VT_rows,p)
## Set Effects for VTs and excluded types equal to small values
## so that none of these will be selected as the next VT.
minvalue<- -2*max(abs(Effects))
if (Excluded_howmany>0) {Effects[Excluded_rows]<-minvalue}
if (VT_rows[1]>0) {Effects[VT_rows]<-minvalue}
## BestVTs[i] = Index of serotype with maximum decrease in IPD.
BestVTs[i]<-order(-1*Effects)[1]
## BestEffects[i] = Decrese in IPD due to addition of BestVTs[i]
## to the vaccine.
BestEffects[i]<-Effects[BestVTs[i]]
VT_rows<-c(VT_rows,BestVTs[i])
if (VT_rows[1]==0) {VT_rows<-VT_rows[-1]}
VaccMat<-Vaccination(IPD,Car,VT_rows,p,1)
IPD<-VaccMat[[1]]; Car<-VaccMat[[2]]
}
t(matrix(c(BestVTs,BestEffects),HowmanyAdded,2))
}
OptimalVacc<-function(IPD,Car,VT_rows,p,q,HowmanyAdded) {
##
## Result:
## A list of 3 elements: (1) Row numbers of serotypes in the optimal
## vaccine composition (2)-(3) IPD and carriage incidences
## by serotype and age class corresponding to the optimal
## vaccine formed using the sequential procedure in the
## function OptimalSequence. [Markku Nurhonen 2013]
##
Additional_VTs<-OptimalSequence(IPD,Car,VT_rows,p,HowmanyAdded)[1,]
All_VTs<-c(VT_rows,Additional_VTs)
if (All_VTs[1]==0) All_VTs<-All_VTs[-1]
VaccMat<-Vaccination(IPD,Car,All_VTs,p,q)
list(All_VTs,VaccMat[[1]],VaccMat[[2]])
}
VacCar <- Ovariable("VacCar",
dependencies = data.frame(Name = c(
"IPD", # incidence of pneumococcus disease
"Car", # number of carriers of pneumococcus
"servac", # ovariable of serotypes in vaccine (1 for serotypes in a vaccine, otherwise result is 0)
"p", # proportion of eliminated VT carriage that is replaced by NVT carriage
"q" # proportion of of VT carriage eliminated by vaccine
)),
formula = function(...) {
## Result:
## An ovariable of carriage incidences
## after vaccination (corresponding to Car).
## [Markku Nurhonen 2013, Jouni Tuomisto 2014]
# Post vaccination carriage incidences
# Sum over serotypes and drop extra columns
Car_Total<- unkeep(oapply(Car, cols = "Serotype", FUN = sum) * 1, prevresults = TRUE)
# Car2 is a temporary ovariable with NVT carriers only
Car2 <- unkeep(Car * (1 - servac), prevresults = TRUE) # Take only NVT carriers
Car_NVT <- oapply(Car2, cols = "Serotype", FUN = sum) # Carriers of serotypes not in vaccine (NVT)
Car_VT <- Car_Total - Car_NVT # Carriers of vaccine serotypes
CarNew <- q * (1 + p * Car_VT / Car_NVT) * Car2 + (1 - q) * Car
return(CarNew)
}
)
VacIPD <- Ovariable("VacIPD",
dependencies = data.frame(Name = c(
"IPD", # incidence of pneumococcus disease
"Car", # number of carriers of pneumococcus
"servac", # ovariable of serotypes in vaccine (1 for serotypes in a vaccine, otherwise result is 0)
"p", # proportion of eliminated VT carriage that is replaced by NVT carriage
"q" # proportion of of VT carriage eliminated by vaccine
)),
formula = function(...) {
## Result:
## An ovariable of IPD incidence
## after vaccination (corresponding to ovariable IPD).
## [Markku Nurhonen 2013, Jouni Tuomisto 2014]
# Post vaccination carriage incidences (same code as in VacCar)
Car_Total <- unkeep(oapply(Car, cols = "Serotype", FUN = sum) * 1, prevresults = TRUE) # Sums over serotypes
Car2 <- unkeep(Car * (1 - servac), prevresults = TRUE)
Car_NVT <- oapply(Car2, cols = "Serotype", FUN = sum) # Carriers of serotypes not in vaccine (NVT)
Car_VT <- Car_Total - Car_NVT # Carriers of vaccine serotypes
CarNew <- q * (1 + p * Car_VT / Car_NVT) * Car2 + (1 - q) * Car
# Post vaccination IPD incidences
# CCR=Case-to-carrier ratios
CCR <- IPD / Car
# Apply the equation appearing above
# equation (1) in text for each serotype.
# First term applies to VTs.
IPDNewVT <- (1 - q) * IPD * servac
# Second term applies to NVTs.
IPDNewNVT <- (Car_NVT + p * q * Car_VT) * (Car / Car_NVT) * CCR * (1 - servac)
IPDNew <- IPDNewVT + IPDNewNVT
return(IPDNew)
}
)
objects.store(Vaccination, NextVT, OptimalSequence, OptimalVacc, VacCar, VacIPD)
cat("Funktiot Vaccination, NextVT, OptimalSequence, OptimalVacc sekä ovariablet VacCar, VacIPD tallennettu. \n")
</rcode>
=== Data ===
=== Data ===
Edistymisluokitus
Opasnetissa lukuisat sivut ovat työn alla eri vaiheissa. Niiden tietosisältöön pitää siis suhtautua harkiten. Tämän sivun sisällön edistyminen on arvioitu:
Tämä sivu on täysluonnos
Sivu on kirjoitettu kertaalleen alusta loppuun eli kaikki olennaiset sisällöt ovat jo paikoillaan. Kuitenkaan sisältöjä ei ole vielä kunnolla tarkistettu, ja esimerkiksi tärkeitä viitteitä voi puuttua.
Kysymys
Miten arvioidaan vakavan pneumokokkitaudin tautitaakka tilanteessa, jossa
kansallisessa rokotusohjelmassa on jo vuodesta 2010 lähtien käytetty pikkulapsille tiettyjä rokoteserotyyppejä sisältävää konjugaattirokotetta?
Vakava pneumokokkitauti tarkoittaa invasiivista, veriviljelyllä varmennettua pneumokokkitautia (ks. vertailuperusteet ).
Arvioidaan tautitapausten vuosittainen määrä kaikissa ikäryhmissä.
Rokotuskattavuus, rokotteen teho ja aika rokotusten aloittamisesta ovat riittävät, jotta rokoteserotyyppien nielukantajuus ja tauti häviävät.
Oletetaan, että rokoteserotyyppien nielukantajuus korvautuu täysin muilla pneumokokin serotyypeillä, joiden taudinaiheuttamiskyky säilyy ennallaan.
Vastaus
Ennuste vakavien pneumokokkitautitapausten vuosittaisesta määrästä ikäluokittain
lasketaan laskennallisen mallin avulla (ks. 'Perustelut' alla). Tässä vaiheessa ennuste koskee veriviljelypositiivista vakavaa pneumokokkitautia (invasive pneumococcal disease, IPD).
Perustelut
Pneumokokkitaudin rokotusten jälkeinen tautitaakka arvioidaan nielukantajuuden laskennallisen korvautumismallin
[1] avulla. Mallissa rokoteserotyyppien nielukantajuus häviää vähitellen rokotusohjelman kohdeväestössä sekä rokotetun että rokottamattoman väestönosan keskuudessa. Samalla rokotetyyppien nielukantajuus korvautuu ei-rokotetyyppien kantajuudella. Tämän korvautumisen seuraukset voidaan laskea ennen rokotuksia vallinneiden serotyyppikohtaisten nielukantajuusosuuksien ja tautimäärien perusteella.
Korvautumisen seuraukset riippuvat oleellisesti kahdesta mallissa hyödynnetystä oletuksesta
Rokotteeseen kuulumattomien serotyyppien nielukantajuusosuudet toisiinsa verrattuina eivät muutu rokotuksen vaikutuksesta
Rokotuksella ei ole vaikutusta yksittäisten serotyyppien taudinaiheuttamiskykyyn
Rokottamisen vaikutus tautimäärään lasketaan nielukantajuuden muutosten kautta ja korvautuminen pneumokokkiserotyyppien nielukantajuudessa heijastuu suoraan muutoksena niiden aiheuttamissa tautimäärissä. Rokotusten vaikutus kokonaistautitaakkaan riippuu oleellisesti rokoteserotyyppien taudinaiheuttamiskyvystä verrattuna muiden serotyyppien taudinaiheuttamiskykyyn. Joidenkin serotyyppien kohdalla tarkastellaan kuitenkin myös vaihtoehtoista oletusta, jossa rokote voi vähentää serotyypin aiheuttaman taudin esiintymistä rokotettujen keskuudessa ilman vaikutusta nielukantajuuteen.
Korvautuminen
Korvautuminen on ilmiö, jossa rokotusten hävittämät pneumokokkiserotyypit korvautuvat väestössä osittain muilla serotyypeillä. Tällöin pneumokokkien kokonaismäärä ei vähene väestössä niin paljon kuin rokoteserotyyppien yleisyys antaisi olettaa. Ilmiötä on tarkemmin kuvattu omalla sivullaan .
Kuva 1. Korvautumismallin periaate. Pneumokokin nielukantajuus (carriage, x-akseli) ja sairastumistapaukset kantajuusepisodia kohden (case-to-carrier ratio, y-akseli) rokotteen serotyypeille (VT) ja serotyypeille joihin rokote ei vaikuta (NVT) ennen rokotusohjelmaa (kuva A) ja sen jälkeen (kuva A). Sairastumistapaukset (DVT ja DNVT) on saatu kertomalla akseleiden arvot ja ne vastaavat kuvaajassa suorakulmion muotoisia alueita. Rokottamisen vaikutuksesta rokoteserotyyppien nielukantajuus häviää ja korvautuu muiden serotyyppien kantajuudella (kuva B). Tautitapausten määrä laskee hävinneen ja korvaavan nielukantajuuden sairastuttavuuden (RVT ja RNVT) eroavuuden vuoksi. Tautihäviämä on (kuva B) merkitty sinisellä suorakulmiolla.
Laskenta
Seuraava ohjelma havainnollistaa korvautumismallia. Ohjelmassa voidaan verrata keskenään rokotteita PCV10 ja PCV13. Lisäksi mukana vertailussa voi olla käyttäjän valitsemat serotyypit sisältävä pneumokokkirokote sekä tilanne, jossa ei rokoteta. Tuloksena esitetään mallin mukainen vakavien pneumokokkitautitapausten lukumäärä Suomessa vuosittain ensin serotyyppikohtaisesti ja sen jälkeen erikseen ikäluokissa <5 vuotta ja 5+ vuotta. Ohjelmakoodi perustuu viitteen [1] liitetiedostoon S1.
---- # : . Tämän ohjelmakoodin tarjoamia valintavaihtoehtoja tullaan laajentamaan siten, että osalle serotyypeistä voidaan rokotteen olettaa antavan osittaisen suojan tautia vastaan ilman vaikutusta nielukantajuuteen. --Markku N. (keskustelu ) 27. kesäkuuta 2014 kello 10.12 (UTC) (type: truth ; paradigms: science : comment )
Ohje käyttäjälle: Voit verrata eri rokotteita keskenään tai rokotetta/rokotteita tilanteeseen, jossa ei rokoteta lainkaan. Valitse ensin vertailuun haluamasi rokotteet. PCV10, PCV13 ja 'Ei rokoteta'-skenaario voi tehdä suoravalintana. Sen lisäksi voit tarkastella myös rokotetta, johon itse valitset haluamasi serotyypit. Valintojen jälkeen klikkaa painiketta "Aja koodi". Tulokset lasketaan erilliselle välilehdelle.
+ Näytä koodi - Piilota koodi
library(OpasnetUtils)
library(ggplot2)
#vacc1 <- vac
#vacc2 <- custom_vac
if(custom_vac) {
vac <- c(vac, "Oma")
}
if (length(vac) == 0) stop("Mitään skenaariota ei valittu")
user_args <- list(
Scenario = vac
)
# Ulkoinen säilö datalle jollain sivulla?
temp <- data.frame(
Vaccine = rep(c("PCV10", "PCV13"), c(9, 12)),
Serotype = c('19F', '23F', '6B', '14', '9V', '4', '18C', '1', '7',
'19F', '23F', '6B', '14', '9V', '4', '18C', '1', '7', '3', '6A', '19A'
)
)
user_args$Vaccines <- temp[temp$Vaccine %in% user_args$Scenario, ]
if(custom_vac) {
user_args$Vaccines <- rbind(
user_args$Vaccines,
data.frame(Vaccine = "Oma", Serotype = vac_user)
)
}
#if(!exists("servac_user")) servac_user <- c('19F', '23F', '6B', '14', '9V', '4', '18C', '1', '7')
objects.latest("Op_en6353", code_name = "initiate") # [[:op_en:Epidemiological modelling]] ovariables VacCar, VacIPD
objects.latest("Op_en6007", code_name = "answer") # [[OpasnetUtils/Drafts]]
openv.setN(100)
## Read the annual IPD and carriage incidence data.
## The 0 entries in IPD and carriage data are replaced by small values.
serotypes<-c(
"19F", "23F", "6B", "14", "9V", "4", "18C", "1", "7",
"6A", "19A", "3", "8", "9N", "10", "11", "12", "15",
"16", "20", "22", "23A", "33", "35", "38", "6C", "Oth")
car_under5<-c(
156030, 156030, 126990, 41200, 22290, 12830, 10130, 10, 14180,
54940, 24320, 12160, 1350, 20940, 4050, 72270, 10, 33100,
3380, 1350, 12160, 3380, 680, 30400, 4050, 27470, 24320 )
car_over5<-c(
168100, 314800, 256700, 209800, 114100, 62500, 200700, 100, 100,
158800, 54900, 30800, 8800, 8800, 20800, 97700, 100, 100,
191900, 25200, 72500, 22000, 100, 71300, 100, 79400, 330100 )
ipd_under5<-c(
7.78, 7.88, 24.39, 20.76, 2.91, 2.91, 6.64, 0.31, 3.02,
3.94, 9.88, 1.25, 0.10, 0.83, 0.41, 0.42, 0.21, 1.98,
0.21, 0.01, 0.93, 0.10, 0.42, 0.31, 0.42, 0.01, 0.73 )
ipd_over5<-c(
28.51, 53.72, 29.53, 99.43, 43.07, 76.99, 24.39, 6.58, 46.88,
17.42, 20.54, 55.04, 11.21, 25.20, 6.28, 12.76, 13.89, 9.18,
4.73, 3.29, 29.03, 4.40, 5.64, 12.41, 1.43, 5.50, 11.20 )
## Combine the data into 2 matrices of dimension 27*2:
IPD<-cbind(ipd_under5, ipd_over5)
Car<-cbind(car_under5, car_over5)
## Row numbers corresponding to the 3 different PCV formulations
## in matrices IPD and Car. Note: there is no serotype 5 in our data.
pcv7rows<-seq(7); pcv10rows<-seq(9); pcv13rows<-seq(12)
## Example S1.2A: Calculate the predicted incidence of IPD for the non-vaccine
## types(NVTs) under PCV13. The predictions are calculated separately for the
## two age classes. These are the values reported on the bottom panel in
## Figure 2 (there given as per 100K incidences).
postvacc <-Vaccination(IPD,Car,VT_rows=pcv13rows,p=1,q=1)
## Example S1.2B: Decrease in IPD incidence after adding a single new serotype
## to PCV13 separately for the two age categories.
next_under5<-NextVT(IPD[,1],Car[,1], VT_rows=pcv13rows,p=1)
next_over5 <-NextVT(IPD[,2],Car[,2], VT_rows=pcv13rows,p=1)
# Nämä taulukot kannattaisi transposata niin näyttäisivät siistimmiltä.
## Example S1.3A: The optimal sequence for under 5 year olds when replacement is 100%.
## The output shows the decreases in IPD incidence for each step,
## corresponding to Figure 5(C). The last serotype (row 27, the category "Other")
## is excluded from any vaccine composition but is taken into account as a
## replacing serotype at each stage.
opt<-OptimalSequence(IPD[,1],Car[,1],VT_rows=0,Excluded_rows=27,p=1.0,HowmanyAdded=20)
## Example S1.3B: The optimal sequence for the whole population when
## replacement is 50% and the current composition includes the PCV7 serotypes.
opt<-OptimalSequence(IPD,Car, VT_rows=pcv7rows,Excluded_rows=length(serotypes),
p=0.5,HowmanyAdded=17)
###################################
## Read the annual IPD and carriage incidence data.
## The 0 entries in IPD and carriage data are replaced by small values.
IPD <- Ovariable("IPD", ddata = "Op_fi4305.pneumokokki_vaestossa")
IPD@data <- IPD@data[IPD@data$Observation == "Incidence" , colnames(IPD@data) != "Observation"]
Car <- Ovariable("Car", ddata = "Op_fi4305.pneumokokki_vaestossa")
Car@data <- Car@data[Car@data$Observation == "Carrier" , colnames(Car@data) != "Observation"]
servac <- merge(data.frame(Vaccine = user_args$Scenario), data.frame(Serotype = serotypes))
servac <- merge(
data.frame(user_args$Vaccines, Result = 1),
servac,
all.y = TRUE
)
servac$Result <- as.numeric(!is.na(servac$Result))
servac <- Ovariable(
"servac",
data = servac
)
#data.frame(
#Vaccine = rep(c("Current", "New"), each = length(serotypes)),
#Serotype = serotypes,
#Result = as.numeric(c(
# serotypes %in% c("19F", "23F", "6B", "14", "9V", "4", "18C", "1", "7"),
# serotypes %in% servac_user
# ))
#))
p_user<-q_user<-adultcarriers<-1
p <- Ovariable("p", data = data.frame(Result = p_user))
q <- EvalOutput(Ovariable("q", data = data.frame(Result = q_user)))
# EvalOutput must be used because q is mentioned twice in the code and there will otherwise be a merge mismatch.
# The true number of adult carriers may actually be larger than estimated. This adjusts for that.
Car <- Car * Ovariable("adjust", data = data.frame(Age = c("Under 5", "Over 5"), Result = c(1, adultcarriers)))
VacCar <- EvalOutput(VacCar)
VacIPD <- EvalOutput(VacIPD)
if (1==0) {
cat("servac\n")
oprint(summary(servac))
cat("Number of carriers\n")
oprint(summary(VacCar))
cat("Incidence of invasive pneumococcal disease.\n")
oprint(summary(VacIPD)) }
if("Iter" %in% colnames(VacCar@output)) N <- max(VacCar@output$Iter) else N <- 1
if (1==0) {ggplot(VacCar@output, aes(x = Serotype, weight = result(VacCar) / N, fill = Vaccine)) + geom_bar(position = "dodge") + theme_gray(base_size = 24) +
labs(title = "Carriers", y = "Number of carriers in Finland") }
ggplot(VacIPD@output, aes(x = Serotype, weight = result(VacIPD) / N, fill = Vaccine)) + geom_bar(position = "dodge") + theme_gray(base_size = 24) +
labs(title = "Incidence of invasive pneumococcal disease", y = "Number of cases per year")
ggplot(VacIPD@output, aes(x = Vaccine, weight = result(VacIPD) / N, fill = Age)) + geom_bar(position = "stack") + theme_gray(base_size = 24) +
labs(title = "Incidence of invasive pneumococcal disease", y = "Number of cases per year")
Funktioiden alustus
Mallissa käytetään samoja funktioita ja ovariableja kuin englanninkielisessä mallissa. Katso siis op_en:Epidemiological modelling#Initiate functions .
Data
Pneumokokin esiintyvyys suomalaisessa väestössä. Carrier: (oireettomien) kantajuusedpisodien lukumäärä vuodessa, Incidence: invasiivisten pneumokokkitautitapausten lukumäärä vuodessa.
Näytä yksityiskohdat
Alla olevan taulukon data otettu täältä .
Pneumokokki väestössä(#, #/100000py) Obs Serotype Age Carrier Incidence 1 19F Under 5 156030 7.78 2 23F Under 5 156030 7.88 3 6B Under 5 126990 24.39 4 14 Under 5 41200 20.76 5 9V Under 5 22290 2.91 6 4 Under 5 12830 2.91 7 18C Under 5 10130 6.64 8 1 Under 5 10 0.31 9 7 Under 5 14180 3.02 10 6A Under 5 54940 3.94 11 19A Under 5 24320 9.88 12 3 Under 5 12160 1.25 13 8 Under 5 1350 0.1 14 9N Under 5 20940 0.83 15 10 Under 5 4050 0.41 16 11 Under 5 72270 0.42 17 12 Under 5 10 0.21 18 15 Under 5 33100 1.98 19 16 Under 5 3380 0.21 20 20 Under 5 1350 0.01 21 22 Under 5 12160 0.93 22 23A Under 5 3380 0.1 23 33 Under 5 680 0.42 24 35 Under 5 30400 0.31 25 38 Under 5 4050 0.42 26 6C Under 5 27470 0.01 27 Oth Under 5 24320 0.73 28 19F Over 5 168100 28.51 29 23F Over 5 314800 53.72 30 6B Over 5 256700 29.53 31 14 Over 5 209800 99.43 32 9V Over 5 114100 43.07 33 4 Over 5 62500 76.99 34 18C Over 5 200700 24.39 35 1 Over 5 100 6.58 36 7 Over 5 100 46.88 37 6A Over 5 158800 17.42 38 19A Over 5 54900 20.54 39 3 Over 5 30800 55.04 40 8 Over 5 8800 11.21 41 9N Over 5 8800 25.2 42 10 Over 5 20800 6.28 43 11 Over 5 97700 12.76 44 12 Over 5 100 13.89 45 15 Over 5 100 9.18 46 16 Over 5 191900 4.73 47 20 Over 5 25200 3.29 48 22 Over 5 72500 29.03 49 23A Over 5 22000 4.4 50 33 Over 5 100 5.64 51 35 Over 5 71300 12.41 52 38 Over 5 100 1.43 53 6C Over 5 79400 5.5 54 Oth Over 5 330100 11.2
Vakavan pneumokokkitaudit ikäryhmittäin vuosina 2004-2013(ilmaantuvuus/100 000 henkilövuotta) Obs Vuosi Ikä PCV10-rokotteen pneumokokkityypit PCV10-rokotteen sukulaistyypit Muut kuin PCV-rokotteen pneumokokkityypit ja niiden sukulaistyypit Tyypittämättömät näytteet Kaikki pneumokokkibakteerityypit 1 2004 0-1 35.8 20.1 5.2 4.4 61.2 2 2005 0-1 48.5 11.3 2.6 5.2 62.3 3 2006 0-1 57.3 6 5.1 0.9 68.5 4 2007 0-1 53.4 10.2 2.5 0 66.1 5 2008 0-1 42.1 7.6 4.2 1.7 53.9 6 2009 0-1 41.5 7.5 2.5 2.5 51.5 7 2010 0-1 43.5 3.3 3.3 1.6 50 8 2011 0-1 28 2.5 6.6 0 37 9 2012 0-1 6.7 0.8 5 0 12.5 10 2013 0-1 5.8 4.2 5.8 0.8 15.8 11 2004 2-4 18.3 4.1 0.6 2.4 23 12 2005 2-4 16.5 3.5 1.2 1.8 21.2 13 2006 2-4 14.6 2.3 0.6 0 17.5 14 2007 2-4 23 2.3 0.6 1.2 25.9 15 2008 2-4 14.7 1.7 1.7 0 18.1 16 2009 2-4 15.2 2.3 0 0.6 17.4 17 2010 2-4 20 1.7 1.1 0.6 17.4 18 2011 2-4 8.8 4.4 1.7 0 14.9 19 2012 2-4 8.2 1.1 0 0 9.2 20 2013 2-4 1.6 3.3 2.7 0 7.6 21 2004 5-17 1.7 0.1 0.1 0 1.9 22 2005 5-17 2.1 0 0.4 0.2 2.4 23 2006 5-17 1.8 0 0.4 0.1 2.2 24 2007 5-17 1.6 0.4 0.5 0.2 2.5 25 2008 5-17 2.4 0.1 0.4 0.1 2.9 26 2009 5-17 3 0.1 0.4 0.1 2.9 27 2010 5-17 1.4 0.6 0.1 0.3 2.2 28 2011 5-17 1.9 0.3 0.5 0 2.7 29 2012 5-17 0.9 0.4 0.6 0 1.9 30 2013 5-17 1.2 0.4 0.3 0 1.8 31 2004 18-49 6.6 0.6 1.8 0.3 9 32 2005 18-49 5.5 0.8 1.5 0.4 7.8 33 2006 18-49 5.2 0.9 1.4 0.2 7.5 34 2007 18-49 5.6 0.4 1.7 0.2 7.7 35 2008 18-49 7.2 0.7 2.1 0.5 10.1 36 2009 18-49 6.6 0.5 2.1 0.3 9.3 37 2010 18-49 5.1 0.6 2.6 0.4 8.4 38 2011 18-49 4.9 0.7 1.9 0 7.6 39 2012 18-49 3.7 1 1.8 0 6.5 40 2013 18-49 3.7 0.8 2.5 0.2 7.1 41 2004 50-64 10.4 1.8 4.9 1.4 17.2 42 2005 50-64 11.8 1.4 4.9 1.4 17.2 43 2006 50-64 11.8 1.4 5.3 0.9 18.5 44 2007 50-64 10.8 1.9 3.3 0.8 16 45 2008 50-64 12.2 3 6.9 1 22.2 46 2009 50-64 12.4 2.4 5 0.9 19.8 47 2010 50-64 12.3 2.2 5.2 0.8 19.6 48 2011 50-64 9.6 3.2 6.4 0.3 19.3 49 2012 50-64 9.4 3.3 6.5 0.1 19.2 50 2013 50-64 7.4 3.6 6.9 0.4 17.9 51 2004 65- 16.6 4.6 7.6 1 28.8 52 2005 65- 16.6 4.3 6.3 2 27.2 53 2006 65- 19.3 3.9 7.8 1.6 31.1 54 2007 65- 20.8 3.9 9 0.6 33.7 55 2008 65- 23.1 4.6 9 1.7 36.7 56 2009 65- 19 4.9 8.5 1.5 32.4 57 2010 65- 18.5 5.1 8.7 1.5 32.3 58 2011 65- 15.4 5.2 9.8 0.4 30.4 59 2012 65- 14.8 6.7 12.2 0.6 33.7 60 2013 65- 11.1 8.6 11.7 0.9 31.4 61 2004 Kaikki 8.7 1.8 3 0.7 14.3 62 2005 Kaikki 8.8 1.5 2.7 0.9 13.9 63 2006 Kaikki 9.3 1.6 2.6 0.6 14.1 64 2007 Kaikki 9.8 1.6 3.2 0.4 14.9 65 2008 Kaikki 10.8 1.9 3.9 0.8 17.3 66 2009 Kaikki 10.1 1.8 3.4 0.7 16 67 2010 Kaikki 9.4 1.7 3.7 0.7 15.5 68 2011 Kaikki 8 2.1 4.2 0.2 14.4 69 2012 Kaikki 6.7 2.4 4.5 0.1 13.8 70 2013 Kaikki 5.3 2.9 4.8 0.4 13.4
Katso myös
Tämä rokotehankintakeskustelu toimitettiin tiedoksi kansalliselle rokotusasiantuntijaryhmälle 8.9.2014.
Viitteet
↑ 1,0 1,1 Nurhonen M, Auranen K (2014) Optimal Serotype Compositions for Pneumococcal Conjugate Vaccination under Serotype Replacement. PLoS Computational Biology 10(2): e1003477. [1]
Kommentoi