diff --git a/DESCRIPTION b/DESCRIPTION index 6f70316..b26abd9 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: IPDMR Title: Support Code for the Introduction to Practical Disease Modelling Course -Version: 0.4.3-1 -Date: 2024-11-07 +Version: 0.5.0-1 +Date: 2024-11-08 Description: A collection of functions and classes that are used to illustrate fundamental concepts of disease modelling as part of a physical course series taught jointly by the University of Copenhagen and University of Sydney. The diff --git a/NAMESPACE b/NAMESPACE index 6ae7ee4..b474697 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -19,6 +19,7 @@ export(si_continuous) export(si_discrete) export(sir_det) export(sir_stoc) +export(suggest_boxes) import(R6) import(Rcpp) import(dplyr) @@ -33,6 +34,8 @@ importFrom(methods,new) importFrom(pbapply,pblapply) importFrom(rlang,.data) importFrom(rlang,set_names) +importFrom(stats,dgamma) +importFrom(stats,qgamma) importFrom(stats,quantile) importFrom(stats,rmultinom) importFrom(tibble,tibble) diff --git a/R/BetweenGroupClass.R b/R/BetweenGroupClass.R index 52e4767..f644bc2 100644 --- a/R/BetweenGroupClass.R +++ b/R/BetweenGroupClass.R @@ -117,7 +117,14 @@ BetweenGroupClass <- R6::R6Class( ## TODO: C++ function if private$.allcpp - trans_b <- colSums(private$.beta_matrix * sapply(private$.groups, \(x) x$I)) + if(private$.trans_between == "frequency"){ + multby <- sapply(private$.groups, \(x){ x$I / x$N }) + }else if(private$.trans_between == "density"){ + multby <- sapply(private$.groups, \(x) x$I) + }else{ + stop("Unrecognised private$.trans_between") + } + trans_b <- colSums(private$.beta_matrix * multby) for(i in seq_along(private$.groups)){ private$.groups[[i]]$trans_external <- trans_b[i] private$.groups[[i]]$update(d_time) @@ -206,6 +213,7 @@ BetweenGroupClass <- R6::R6Class( .ngroups = numeric(), .groups = list(), .time = numeric(), + .trans_between = "density", .dummy=NULL ), @@ -229,6 +237,13 @@ BetweenGroupClass <- R6::R6Class( private$.time }, + #' @field transmission_between the between-group transmission type (frequency or density) + transmission_between = function(value){ + if(missing(value)) return(private$.trans_between) + value <- match.arg(value, c("frequency","density")) + private$.trans_between <- value + }, + #' @field state a data frame of the current state of each group state = function(){ lapply(private$.groups, function(x) x$state) |> diff --git a/R/SEIRclass.R b/R/SEIRclass.R index daba25c..d51c9c8 100644 --- a/R/SEIRclass.R +++ b/R/SEIRclass.R @@ -169,6 +169,8 @@ SEIRclass <- R6::R6Class("SEIRclass", "beta/omega/gamma/delta = ", self$beta, "/", self$omega, "/", self$gamma, "/", self$delta, "\n\t", "vacc/repl/cull = ", self$vacc, "/", self$repl, "/", self$cull, "\n\t", "E compartments = ", private$.numE, "\n\t", + "I compartments = 1\n\t", + "R compartments = 1\n\t", "external transmission = ", private$.trans_external, "\n\t", "update type = ", private$.update_type, "\n\t", "transmission type = ", private$.transmission_type, "\n\t", diff --git a/R/make_group.R b/R/make_group.R index 4bfbb6a..b121388 100644 --- a/R/make_group.R +++ b/R/make_group.R @@ -8,9 +8,10 @@ #' implementations should be identical). #' #' @param update_type either stochastic or deterministic -#' @param numE the number of sub-compartments desired for the E state +#' @param numE the number of sub-compartments desired for the E state (0 or more) +#' @param numI the number of sub-compartments desired for the I state (1 or more) +#' @param numR the number of sub-compartments desired for the R state (0 or more) #' @param group_name an optional name for the group -#' @param model_type the compartmental model representation desired (currently only SEIR is supported) #' @param implementation either C++ or R6 #' #' @importFrom methods new @@ -26,35 +27,33 @@ #' stopifnot(unlist(r6res) - unlist(cppres) == 0L) #' #' @export -make_group <- function(update_type = c("deterministic","stochastic"), numE = 3L, group_name=NA_character_, model_type = c("SEIR", "SIR", "SI"), implementation = c("C++","R6")){ +make_group <- function(update_type = c("deterministic","stochastic"), numE = 3L, numI = 1L, numR = 1L, group_name=NA_character_, implementation = c("C++","R6")){ update_type <- match.arg(update_type) implementation <- toupper(implementation) implementation <- match.arg(implementation) - model_type <- toupper(model_type) - model_type <- match.arg(model_type) - stopifnot(model_type=="SEIR") + qassert(numE, "X1[0,)") + qassert(numI, "X1(0,)") + qassert(numR, "X1[0,)") if(implementation=="R6"){ + if(numE==0L) stop("The R6 implementation is limited to numE>=1") + if(numI!=1L) stop("The R6 implementation is limited to numI==1") + if(numR!=1L) stop("The R6 implementation is limited to numR==1") + model <- SEIRclass$new(update_type=update_type, numE=numE, group_name=group_name) }else if(implementation=="C++"){ - if(update_type=="deterministic"){ - if(numE==3L){ - model <- new(SEIRdet3, 3L, group_name) - }else{ - model <- new(SEIRdetN, numE, group_name) - } - }else{ - if(numE==3L){ - model <- new(SEIRstoc3, 3L, group_name) - }else{ - model <- new(SEIRstocN, numE, group_name) - } - } + modname <- str_c("SEIR", + if(update_type=="deterministic") "det" else "stoc", + if(numE %in% c(0,1,3)) numE else "N", + if(numI %in% c(1)) numI else "N", + if(numR %in% c(0,1)) numR else "N" + ) + model <- new(get(modname), numE, numI, numR, group_name) }else{ stop("Unmatched implementation type") diff --git a/R/model_wrappers.R b/R/model_wrappers.R index f1381fa..23829ac 100644 --- a/R/model_wrappers.R +++ b/R/model_wrappers.R @@ -31,11 +31,47 @@ NULL #' @rdname group_models #' @export -sir_det <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmission_type="frequency", d_time=1, max_time=100){ +sir_det <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmission_type=c("frequency","density"), d_time=1, max_time=100){ - qassert(transmission_type, "S1") + transmission_type <- match.arg(transmission_type) + + model <- make_group(update_type="deterministic", numE=0, numI=1, numR=1) + #model <- WithinGroupModel$new(model_type="sir", update_type="deterministic", transmission_type=transmission_type, d_time=d_time) + + model$transmission_type <- transmission_type + model$S <- S + model$I <- I + model$R <- R + model$beta <- beta + model$gamma <- gamma + model$delta <- delta + out <- model$run(max_time, d_time) + rm(model) + + class(out) <- c("ipdmr_dt", class(out)) + attr(out, "plot_caption") <- str_c("deterministic; discrete; ", transmission_type) + return(out) + + ### OLDER CODE + + + update_type <- "deterministic" + if(update_type=="deterministic"){ + + + }else{ + + out |> + mutate(Iteration = 1L) |> + select(Iteration, everything()) -> + out + + class(out) <- c("ipdmr_st", class(out)) + attr(out,'iterations') <- 1L + attr(out, "plot_caption") <- str_c("stochastic; discrete; ", transmission_type) + + } - model <- WithinGroupModel$new(model_type="sir", update_type="deterministic", transmission_type=transmission_type, d_time=d_time) model$S <- S model$I <- I @@ -54,16 +90,11 @@ sir_det <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmissi #' @export seir_det <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_type=c("frequency","density"), d_time=1, max_time=100){ - #qassert(transmission_type, "S1") transmission_type <- match.arg(transmission_type) - model <- make_group(update_type="deterministic", numE=numE, group_name=NA_character_, model_type="SEIR", implementation="C++") + model <- make_group(update_type="deterministic", numE=numE, numI=1, numR=1) model$transmission_type <- transmission_type - if(FALSE){ - model <- WithinGroupModel$new(model_type="seir", update_type="deterministic", transmission_type=transmission_type, numE=numE, d_time=d_time) - } - model$S <- S model$E <- E model$I <- I @@ -77,7 +108,7 @@ seir_det <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0 model$repl <- repl model$cull <- cull - model$run(ceiling(max_time/d_time), d_time) -> + model$run(max_time, d_time) -> output class(output) <- c("ipdmr_dt", class(output)) @@ -89,23 +120,27 @@ seir_det <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0 #' @rdname group_models #' @export -sir_stoc <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmission_type="frequency", d_time=1, max_time=100, iterations=1L){ +sir_stoc <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmission_type=c("frequency","density"), d_time=1, max_time=100, iterations=1L){ - qassert(transmission_type, "S1") + transmission_type <- match.arg(transmission_type) + qassert(iterations, "X1") - pblapply(seq_len(iterations), \(i){ + model <- make_group(update_type="stochastic", numE=0, numI=1, numR=1) - model <- WithinGroupModel$new(model_type="sir", update_type="stochastic", transmission_type=transmission_type, d_time=d_time) + model$transmission_type <- transmission_type + model$S <- S + model$I <- I + model$R <- R + model$beta <- beta + model$gamma <- gamma + model$delta <- delta + model$save() - model$S <- S - model$I <- I - model$R <- R + pblapply(seq_len(iterations), \(i){ - model$beta <- beta - model$gamma <- gamma - model$delta <- delta + model$reset() - model$run(ceiling(max_time/d_time), d_time) |> + model$run(max_time, d_time) |> as_tibble() |> mutate(Iteration = i) |> select("Iteration", everything()) @@ -124,12 +159,12 @@ sir_stoc <- function(S=99, I=1, R=0, beta=0.25, gamma=0.2, delta=0.05, transmiss #' @rdname group_models #' @export -seir_stoc <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_type="frequency", d_time=1, max_time=100, iterations=1L){ +seir_stoc <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_type=c("frequency","density"), d_time=1, max_time=100, iterations=1L){ #qassert(transmission_type, "S1") transmission_type <- match.arg(transmission_type) - model <- make_group(update_type="stochastic", numE=numE, group_name=NA_character_, model_type="SEIR", implementation="C++") + model <- make_group(update_type="stochastic", numE=numE, numI=1, numR=1) model$transmission_type <- transmission_type model$S <- S model$E <- E @@ -149,7 +184,7 @@ seir_stoc <- function(S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma= #model <- WithinGroupModel$new(model_type="seir", update_type="stochastic", transmission_type=transmission_type, num_E=num_E, d_time=d_time) model$reset() - model$run(ceiling(max_time/d_time), d_time) |> + model$run(max_time, d_time) |> as_tibble() |> mutate(Iteration = i) |> select("Iteration", everything()) diff --git a/R/multi_wrappers.R b/R/multi_wrappers.R index 6f8c127..a9a6d00 100644 --- a/R/multi_wrappers.R +++ b/R/multi_wrappers.R @@ -22,6 +22,8 @@ #' @param vacc the vaccination rate parameter per unit time (must be positive) #' @param repl the replacement rate parameter per unit time (must be positive) #' @param cull the targeted culling rate parameter per unit time (must be positive) +#' @param transmission_within the within-group transmission type (frequency or density) +#' @param transmission_between the between-group transmission type (frequency or density) #' @param iterations the number of iterations to run (stochastic models only) #' @param d_time the desired time step (delta time) #' @param max_time the desired maximum time point (must be greater than the time step) @@ -37,9 +39,11 @@ NULL #' @rdname multi_models #' @export -multi_seir_det <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, d_time=1, max_time=100){ +multi_seir_det <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_within=c("frequency","density"), transmission_between=c("density","frequency"), d_time=1, max_time=100){ - output <- multi_wrapper("deterministic", n_groups=n_groups, beta_matrix=beta_matrix, S=S, E=E, I=I, R=R, numE=numE, beta=beta, omega=omega, gamma=gamma, delta=delta, vacc=vacc, repl=repl, cull=cull, d_time=d_time, max_time=max_time, iterations=1L) + transmission_within <- match.arg(transmission_within) + transmission_between <- match.arg(transmission_between) + output <- multi_wrapper("deterministic", n_groups=n_groups, beta_matrix=beta_matrix, S=S, E=E, I=I, R=R, numE=numE, beta=beta, omega=omega, gamma=gamma, delta=delta, vacc=vacc, repl=repl, cull=cull, transmission_within=transmission_within, transmission_between=transmission_between, d_time=d_time, max_time=max_time, iterations=1L) class(output) <- c("ipdmr_dm", class(output)) attr(output, "plot_caption") <- str_c("deterministic; ", n_groups, " groups") @@ -49,9 +53,11 @@ multi_seir_det <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, #' @rdname multi_models #' @export -multi_seir_stoc <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, d_time=1, max_time=100, iterations=1L){ +multi_seir_stoc <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_within=c("frequency","density"), transmission_between=c("density","frequency"), d_time=1, max_time=100, iterations=1L){ - output <- multi_wrapper("stochastic", n_groups=n_groups, beta_matrix=beta_matrix, S=S, E=E, I=I, R=R, numE=numE, beta=beta, omega=omega, gamma=gamma, delta=delta, vacc=vacc, repl=repl, cull=cull, d_time=d_time, max_time=max_time, iterations=iterations) + transmission_within <- match.arg(transmission_within) + transmission_between <- match.arg(transmission_between) + output <- multi_wrapper("stochastic", n_groups=n_groups, beta_matrix=beta_matrix, S=S, E=E, I=I, R=R, numE=numE, beta=beta, omega=omega, gamma=gamma, delta=delta, vacc=vacc, repl=repl, cull=cull, transmission_within=transmission_within, transmission_between=transmission_between, d_time=d_time, max_time=max_time, iterations=iterations) class(output) <- c("ipdmr_sm", class(output)) attr(output, "iterations") <- iterations @@ -61,9 +67,11 @@ multi_seir_stoc <- function(n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, } -multi_wrapper <- function(update_type, n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, d_time=1, max_time=100L, iterations=1L){ +multi_wrapper <- function(update_type, n_groups, beta_matrix, S=99, E=0, I=1, R=0, numE=3L, beta=0.25, omega=0.2, gamma=0.2, delta=0.05, vacc=0, repl=0, cull=0, transmission_within=c("frequency","density"), transmission_between=c("density","frequency"), d_time=1, max_time=100L, iterations=1L){ ## Check arguments: + transmission_within <- match.arg(transmission_within) + transmission_between <- match.arg(transmission_between) qassert(n_groups, "X1(0,)") assert_matrix(beta_matrix, "numeric", any.missing=FALSE, nrows=n_groups, ncols=n_groups) qassert(iterations, "X1(0,)") @@ -73,6 +81,7 @@ multi_wrapper <- function(update_type, n_groups, beta_matrix, S=99, E=0, I=1, R= model_pars <- list( S=S, E=E, I=I, R=R, numE=numE, beta=beta, omega=omega, gamma=gamma, delta=delta, vacc=vacc, repl=repl, cull=cull, + transmission_type=transmission_within, group_number=seq_len(n_groups) ) @@ -89,9 +98,7 @@ multi_wrapper <- function(update_type, n_groups, beta_matrix, S=99, E=0, I=1, R= group_split() |> set_names(str_c("Group_", seq_len(n_groups) |> format() |> str_replace_all(" ", "0"))) |> lapply(\(x){ - #md <- WithinGroupModel$new("seir", update_type, "frequency", numE=x$numE, d_time=d_time, group_number=x[["group_number"]]) - md <- make_group(update_type=update_type, numE=x$numE, group_name=x[["group_number"]], model_type="SEIR", implementation="C++") - md$transmission_type <- "frequency" + md <- make_group(update_type=update_type, numE=x$numE, numI=1, numR=1, group_name=x[["group_number"]]) x$numE <- NULL x$group_number <- NULL for(nm in names(x)){ @@ -105,6 +112,7 @@ multi_wrapper <- function(update_type, n_groups, beta_matrix, S=99, E=0, I=1, R= ## Set up the model: model <- BetweenGroupClass$new(models) model$beta_matrix <- beta_matrix + model$transmission_between <- transmission_between model$save() ## Iterate: diff --git a/R/si_discrete.R b/R/si_discrete.R index d7102d3..59517a4 100644 --- a/R/si_discrete.R +++ b/R/si_discrete.R @@ -28,6 +28,23 @@ si_discrete <- function(S=9, I=1, beta=0.05, transmission_type=c("frequency","de ntime <- ceiling(max_time/d_time)+1L type <- match.arg(transmission_type) + model <- make_group("deterministic", numE=0L, numI=1L, numR=0L) + model$transmission_type <- transmission_type + model$S <- S + model$I <- I + model$beta <- beta + model$gamma <- 0 + model$repl <- 0 + model$cull <- 0 + output <- model$run(max_time, d_time) + rm(model) + + class(output) <- c("ipdmr_dt", class(output)) + attr(output, "plot_caption") <- str_c("discrete; ", type, "; d_time=", round(d_time,3)) + return(output) + + ### OLDER CODE BELOW HERE + i_dens <- function(i) 1 - exp(-beta * i) i_freq <- function(i) 1 - exp(-beta * i/N) i_fun <- if(type=="density") i_dens else i_freq diff --git a/R/suggest_boxes.R b/R/suggest_boxes.R new file mode 100644 index 0000000..beee4b5 --- /dev/null +++ b/R/suggest_boxes.R @@ -0,0 +1,62 @@ +#' Suggest a number of sub-compartments to obtain a suitable distribution of transition times +#' +#' @description +#' This is a utility function that takes a desired mean and standard deviation for +#' the distribution of transit times through a disease compartment, and suggests +#' a suitable rate and number of sub-compartments that matches the provided mean +#' and variance as closely as possible. +#' +#' @param mean the desired mean waiting time +#' @param sd the desired standard deviation in waiting time +#' +#' @returns the function returns a ggplot object illustrating the suggestions, +#' and prints the suggested number of sub-compartments and rates to screen +#' +#' @examples +#' suggest_boxes(mean=5, sd=1.4) +#' +#' @importFrom stats dgamma qgamma +#' +#' @export +suggest_boxes <- function(mean, sd){ + + qassert(mean, "N1(0,)") + qassert(sd, "N1(0,)") + + rate <- round(1/mean, 2) + + variance <- sd^2 + shape <- mean^2/variance^2 + + options <- seq(floor(shape), ceiling(shape), by=1L) + opt_shapes <- unique(options[options>0]) + vars <- sqrt(mean^2/opt_shapes) + + yields <- paste0(opt_shapes, " subcompartments with overall rate ", rate, ", which yields:\n\tmean = ", round(1/rate, 2), " (desired: ", round(mean,2), ")\n\tsd = ", round(sqrt(vars), 2), " (desired: ", round(sd,2), ")\n", sep="") + yields + + if(length(opt_shapes)==1L){ + cat("The closest match is ", yields, sep="") + #cat("The closest match is Erlang(shape=", shapes, ", scale=", scales, "), which yields:\n\tmean = ", round(shapes/rates, 2), " (desired: ", round(mean,2), ")\n\tsd = ", round(shapes^0.5/scales, 2), " (desired: ", round(sd,2), ")\n", sep="") + }else{ + cat("Possible matches are:\n", paste0("\t", str_replace_all(yields, "\n\t","\n\t\t"))) + } + + seq_along(opt_shapes) |> + lapply(\(x){ + shape <- opt_shapes[x] + scale <- mean/shape + range <- qgamma(c(0.001,1-0.001), shape, scale=scale) + tibble( + `#Boxes: `=as.character(shape), Time=seq(range[1],range[2],length.out=1e3), + `rate: `=as.character(rate) + ) |> + mutate(Density = dgamma(Time,shape,scale=scale)) + }) |> + bind_rows() |> + ggplot(aes(x=Time, y=Density, col=`#Boxes: `, lty=`rate: `)) + + geom_line() + + theme_light() + + theme(legend.position="bottom") + +} diff --git a/man/BetweenGroupClass.Rd b/man/BetweenGroupClass.Rd index ca9262f..966822d 100644 --- a/man/BetweenGroupClass.Rd +++ b/man/BetweenGroupClass.Rd @@ -69,6 +69,8 @@ summary(all_output) \item{\code{time}}{the current time point} +\item{\code{transmission_between}}{the between-group transmission type (frequency or density)} + \item{\code{state}}{a data frame of the current state of each group} } \if{html}{\out{}} diff --git a/man/group_models.Rd b/man/group_models.Rd index 77e611f..5f80b3b 100644 --- a/man/group_models.Rd +++ b/man/group_models.Rd @@ -15,7 +15,7 @@ sir_det( beta = 0.25, gamma = 0.2, delta = 0.05, - transmission_type = "frequency", + transmission_type = c("frequency", "density"), d_time = 1, max_time = 100 ) @@ -45,7 +45,7 @@ sir_stoc( beta = 0.25, gamma = 0.2, delta = 0.05, - transmission_type = "frequency", + transmission_type = c("frequency", "density"), d_time = 1, max_time = 100, iterations = 1L @@ -64,7 +64,7 @@ seir_stoc( vacc = 0, repl = 0, cull = 0, - transmission_type = "frequency", + transmission_type = c("frequency", "density"), d_time = 1, max_time = 100, iterations = 1L diff --git a/man/make_group.Rd b/man/make_group.Rd index 782150e..2e1bf07 100644 --- a/man/make_group.Rd +++ b/man/make_group.Rd @@ -7,19 +7,22 @@ make_group( update_type = c("deterministic", "stochastic"), numE = 3L, + numI = 1L, + numR = 1L, group_name = NA_character_, - model_type = c("SEIR", "SIR", "SI"), implementation = c("C++", "R6") ) } \arguments{ \item{update_type}{either stochastic or deterministic} -\item{numE}{the number of sub-compartments desired for the E state} +\item{numE}{the number of sub-compartments desired for the E state (0 or more)} -\item{group_name}{an optional name for the group} +\item{numI}{the number of sub-compartments desired for the I state (1 or more)} + +\item{numR}{the number of sub-compartments desired for the R state (0 or more)} -\item{model_type}{the compartmental model representation desired (currently only SEIR is supported)} +\item{group_name}{an optional name for the group} \item{implementation}{either C++ or R6} } diff --git a/man/multi_models.Rd b/man/multi_models.Rd index 3090c2d..4cf151f 100644 --- a/man/multi_models.Rd +++ b/man/multi_models.Rd @@ -21,6 +21,8 @@ multi_seir_det( vacc = 0, repl = 0, cull = 0, + transmission_within = c("frequency", "density"), + transmission_between = c("density", "frequency"), d_time = 1, max_time = 100 ) @@ -40,6 +42,8 @@ multi_seir_stoc( vacc = 0, repl = 0, cull = 0, + transmission_within = c("frequency", "density"), + transmission_between = c("density", "frequency"), d_time = 1, max_time = 100, iterations = 1L @@ -74,6 +78,10 @@ multi_seir_stoc( \item{cull}{the targeted culling rate parameter per unit time (must be positive)} +\item{transmission_within}{the within-group transmission type (frequency or density)} + +\item{transmission_between}{the between-group transmission type (frequency or density)} + \item{d_time}{the desired time step (delta time)} \item{max_time}{the desired maximum time point (must be greater than the time step)} diff --git a/man/suggest_boxes.Rd b/man/suggest_boxes.Rd new file mode 100644 index 0000000..1dc83e4 --- /dev/null +++ b/man/suggest_boxes.Rd @@ -0,0 +1,27 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/suggest_boxes.R +\name{suggest_boxes} +\alias{suggest_boxes} +\title{Suggest a number of sub-compartments to obtain a suitable distribution of transition times} +\usage{ +suggest_boxes(mean, sd) +} +\arguments{ +\item{mean}{the desired mean waiting time} + +\item{sd}{the desired standard deviation in waiting time} +} +\value{ +the function returns a ggplot object illustrating the suggestions, +and prints the suggested number of sub-compartments and rates to screen +} +\description{ +This is a utility function that takes a desired mean and standard deviation for +the distribution of transit times through a disease compartment, and suggests +a suitable rate and number of sub-compartments that matches the provided mean +and variance as closely as possible. +} +\examples{ +suggest_boxes(mean=5, sd=1.4) + +} diff --git a/notebooks/test_boxes.R b/notebooks/test_boxes.R new file mode 100644 index 0000000..308cf5d --- /dev/null +++ b/notebooks/test_boxes.R @@ -0,0 +1,29 @@ +seq(1,10,by=1) |> + lapply(\(x){ + model <- make_group(numE=0, numI=1, numR=x) + model$S <- 0 + model$I <- 0 + model$R <- 1 + model$beta <- 0 + model$gamma <- 0.1 + model$delta <- 0.1 + model$run(100,0.1) |> mutate(B=x, New=S-lag(S)) + }) |> + bind_rows() |> + ggplot(aes(x=Time, y=New, col=factor(B))) + + geom_line() + + geom_vline(xintercept=1/0.1) + + +## TODO: allow more flexibility in transmission type, e.g. function of N? + + +set.seed(2024-11-05) +r6res <- make_group(update_type = "deterministic", implementation = "R6")$run(10, 0.1) + +set.seed(2024-11-05) +cppres <- make_group(update_type = "deterministic", implementation = "C++")$run(10, 0.1) + +## Should be identical: +stopifnot(unlist(r6res) - unlist(cppres) == 0L) + diff --git a/src/SEIRmodel.h b/src/SEIRmodel.h index 88f9002..333ff3e 100644 --- a/src/SEIRmodel.h +++ b/src/SEIRmodel.h @@ -6,6 +6,7 @@ // virtual methods that will be needed for between-farm spread in C++: class BaseModel { + // TODO: static int for ID and vector of pointers for later retrievel against ID public: virtual bool is_cpp() const = 0; virtual int get_id() const = 0; @@ -14,6 +15,7 @@ class BaseModel virtual void set_trans_external(const double trans_external) = 0; virtual void update(double d_time) = 0; virtual Rcpp::DataFrame get_state() const = 0; + // TODO: N and I, but these will be templated virtual ~BaseModel() = default; }; @@ -29,6 +31,7 @@ enum class trans_type density }; +// TODO: clean this up, and specialise for C is array (i.e. redistribute is a no-op) template class subcomp; @@ -106,13 +109,13 @@ class subcomp }; -template +template struct state { T S = static_cast(99); - subcomp Es; // Initialised externally - T I = static_cast(1); - T R = static_cast(0); + subcomp Es; // Initialised externally + subcomp Is; // Initialised externally + subcomp Rs; // Initialised externally T N = static_cast(0); double timepoint = 0.0; }; @@ -136,8 +139,9 @@ void assertr(bool cond, std::string_view msg); template <> void assertr(bool cond, std::string_view msg) { } +// TODO: decompose the specialisation so there are fewer combinations??? // templated class for specialisation (stochastic/deterministic, sir/seir/numE=0vs3vsX??, debug) -template +template class SEIRmodel : public BaseModel { private: @@ -145,6 +149,15 @@ class SEIRmodel : public BaseModel using t_numE_type = const int; // typedef std::conditional::type t_numE_type; t_numE_type m_numE; + t_numE_type m_numI; + t_numE_type m_numR; + + static constexpr bool t_fixedE = t_numE>=0; + static constexpr bool t_hasE = t_numE!=0; + static constexpr bool t_fixedI = t_numI>=0; + static constexpr bool t_hasI = t_numI!=0; + static constexpr bool t_fixedR = t_numR>=0; + static constexpr bool t_hasR = t_numR!=0; std::string m_group_name; bool m_has_name; @@ -158,31 +171,60 @@ class SEIRmodel : public BaseModel t_update_type == update_type::deterministic, double, int >::type t_state_type; typedef typename std::conditional< - t_fixedE, std::array, std::vector + t_fixedE, std::array, std::vector >::type t_Etype; - state m_state; - state m_saved_state; + typedef typename std::conditional< + t_fixedI, std::array, std::vector + >::type t_Itype; + typedef typename std::conditional< + t_fixedR, std::array, std::vector + >::type t_Rtype; + state m_state; + state m_saved_state; int m_iteration = 0; public: - SEIRmodel(const int numE, const Rcpp::StringVector group_name) : + SEIRmodel(const int numE, const int numI, const int numR, const Rcpp::StringVector group_name) : m_numE(t_fixedE ? t_numE : numE), + m_numI(t_fixedI ? t_numI : numI), + m_numR(t_fixedR ? t_numR : numR), m_group_name(Rcpp::as< std::string > (group_name(0L))), m_has_name(!Rcpp::is_na(group_name)[0L]) { if constexpr (t_debug){ if (t_fixedE && (t_numE != numE)) Rcpp::stop("Invalid numE"); + if (t_fixedI && (t_numI != numI)) Rcpp::stop("Invalid numI"); + if (t_fixedR && (t_numR != numR)) Rcpp::stop("Invalid numR"); if (group_name.size()!=1L) Rcpp::stop("Invalid group_name"); } - // Re-size vector if needed: - if constexpr (!t_fixedE) - { - m_state.Es.values.resize(m_numE); + if constexpr (!t_hasE) { + m_pars.omega = 0.0; + } else { + if constexpr (!t_fixedE){ + m_state.Es.values.resize(m_numE); + } + m_state.Es.set_total(static_cast(0)); + } + + // We always have at least 1 I! + if constexpr (!t_fixedI){ + m_state.Is.values.resize(m_numI); + } + m_state.Is.set_total(static_cast(1)); + + if constexpr (!t_hasR) { + m_pars.delta = 0.0; + m_pars.vacc = 0.0; + } else { + if constexpr (!t_fixedR){ + m_state.Rs.values.resize(m_numR); + } + m_state.Rs.set_total(static_cast(0)); } - m_state.Es.set_total(static_cast(0)); + reset_N(); // Run save method: @@ -214,7 +256,9 @@ class SEIRmodel : public BaseModel { m_state = m_saved_state; // For compatibility with R6: - m_state.Es.reset(); + if constexpr (t_hasE) m_state.Es.reset(); + m_state.Is.reset(); + if constexpr (t_hasR) m_state.Rs.reset(); m_pars = m_saved_pars; } @@ -228,9 +272,9 @@ class SEIRmodel : public BaseModel { double val = 0.0; if(m_pars.transmission_type == trans_type::frequency){ - val = m_pars.beta * m_state.I / m_state.N; + val = m_pars.beta * m_state.Is.get_total() / m_state.N; }else if(m_pars.transmission_type == trans_type::density){ - val = m_pars.beta * m_state.I; + val = m_pars.beta * m_state.Is.get_total(); }else{ Rcpp::stop("Unrecognised m_pars.transmission_type"); } @@ -253,29 +297,61 @@ class SEIRmodel : public BaseModel std::array srates = { transmission_rate(), m_pars.vacc }; std::array leave_S = apply_rates<2>(old_state.S, srates, d_time); m_state.S -= (leave_S[0] + leave_S[1]); - m_state.Es.values[0L] += leave_S[0]; - m_state.R += leave_S[1]; - - t_state_type EtoS = static_cast(0); - t_state_type Ecarry = static_cast(0); - std::array erates = { m_pars.omega*m_numE, m_pars.repl }; - for(int i=0; i leave_E = apply_rates<2>(old_state.Es.values[i], erates, d_time); - m_state.Es.values[i] += Ecarry - leave_E[0] - leave_E[1]; - Ecarry = leave_E[0]; - EtoS += leave_E[1]; + if constexpr (t_hasE) { + m_state.Es.values[0] += leave_S[0]; + }else{ + m_state.Is.values[0] += leave_S[0]; + } + if constexpr (t_hasR) { + m_state.Rs.values[0] += leave_S[1]; + } + + if constexpr (t_hasE) { + t_state_type carry = static_cast(0); + t_state_type toS = static_cast(0); + std::array rates = { m_pars.omega*m_numE, m_pars.repl }; + for(int i=0; i<(t_numE>0 ? t_numE : m_numE); ++i){ + std::array leave = apply_rates<2>(old_state.Es.values[i], rates, d_time); + m_state.Es.values[i] += carry - leave[0] - leave[1]; + carry = leave[0]; + toS += leave[1]; + } + m_state.S += toS; + m_state.Is.values[0] += carry; } - m_state.S += EtoS; - std::array irates = { m_pars.gamma, m_pars.repl + m_pars.cull }; - std::array leave_I = apply_rates<2>(old_state.I, irates, d_time); - m_state.I += Ecarry - leave_I[0] - leave_I[1]; - m_state.S += leave_I[1]; + // We always have I! + { + t_state_type carry = static_cast(0); + t_state_type toS = static_cast(0); + std::array rates = { m_pars.gamma*m_numI, m_pars.repl + m_pars.cull }; + for(int i=0; i<(t_numI>0 ? t_numI : m_numI); ++i){ + std::array leave = apply_rates<2>(old_state.Is.values[i], rates, d_time); + m_state.Is.values[i] += carry - leave[0] - leave[1]; + carry = leave[0]; + toS += leave[1]; + } + m_state.S += toS; + if constexpr (t_hasR) { + m_state.Rs.values[0] += carry; + } else { + m_state.S += carry; + } + } - std::array rrates = { m_pars.delta + m_pars.repl }; - std::array leave_R = apply_rates<1>(old_state.R, rrates, d_time); - m_state.R += leave_I[0] - leave_R[0]; - m_state.S += leave_R[0]; + if constexpr (t_hasR) { + t_state_type carry = static_cast(0); + t_state_type toS = static_cast(0); + std::array rates = { m_pars.delta*m_numR, m_pars.repl }; + for(int i=0; i<(t_numR>0 ? t_numR : m_numR); ++i){ + std::array leave = apply_rates<2>(old_state.Rs.values[i], rates, d_time); + m_state.Rs.values[i] += carry - leave[0] - leave[1]; + carry = leave[0]; + toS += leave[1]; + } + m_state.S += toS; + m_state.S += carry; + } m_state.timepoint += d_time; check_state(); @@ -287,8 +363,8 @@ class SEIRmodel : public BaseModel Rcpp::Named("Time") = m_state.timepoint, Rcpp::Named("S") = m_state.S, Rcpp::Named("E") = m_state.Es.get_total(), - Rcpp::Named("I") = m_state.I, - Rcpp::Named("R") = m_state.R + Rcpp::Named("I") = m_state.Is.get_total(), + Rcpp::Named("R") = m_state.Rs.get_total() ); if(m_has_name) @@ -296,8 +372,14 @@ class SEIRmodel : public BaseModel Rcpp::String group_name = m_group_name; rv.push_front(group_name, "Group"); } + if constexpr (!t_hasR) { + rv.erase(4); + } + if constexpr (!t_hasE) { + rv.erase(2); + } - return rv; + return Rcpp::as(rv); } // New methods: @@ -340,7 +422,7 @@ class SEIRmodel : public BaseModel void reset_N() { - m_state.N = m_state.S+m_state.Es.get_total()+m_state.I+m_state.R; + m_state.N = m_state.S+m_state.Es.get_total()+m_state.Is.get_total()+m_state.Rs.get_total(); check_state(); } @@ -356,6 +438,7 @@ class SEIRmodel : public BaseModel void set_E(t_state_type val) { + if constexpr (!t_hasE) Rcpp::stop("Model contains no E compartments!"); m_state.Es.set_total(val); reset_N(); } @@ -366,22 +449,23 @@ class SEIRmodel : public BaseModel void set_I(t_state_type val) { - m_state.I = val; + m_state.Is.set_total(val); reset_N(); } t_state_type get_I() const { - return m_state.I; + return m_state.Is.get_total(); } void set_R(t_state_type val) { - m_state.R = val; + if constexpr (!t_hasR) Rcpp::stop("Model contains no R compartments!"); + m_state.Rs.set_total(val); reset_N(); } t_state_type get_R() const { - return m_state.R; + return m_state.Rs.get_total();; } t_state_type get_N() const @@ -400,6 +484,7 @@ class SEIRmodel : public BaseModel void set_omega(double val) { + if constexpr(!t_hasE) Rcpp::stop("Unable to change omega: no E state!"); m_pars.omega = val; } double get_omega() const @@ -418,6 +503,7 @@ class SEIRmodel : public BaseModel void set_delta(double val) { + if constexpr(!t_hasR) Rcpp::stop("Unable to change delta: no R state!"); m_pars.delta = val; } double get_delta() const @@ -445,6 +531,7 @@ class SEIRmodel : public BaseModel void set_vacc(double val) { + if constexpr(!t_hasR) Rcpp::stop("Unable to change vacc: no R state!"); m_pars.vacc = val; } double get_vacc() const @@ -493,7 +580,7 @@ class SEIRmodel : public BaseModel { if constexpr (t_debug) { - t_state_type newN = m_state.S+m_state.Es.get_total()+m_state.I+m_state.R; + t_state_type newN = m_state.S+m_state.Es.get_total()+m_state.Is.get_total()+m_state.Rs.get_total(); if constexpr (t_update_type==update_type::deterministic){ if(std::abs(newN - m_state.N) > 1e-6) Rcpp::stop("Error in update: N has changed!"); }else{ @@ -509,10 +596,12 @@ class SEIRmodel : public BaseModel Rcpp::Rcout << "An SEIR model with "; if (m_has_name) Rcpp::Rcout << "identifier/name '" << m_group_name << "' and "; Rcpp::Rcout << "the following properties:\n\t"; - Rcpp::Rcout << "S/E/I/R (N) = " << m_state.S << "/" << m_state.Es.get_total() << "/" << m_state.I << "/" << m_state.R << " (" << m_state.N << ")\n\t"; + Rcpp::Rcout << "S/E/I/R (N) = " << m_state.S << "/" << m_state.Es.get_total() << "/" << m_state.Is.get_total() << "/" << m_state.Rs.get_total() << " (" << m_state.N << ")\n\t"; Rcpp::Rcout << "beta/omega/gamma/delta = " << m_pars.beta << "/" << m_pars.omega << "/" << m_pars.gamma << "/" << m_pars.delta << "\n\t"; Rcpp::Rcout << "vacc/repl/cull = " << m_pars.vacc << "/" << m_pars.repl << "/" << m_pars.cull << "\n\t"; Rcpp::Rcout << "E compartments = " << m_numE << "\n\t"; + Rcpp::Rcout << "I compartments = " << m_numI << "\n\t"; + Rcpp::Rcout << "R compartments = " << m_numR << "\n\t"; Rcpp::Rcout << "external transmission = " << m_pars.trans_external << "\n\t"; if constexpr (t_update_type==update_type::deterministic){ Rcpp::Rcout << "update type = " << "deterministic" << "\n\t"; @@ -583,8 +672,14 @@ class SEIRmodel : public BaseModel Rcpp::String group_name = m_group_name; rv.push_front(group_name, "Group"); } + if constexpr (!t_hasR) { + rv.erase(4); + } + if constexpr (!t_hasE) { + rv.erase(2); + } - return rv; + return Rcpp::as(rv); } }; diff --git a/src/ipdmr_module.cpp b/src/ipdmr_module.cpp index e978862..4d1a005 100644 --- a/src/ipdmr_module.cpp +++ b/src/ipdmr_module.cpp @@ -20,120 +20,1396 @@ RCPP_MODULE(IPDMRmodule){ using namespace Rcpp; - using SEIRdetN = SEIRmodel; - class_("SEIRdetN") - .constructor("Constructor") - .factory(invalidate_default_constructor) - - .method("show", &SEIRdetN::show, "The show/print method") - .method("update", &SEIRdetN::update, "The update method") - .method("run", &SEIRdetN::run, "The run method") - .method("save", &SEIRdetN::save, "The save method") - .method("reset", &SEIRdetN::reset, "The reset method") - - .property("state", &SEIRdetN::get_state, "Get current state") - .property("S", &SEIRdetN::get_S, &SEIRdetN::set_S, "Get/set current S") - .property("E", &SEIRdetN::get_E, &SEIRdetN::set_E, "Get/set current E") - .property("I", &SEIRdetN::get_I, &SEIRdetN::set_I, "Get/set current I") - .property("R", &SEIRdetN::get_R, &SEIRdetN::set_R, "Get/set current R") - .property("N", &SEIRdetN::get_N, "Get current N") - .property("beta", &SEIRdetN::get_beta, &SEIRdetN::set_beta, "Get/set current beta") - .property("omega", &SEIRdetN::get_omega, &SEIRdetN::set_omega, "Get/set current omega") - .property("gamma", &SEIRdetN::get_gamma, &SEIRdetN::set_gamma, "Get/set current gamma") - .property("delta", &SEIRdetN::get_delta, &SEIRdetN::set_delta, "Get/set current delta") - .property("repl", &SEIRdetN::get_repl, &SEIRdetN::set_repl, "Get/set current repl") - .property("cull", &SEIRdetN::get_cull, &SEIRdetN::set_cull, "Get/set current cull") - .property("vacc", &SEIRdetN::get_vacc, &SEIRdetN::set_vacc, "Get/set current vacc") - .property("time", &SEIRdetN::get_time, "Get current time") - .property("trans_external", &SEIRdetN::get_trans_external, &SEIRdetN::set_trans_external, "Get/set current trans_external") - .property("transmission_type", &SEIRdetN::get_trans_type, &SEIRdetN::set_trans_type, "Get/set current trans_type") - ; - - using SEIRstocN = SEIRmodel; - class_("SEIRstocN") - .constructor("Constructor") - .factory(invalidate_default_constructor) - - .method("show", &SEIRstocN::show, "The show/print method") - .method("update", &SEIRstocN::update, "The update method") - .method("run", &SEIRstocN::run, "The run method") - .method("save", &SEIRstocN::save, "The save method") - .method("reset", &SEIRstocN::reset, "The reset method") - - .property("state", &SEIRstocN::get_state, "Get current state") - .property("S", &SEIRstocN::get_S, &SEIRstocN::set_S, "Get/set current S") - .property("E", &SEIRstocN::get_E, &SEIRstocN::set_E, "Get/set current E") - .property("I", &SEIRstocN::get_I, &SEIRstocN::set_I, "Get/set current I") - .property("R", &SEIRstocN::get_R, &SEIRstocN::set_R, "Get/set current R") - .property("N", &SEIRstocN::get_N, "Get current N") - .property("beta", &SEIRstocN::get_beta, &SEIRstocN::set_beta, "Get/set current beta") - .property("omega", &SEIRstocN::get_omega, &SEIRstocN::set_omega, "Get/set current omega") - .property("gamma", &SEIRstocN::get_gamma, &SEIRstocN::set_gamma, "Get/set current gamma") - .property("delta", &SEIRstocN::get_delta, &SEIRstocN::set_delta, "Get/set current delta") - .property("repl", &SEIRstocN::get_repl, &SEIRstocN::set_repl, "Get/set current repl") - .property("cull", &SEIRstocN::get_cull, &SEIRstocN::set_cull, "Get/set current cull") - .property("vacc", &SEIRstocN::get_vacc, &SEIRstocN::set_vacc, "Get/set current vacc") - .property("time", &SEIRstocN::get_time, "Get current time") - .property("trans_external", &SEIRstocN::get_trans_external, &SEIRstocN::set_trans_external, "Get/set current trans_external") - .property("transmission_type", &SEIRstocN::get_trans_type, &SEIRstocN::set_trans_type, "Get/set current trans_type") - ; - - using SEIRdet3 = SEIRmodel; - class_("SEIRdet3") - .constructor("Constructor") - .factory(invalidate_default_constructor) - - .method("show", &SEIRdet3::show, "The show/print method") - .method("update", &SEIRdet3::update, "The update method") - .method("run", &SEIRdet3::run, "The run method") - .method("save", &SEIRdet3::save, "The save method") - .method("reset", &SEIRdet3::reset, "The reset method") - - .property("state", &SEIRdet3::get_state, "Get current state") - .property("S", &SEIRdet3::get_S, &SEIRdet3::set_S, "Get/set current S") - .property("E", &SEIRdet3::get_E, &SEIRdet3::set_E, "Get/set current E") - .property("I", &SEIRdet3::get_I, &SEIRdet3::set_I, "Get/set current I") - .property("R", &SEIRdet3::get_R, &SEIRdet3::set_R, "Get/set current R") - .property("N", &SEIRdet3::get_N, "Get current N") - .property("beta", &SEIRdet3::get_beta, &SEIRdet3::set_beta, "Get/set current beta") - .property("omega", &SEIRdet3::get_omega, &SEIRdet3::set_omega, "Get/set current omega") - .property("gamma", &SEIRdet3::get_gamma, &SEIRdet3::set_gamma, "Get/set current gamma") - .property("delta", &SEIRdet3::get_delta, &SEIRdet3::set_delta, "Get/set current delta") - .property("repl", &SEIRdet3::get_repl, &SEIRdet3::set_repl, "Get/set current repl") - .property("cull", &SEIRdet3::get_cull, &SEIRdet3::set_cull, "Get/set current cull") - .property("vacc", &SEIRdet3::get_vacc, &SEIRdet3::set_vacc, "Get/set current vacc") - .property("time", &SEIRdet3::get_time, "Get current time") - .property("trans_external", &SEIRdet3::get_trans_external, &SEIRdet3::set_trans_external, "Get/set current trans_external") - .property("transmission_type", &SEIRdet3::get_trans_type, &SEIRdet3::set_trans_type, "Get/set current trans_type") - ; - - using SEIRstoc3 = SEIRmodel; - class_("SEIRstoc3") - .constructor("Constructor") - .factory(invalidate_default_constructor) - - .method("show", &SEIRstoc3::show, "The show/print method") - .method("update", &SEIRstoc3::update, "The update method") - .method("run", &SEIRstoc3::run, "The run method") - .method("save", &SEIRstoc3::save, "The save method") - .method("reset", &SEIRstoc3::reset, "The reset method") - - .property("state", &SEIRstoc3::get_state, "Get current state") - .property("S", &SEIRstoc3::get_S, &SEIRstoc3::set_S, "Get/set current S") - .property("E", &SEIRstoc3::get_E, &SEIRstoc3::set_E, "Get/set current E") - .property("I", &SEIRstoc3::get_I, &SEIRstoc3::set_I, "Get/set current I") - .property("R", &SEIRstoc3::get_R, &SEIRstoc3::set_R, "Get/set current R") - .property("N", &SEIRstoc3::get_N, "Get current N") - .property("beta", &SEIRstoc3::get_beta, &SEIRstoc3::set_beta, "Get/set current beta") - .property("omega", &SEIRstoc3::get_omega, &SEIRstoc3::set_omega, "Get/set current omega") - .property("gamma", &SEIRstoc3::get_gamma, &SEIRstoc3::set_gamma, "Get/set current gamma") - .property("delta", &SEIRstoc3::get_delta, &SEIRstoc3::set_delta, "Get/set current delta") - .property("repl", &SEIRstoc3::get_repl, &SEIRstoc3::set_repl, "Get/set current repl") - .property("cull", &SEIRstoc3::get_cull, &SEIRstoc3::set_cull, "Get/set current cull") - .property("vacc", &SEIRstoc3::get_vacc, &SEIRstoc3::set_vacc, "Get/set current vacc") - .property("time", &SEIRstoc3::get_time, "Get current time") - .property("trans_external", &SEIRstoc3::get_trans_external, &SEIRstoc3::set_trans_external, "Get/set current trans_external") - .property("transmission_type", &SEIRstoc3::get_trans_type, &SEIRstoc3::set_trans_type, "Get/set current trans_type") + using SEIRdetNNN = SEIRmodel; + class_("SEIRdetNNN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetNNN::show, "The show/print method") + .method("update", &SEIRdetNNN::update, "The update method") + .method("run", &SEIRdetNNN::run, "The run method") + .method("save", &SEIRdetNNN::save, "The save method") + .method("reset", &SEIRdetNNN::reset, "The reset method") + + .property("state", &SEIRdetNNN::get_state, "Get current state") + .property("S", &SEIRdetNNN::get_S, &SEIRdetNNN::set_S, "Get/set current S") + .property("E", &SEIRdetNNN::get_E, &SEIRdetNNN::set_E, "Get/set current E") + .property("I", &SEIRdetNNN::get_I, &SEIRdetNNN::set_I, "Get/set current I") + .property("R", &SEIRdetNNN::get_R, &SEIRdetNNN::set_R, "Get/set current R") + .property("N", &SEIRdetNNN::get_N, "Get current N") + .property("beta", &SEIRdetNNN::get_beta, &SEIRdetNNN::set_beta, "Get/set current beta") + .property("omega", &SEIRdetNNN::get_omega, &SEIRdetNNN::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetNNN::get_gamma, &SEIRdetNNN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetNNN::get_delta, &SEIRdetNNN::set_delta, "Get/set current delta") + .property("repl", &SEIRdetNNN::get_repl, &SEIRdetNNN::set_repl, "Get/set current repl") + .property("cull", &SEIRdetNNN::get_cull, &SEIRdetNNN::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetNNN::get_vacc, &SEIRdetNNN::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetNNN::get_time, "Get current time") + .property("trans_external", &SEIRdetNNN::get_trans_external, &SEIRdetNNN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetNNN::get_trans_type, &SEIRdetNNN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdetNN0 = SEIRmodel; + class_("SEIRdetNN0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetNN0::show, "The show/print method") + .method("update", &SEIRdetNN0::update, "The update method") + .method("run", &SEIRdetNN0::run, "The run method") + .method("save", &SEIRdetNN0::save, "The save method") + .method("reset", &SEIRdetNN0::reset, "The reset method") + + .property("state", &SEIRdetNN0::get_state, "Get current state") + .property("S", &SEIRdetNN0::get_S, &SEIRdetNN0::set_S, "Get/set current S") + .property("E", &SEIRdetNN0::get_E, &SEIRdetNN0::set_E, "Get/set current E") + .property("I", &SEIRdetNN0::get_I, &SEIRdetNN0::set_I, "Get/set current I") + .property("R", &SEIRdetNN0::get_R, &SEIRdetNN0::set_R, "Get/set current R") + .property("N", &SEIRdetNN0::get_N, "Get current N") + .property("beta", &SEIRdetNN0::get_beta, &SEIRdetNN0::set_beta, "Get/set current beta") + .property("omega", &SEIRdetNN0::get_omega, &SEIRdetNN0::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetNN0::get_gamma, &SEIRdetNN0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetNN0::get_delta, &SEIRdetNN0::set_delta, "Get/set current delta") + .property("repl", &SEIRdetNN0::get_repl, &SEIRdetNN0::set_repl, "Get/set current repl") + .property("cull", &SEIRdetNN0::get_cull, &SEIRdetNN0::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetNN0::get_vacc, &SEIRdetNN0::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetNN0::get_time, "Get current time") + .property("trans_external", &SEIRdetNN0::get_trans_external, &SEIRdetNN0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetNN0::get_trans_type, &SEIRdetNN0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdetNN1 = SEIRmodel; + class_("SEIRdetNN1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetNN1::show, "The show/print method") + .method("update", &SEIRdetNN1::update, "The update method") + .method("run", &SEIRdetNN1::run, "The run method") + .method("save", &SEIRdetNN1::save, "The save method") + .method("reset", &SEIRdetNN1::reset, "The reset method") + + .property("state", &SEIRdetNN1::get_state, "Get current state") + .property("S", &SEIRdetNN1::get_S, &SEIRdetNN1::set_S, "Get/set current S") + .property("E", &SEIRdetNN1::get_E, &SEIRdetNN1::set_E, "Get/set current E") + .property("I", &SEIRdetNN1::get_I, &SEIRdetNN1::set_I, "Get/set current I") + .property("R", &SEIRdetNN1::get_R, &SEIRdetNN1::set_R, "Get/set current R") + .property("N", &SEIRdetNN1::get_N, "Get current N") + .property("beta", &SEIRdetNN1::get_beta, &SEIRdetNN1::set_beta, "Get/set current beta") + .property("omega", &SEIRdetNN1::get_omega, &SEIRdetNN1::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetNN1::get_gamma, &SEIRdetNN1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetNN1::get_delta, &SEIRdetNN1::set_delta, "Get/set current delta") + .property("repl", &SEIRdetNN1::get_repl, &SEIRdetNN1::set_repl, "Get/set current repl") + .property("cull", &SEIRdetNN1::get_cull, &SEIRdetNN1::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetNN1::get_vacc, &SEIRdetNN1::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetNN1::get_time, "Get current time") + .property("trans_external", &SEIRdetNN1::get_trans_external, &SEIRdetNN1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetNN1::get_trans_type, &SEIRdetNN1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdetN1N = SEIRmodel; + class_("SEIRdetN1N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetN1N::show, "The show/print method") + .method("update", &SEIRdetN1N::update, "The update method") + .method("run", &SEIRdetN1N::run, "The run method") + .method("save", &SEIRdetN1N::save, "The save method") + .method("reset", &SEIRdetN1N::reset, "The reset method") + + .property("state", &SEIRdetN1N::get_state, "Get current state") + .property("S", &SEIRdetN1N::get_S, &SEIRdetN1N::set_S, "Get/set current S") + .property("E", &SEIRdetN1N::get_E, &SEIRdetN1N::set_E, "Get/set current E") + .property("I", &SEIRdetN1N::get_I, &SEIRdetN1N::set_I, "Get/set current I") + .property("R", &SEIRdetN1N::get_R, &SEIRdetN1N::set_R, "Get/set current R") + .property("N", &SEIRdetN1N::get_N, "Get current N") + .property("beta", &SEIRdetN1N::get_beta, &SEIRdetN1N::set_beta, "Get/set current beta") + .property("omega", &SEIRdetN1N::get_omega, &SEIRdetN1N::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetN1N::get_gamma, &SEIRdetN1N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetN1N::get_delta, &SEIRdetN1N::set_delta, "Get/set current delta") + .property("repl", &SEIRdetN1N::get_repl, &SEIRdetN1N::set_repl, "Get/set current repl") + .property("cull", &SEIRdetN1N::get_cull, &SEIRdetN1N::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetN1N::get_vacc, &SEIRdetN1N::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetN1N::get_time, "Get current time") + .property("trans_external", &SEIRdetN1N::get_trans_external, &SEIRdetN1N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetN1N::get_trans_type, &SEIRdetN1N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdetN10 = SEIRmodel; + class_("SEIRdetN10") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetN10::show, "The show/print method") + .method("update", &SEIRdetN10::update, "The update method") + .method("run", &SEIRdetN10::run, "The run method") + .method("save", &SEIRdetN10::save, "The save method") + .method("reset", &SEIRdetN10::reset, "The reset method") + + .property("state", &SEIRdetN10::get_state, "Get current state") + .property("S", &SEIRdetN10::get_S, &SEIRdetN10::set_S, "Get/set current S") + .property("E", &SEIRdetN10::get_E, &SEIRdetN10::set_E, "Get/set current E") + .property("I", &SEIRdetN10::get_I, &SEIRdetN10::set_I, "Get/set current I") + .property("R", &SEIRdetN10::get_R, &SEIRdetN10::set_R, "Get/set current R") + .property("N", &SEIRdetN10::get_N, "Get current N") + .property("beta", &SEIRdetN10::get_beta, &SEIRdetN10::set_beta, "Get/set current beta") + .property("omega", &SEIRdetN10::get_omega, &SEIRdetN10::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetN10::get_gamma, &SEIRdetN10::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetN10::get_delta, &SEIRdetN10::set_delta, "Get/set current delta") + .property("repl", &SEIRdetN10::get_repl, &SEIRdetN10::set_repl, "Get/set current repl") + .property("cull", &SEIRdetN10::get_cull, &SEIRdetN10::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetN10::get_vacc, &SEIRdetN10::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetN10::get_time, "Get current time") + .property("trans_external", &SEIRdetN10::get_trans_external, &SEIRdetN10::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetN10::get_trans_type, &SEIRdetN10::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdetN11 = SEIRmodel; + class_("SEIRdetN11") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdetN11::show, "The show/print method") + .method("update", &SEIRdetN11::update, "The update method") + .method("run", &SEIRdetN11::run, "The run method") + .method("save", &SEIRdetN11::save, "The save method") + .method("reset", &SEIRdetN11::reset, "The reset method") + + .property("state", &SEIRdetN11::get_state, "Get current state") + .property("S", &SEIRdetN11::get_S, &SEIRdetN11::set_S, "Get/set current S") + .property("E", &SEIRdetN11::get_E, &SEIRdetN11::set_E, "Get/set current E") + .property("I", &SEIRdetN11::get_I, &SEIRdetN11::set_I, "Get/set current I") + .property("R", &SEIRdetN11::get_R, &SEIRdetN11::set_R, "Get/set current R") + .property("N", &SEIRdetN11::get_N, "Get current N") + .property("beta", &SEIRdetN11::get_beta, &SEIRdetN11::set_beta, "Get/set current beta") + .property("omega", &SEIRdetN11::get_omega, &SEIRdetN11::set_omega, "Get/set current omega") + .property("gamma", &SEIRdetN11::get_gamma, &SEIRdetN11::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdetN11::get_delta, &SEIRdetN11::set_delta, "Get/set current delta") + .property("repl", &SEIRdetN11::get_repl, &SEIRdetN11::set_repl, "Get/set current repl") + .property("cull", &SEIRdetN11::get_cull, &SEIRdetN11::set_cull, "Get/set current cull") + .property("vacc", &SEIRdetN11::get_vacc, &SEIRdetN11::set_vacc, "Get/set current vacc") + .property("time", &SEIRdetN11::get_time, "Get current time") + .property("trans_external", &SEIRdetN11::get_trans_external, &SEIRdetN11::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdetN11::get_trans_type, &SEIRdetN11::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet0NN = SEIRmodel; + class_("SEIRdet0NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet0NN::show, "The show/print method") + .method("update", &SEIRdet0NN::update, "The update method") + .method("run", &SEIRdet0NN::run, "The run method") + .method("save", &SEIRdet0NN::save, "The save method") + .method("reset", &SEIRdet0NN::reset, "The reset method") + + .property("state", &SEIRdet0NN::get_state, "Get current state") + .property("S", &SEIRdet0NN::get_S, &SEIRdet0NN::set_S, "Get/set current S") + .property("E", &SEIRdet0NN::get_E, &SEIRdet0NN::set_E, "Get/set current E") + .property("I", &SEIRdet0NN::get_I, &SEIRdet0NN::set_I, "Get/set current I") + .property("R", &SEIRdet0NN::get_R, &SEIRdet0NN::set_R, "Get/set current R") + .property("N", &SEIRdet0NN::get_N, "Get current N") + .property("beta", &SEIRdet0NN::get_beta, &SEIRdet0NN::set_beta, "Get/set current beta") + .property("omega", &SEIRdet0NN::get_omega, &SEIRdet0NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet0NN::get_gamma, &SEIRdet0NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet0NN::get_delta, &SEIRdet0NN::set_delta, "Get/set current delta") + .property("repl", &SEIRdet0NN::get_repl, &SEIRdet0NN::set_repl, "Get/set current repl") + .property("cull", &SEIRdet0NN::get_cull, &SEIRdet0NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet0NN::get_vacc, &SEIRdet0NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet0NN::get_time, "Get current time") + .property("trans_external", &SEIRdet0NN::get_trans_external, &SEIRdet0NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet0NN::get_trans_type, &SEIRdet0NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet0N0 = SEIRmodel; + class_("SEIRdet0N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet0N0::show, "The show/print method") + .method("update", &SEIRdet0N0::update, "The update method") + .method("run", &SEIRdet0N0::run, "The run method") + .method("save", &SEIRdet0N0::save, "The save method") + .method("reset", &SEIRdet0N0::reset, "The reset method") + + .property("state", &SEIRdet0N0::get_state, "Get current state") + .property("S", &SEIRdet0N0::get_S, &SEIRdet0N0::set_S, "Get/set current S") + .property("E", &SEIRdet0N0::get_E, &SEIRdet0N0::set_E, "Get/set current E") + .property("I", &SEIRdet0N0::get_I, &SEIRdet0N0::set_I, "Get/set current I") + .property("R", &SEIRdet0N0::get_R, &SEIRdet0N0::set_R, "Get/set current R") + .property("N", &SEIRdet0N0::get_N, "Get current N") + .property("beta", &SEIRdet0N0::get_beta, &SEIRdet0N0::set_beta, "Get/set current beta") + .property("omega", &SEIRdet0N0::get_omega, &SEIRdet0N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet0N0::get_gamma, &SEIRdet0N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet0N0::get_delta, &SEIRdet0N0::set_delta, "Get/set current delta") + .property("repl", &SEIRdet0N0::get_repl, &SEIRdet0N0::set_repl, "Get/set current repl") + .property("cull", &SEIRdet0N0::get_cull, &SEIRdet0N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet0N0::get_vacc, &SEIRdet0N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet0N0::get_time, "Get current time") + .property("trans_external", &SEIRdet0N0::get_trans_external, &SEIRdet0N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet0N0::get_trans_type, &SEIRdet0N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet0N1 = SEIRmodel; + class_("SEIRdet0N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet0N1::show, "The show/print method") + .method("update", &SEIRdet0N1::update, "The update method") + .method("run", &SEIRdet0N1::run, "The run method") + .method("save", &SEIRdet0N1::save, "The save method") + .method("reset", &SEIRdet0N1::reset, "The reset method") + + .property("state", &SEIRdet0N1::get_state, "Get current state") + .property("S", &SEIRdet0N1::get_S, &SEIRdet0N1::set_S, "Get/set current S") + .property("E", &SEIRdet0N1::get_E, &SEIRdet0N1::set_E, "Get/set current E") + .property("I", &SEIRdet0N1::get_I, &SEIRdet0N1::set_I, "Get/set current I") + .property("R", &SEIRdet0N1::get_R, &SEIRdet0N1::set_R, "Get/set current R") + .property("N", &SEIRdet0N1::get_N, "Get current N") + .property("beta", &SEIRdet0N1::get_beta, &SEIRdet0N1::set_beta, "Get/set current beta") + .property("omega", &SEIRdet0N1::get_omega, &SEIRdet0N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet0N1::get_gamma, &SEIRdet0N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet0N1::get_delta, &SEIRdet0N1::set_delta, "Get/set current delta") + .property("repl", &SEIRdet0N1::get_repl, &SEIRdet0N1::set_repl, "Get/set current repl") + .property("cull", &SEIRdet0N1::get_cull, &SEIRdet0N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet0N1::get_vacc, &SEIRdet0N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet0N1::get_time, "Get current time") + .property("trans_external", &SEIRdet0N1::get_trans_external, &SEIRdet0N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet0N1::get_trans_type, &SEIRdet0N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet01N = SEIRmodel; + class_("SEIRdet01N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet01N::show, "The show/print method") + .method("update", &SEIRdet01N::update, "The update method") + .method("run", &SEIRdet01N::run, "The run method") + .method("save", &SEIRdet01N::save, "The save method") + .method("reset", &SEIRdet01N::reset, "The reset method") + + .property("state", &SEIRdet01N::get_state, "Get current state") + .property("S", &SEIRdet01N::get_S, &SEIRdet01N::set_S, "Get/set current S") + .property("E", &SEIRdet01N::get_E, &SEIRdet01N::set_E, "Get/set current E") + .property("I", &SEIRdet01N::get_I, &SEIRdet01N::set_I, "Get/set current I") + .property("R", &SEIRdet01N::get_R, &SEIRdet01N::set_R, "Get/set current R") + .property("N", &SEIRdet01N::get_N, "Get current N") + .property("beta", &SEIRdet01N::get_beta, &SEIRdet01N::set_beta, "Get/set current beta") + .property("omega", &SEIRdet01N::get_omega, &SEIRdet01N::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet01N::get_gamma, &SEIRdet01N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet01N::get_delta, &SEIRdet01N::set_delta, "Get/set current delta") + .property("repl", &SEIRdet01N::get_repl, &SEIRdet01N::set_repl, "Get/set current repl") + .property("cull", &SEIRdet01N::get_cull, &SEIRdet01N::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet01N::get_vacc, &SEIRdet01N::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet01N::get_time, "Get current time") + .property("trans_external", &SEIRdet01N::get_trans_external, &SEIRdet01N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet01N::get_trans_type, &SEIRdet01N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet010 = SEIRmodel; + class_("SEIRdet010") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet010::show, "The show/print method") + .method("update", &SEIRdet010::update, "The update method") + .method("run", &SEIRdet010::run, "The run method") + .method("save", &SEIRdet010::save, "The save method") + .method("reset", &SEIRdet010::reset, "The reset method") + + .property("state", &SEIRdet010::get_state, "Get current state") + .property("S", &SEIRdet010::get_S, &SEIRdet010::set_S, "Get/set current S") + .property("E", &SEIRdet010::get_E, &SEIRdet010::set_E, "Get/set current E") + .property("I", &SEIRdet010::get_I, &SEIRdet010::set_I, "Get/set current I") + .property("R", &SEIRdet010::get_R, &SEIRdet010::set_R, "Get/set current R") + .property("N", &SEIRdet010::get_N, "Get current N") + .property("beta", &SEIRdet010::get_beta, &SEIRdet010::set_beta, "Get/set current beta") + .property("omega", &SEIRdet010::get_omega, &SEIRdet010::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet010::get_gamma, &SEIRdet010::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet010::get_delta, &SEIRdet010::set_delta, "Get/set current delta") + .property("repl", &SEIRdet010::get_repl, &SEIRdet010::set_repl, "Get/set current repl") + .property("cull", &SEIRdet010::get_cull, &SEIRdet010::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet010::get_vacc, &SEIRdet010::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet010::get_time, "Get current time") + .property("trans_external", &SEIRdet010::get_trans_external, &SEIRdet010::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet010::get_trans_type, &SEIRdet010::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet011 = SEIRmodel; + class_("SEIRdet011") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet011::show, "The show/print method") + .method("update", &SEIRdet011::update, "The update method") + .method("run", &SEIRdet011::run, "The run method") + .method("save", &SEIRdet011::save, "The save method") + .method("reset", &SEIRdet011::reset, "The reset method") + + .property("state", &SEIRdet011::get_state, "Get current state") + .property("S", &SEIRdet011::get_S, &SEIRdet011::set_S, "Get/set current S") + .property("E", &SEIRdet011::get_E, &SEIRdet011::set_E, "Get/set current E") + .property("I", &SEIRdet011::get_I, &SEIRdet011::set_I, "Get/set current I") + .property("R", &SEIRdet011::get_R, &SEIRdet011::set_R, "Get/set current R") + .property("N", &SEIRdet011::get_N, "Get current N") + .property("beta", &SEIRdet011::get_beta, &SEIRdet011::set_beta, "Get/set current beta") + .property("omega", &SEIRdet011::get_omega, &SEIRdet011::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet011::get_gamma, &SEIRdet011::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet011::get_delta, &SEIRdet011::set_delta, "Get/set current delta") + .property("repl", &SEIRdet011::get_repl, &SEIRdet011::set_repl, "Get/set current repl") + .property("cull", &SEIRdet011::get_cull, &SEIRdet011::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet011::get_vacc, &SEIRdet011::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet011::get_time, "Get current time") + .property("trans_external", &SEIRdet011::get_trans_external, &SEIRdet011::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet011::get_trans_type, &SEIRdet011::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet1NN = SEIRmodel; + class_("SEIRdet1NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet1NN::show, "The show/print method") + .method("update", &SEIRdet1NN::update, "The update method") + .method("run", &SEIRdet1NN::run, "The run method") + .method("save", &SEIRdet1NN::save, "The save method") + .method("reset", &SEIRdet1NN::reset, "The reset method") + + .property("state", &SEIRdet1NN::get_state, "Get current state") + .property("S", &SEIRdet1NN::get_S, &SEIRdet1NN::set_S, "Get/set current S") + .property("E", &SEIRdet1NN::get_E, &SEIRdet1NN::set_E, "Get/set current E") + .property("I", &SEIRdet1NN::get_I, &SEIRdet1NN::set_I, "Get/set current I") + .property("R", &SEIRdet1NN::get_R, &SEIRdet1NN::set_R, "Get/set current R") + .property("N", &SEIRdet1NN::get_N, "Get current N") + .property("beta", &SEIRdet1NN::get_beta, &SEIRdet1NN::set_beta, "Get/set current beta") + .property("omega", &SEIRdet1NN::get_omega, &SEIRdet1NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet1NN::get_gamma, &SEIRdet1NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet1NN::get_delta, &SEIRdet1NN::set_delta, "Get/set current delta") + .property("repl", &SEIRdet1NN::get_repl, &SEIRdet1NN::set_repl, "Get/set current repl") + .property("cull", &SEIRdet1NN::get_cull, &SEIRdet1NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet1NN::get_vacc, &SEIRdet1NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet1NN::get_time, "Get current time") + .property("trans_external", &SEIRdet1NN::get_trans_external, &SEIRdet1NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet1NN::get_trans_type, &SEIRdet1NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet1N0 = SEIRmodel; + class_("SEIRdet1N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet1N0::show, "The show/print method") + .method("update", &SEIRdet1N0::update, "The update method") + .method("run", &SEIRdet1N0::run, "The run method") + .method("save", &SEIRdet1N0::save, "The save method") + .method("reset", &SEIRdet1N0::reset, "The reset method") + + .property("state", &SEIRdet1N0::get_state, "Get current state") + .property("S", &SEIRdet1N0::get_S, &SEIRdet1N0::set_S, "Get/set current S") + .property("E", &SEIRdet1N0::get_E, &SEIRdet1N0::set_E, "Get/set current E") + .property("I", &SEIRdet1N0::get_I, &SEIRdet1N0::set_I, "Get/set current I") + .property("R", &SEIRdet1N0::get_R, &SEIRdet1N0::set_R, "Get/set current R") + .property("N", &SEIRdet1N0::get_N, "Get current N") + .property("beta", &SEIRdet1N0::get_beta, &SEIRdet1N0::set_beta, "Get/set current beta") + .property("omega", &SEIRdet1N0::get_omega, &SEIRdet1N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet1N0::get_gamma, &SEIRdet1N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet1N0::get_delta, &SEIRdet1N0::set_delta, "Get/set current delta") + .property("repl", &SEIRdet1N0::get_repl, &SEIRdet1N0::set_repl, "Get/set current repl") + .property("cull", &SEIRdet1N0::get_cull, &SEIRdet1N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet1N0::get_vacc, &SEIRdet1N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet1N0::get_time, "Get current time") + .property("trans_external", &SEIRdet1N0::get_trans_external, &SEIRdet1N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet1N0::get_trans_type, &SEIRdet1N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet1N1 = SEIRmodel; + class_("SEIRdet1N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet1N1::show, "The show/print method") + .method("update", &SEIRdet1N1::update, "The update method") + .method("run", &SEIRdet1N1::run, "The run method") + .method("save", &SEIRdet1N1::save, "The save method") + .method("reset", &SEIRdet1N1::reset, "The reset method") + + .property("state", &SEIRdet1N1::get_state, "Get current state") + .property("S", &SEIRdet1N1::get_S, &SEIRdet1N1::set_S, "Get/set current S") + .property("E", &SEIRdet1N1::get_E, &SEIRdet1N1::set_E, "Get/set current E") + .property("I", &SEIRdet1N1::get_I, &SEIRdet1N1::set_I, "Get/set current I") + .property("R", &SEIRdet1N1::get_R, &SEIRdet1N1::set_R, "Get/set current R") + .property("N", &SEIRdet1N1::get_N, "Get current N") + .property("beta", &SEIRdet1N1::get_beta, &SEIRdet1N1::set_beta, "Get/set current beta") + .property("omega", &SEIRdet1N1::get_omega, &SEIRdet1N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet1N1::get_gamma, &SEIRdet1N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet1N1::get_delta, &SEIRdet1N1::set_delta, "Get/set current delta") + .property("repl", &SEIRdet1N1::get_repl, &SEIRdet1N1::set_repl, "Get/set current repl") + .property("cull", &SEIRdet1N1::get_cull, &SEIRdet1N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet1N1::get_vacc, &SEIRdet1N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet1N1::get_time, "Get current time") + .property("trans_external", &SEIRdet1N1::get_trans_external, &SEIRdet1N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet1N1::get_trans_type, &SEIRdet1N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet11N = SEIRmodel; + class_("SEIRdet11N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet11N::show, "The show/print method") + .method("update", &SEIRdet11N::update, "The update method") + .method("run", &SEIRdet11N::run, "The run method") + .method("save", &SEIRdet11N::save, "The save method") + .method("reset", &SEIRdet11N::reset, "The reset method") + + .property("state", &SEIRdet11N::get_state, "Get current state") + .property("S", &SEIRdet11N::get_S, &SEIRdet11N::set_S, "Get/set current S") + .property("E", &SEIRdet11N::get_E, &SEIRdet11N::set_E, "Get/set current E") + .property("I", &SEIRdet11N::get_I, &SEIRdet11N::set_I, "Get/set current I") + .property("R", &SEIRdet11N::get_R, &SEIRdet11N::set_R, "Get/set current R") + .property("N", &SEIRdet11N::get_N, "Get current N") + .property("beta", &SEIRdet11N::get_beta, &SEIRdet11N::set_beta, "Get/set current beta") + .property("omega", &SEIRdet11N::get_omega, &SEIRdet11N::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet11N::get_gamma, &SEIRdet11N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet11N::get_delta, &SEIRdet11N::set_delta, "Get/set current delta") + .property("repl", &SEIRdet11N::get_repl, &SEIRdet11N::set_repl, "Get/set current repl") + .property("cull", &SEIRdet11N::get_cull, &SEIRdet11N::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet11N::get_vacc, &SEIRdet11N::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet11N::get_time, "Get current time") + .property("trans_external", &SEIRdet11N::get_trans_external, &SEIRdet11N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet11N::get_trans_type, &SEIRdet11N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet110 = SEIRmodel; + class_("SEIRdet110") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet110::show, "The show/print method") + .method("update", &SEIRdet110::update, "The update method") + .method("run", &SEIRdet110::run, "The run method") + .method("save", &SEIRdet110::save, "The save method") + .method("reset", &SEIRdet110::reset, "The reset method") + + .property("state", &SEIRdet110::get_state, "Get current state") + .property("S", &SEIRdet110::get_S, &SEIRdet110::set_S, "Get/set current S") + .property("E", &SEIRdet110::get_E, &SEIRdet110::set_E, "Get/set current E") + .property("I", &SEIRdet110::get_I, &SEIRdet110::set_I, "Get/set current I") + .property("R", &SEIRdet110::get_R, &SEIRdet110::set_R, "Get/set current R") + .property("N", &SEIRdet110::get_N, "Get current N") + .property("beta", &SEIRdet110::get_beta, &SEIRdet110::set_beta, "Get/set current beta") + .property("omega", &SEIRdet110::get_omega, &SEIRdet110::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet110::get_gamma, &SEIRdet110::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet110::get_delta, &SEIRdet110::set_delta, "Get/set current delta") + .property("repl", &SEIRdet110::get_repl, &SEIRdet110::set_repl, "Get/set current repl") + .property("cull", &SEIRdet110::get_cull, &SEIRdet110::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet110::get_vacc, &SEIRdet110::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet110::get_time, "Get current time") + .property("trans_external", &SEIRdet110::get_trans_external, &SEIRdet110::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet110::get_trans_type, &SEIRdet110::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet111 = SEIRmodel; + class_("SEIRdet111") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet111::show, "The show/print method") + .method("update", &SEIRdet111::update, "The update method") + .method("run", &SEIRdet111::run, "The run method") + .method("save", &SEIRdet111::save, "The save method") + .method("reset", &SEIRdet111::reset, "The reset method") + + .property("state", &SEIRdet111::get_state, "Get current state") + .property("S", &SEIRdet111::get_S, &SEIRdet111::set_S, "Get/set current S") + .property("E", &SEIRdet111::get_E, &SEIRdet111::set_E, "Get/set current E") + .property("I", &SEIRdet111::get_I, &SEIRdet111::set_I, "Get/set current I") + .property("R", &SEIRdet111::get_R, &SEIRdet111::set_R, "Get/set current R") + .property("N", &SEIRdet111::get_N, "Get current N") + .property("beta", &SEIRdet111::get_beta, &SEIRdet111::set_beta, "Get/set current beta") + .property("omega", &SEIRdet111::get_omega, &SEIRdet111::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet111::get_gamma, &SEIRdet111::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet111::get_delta, &SEIRdet111::set_delta, "Get/set current delta") + .property("repl", &SEIRdet111::get_repl, &SEIRdet111::set_repl, "Get/set current repl") + .property("cull", &SEIRdet111::get_cull, &SEIRdet111::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet111::get_vacc, &SEIRdet111::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet111::get_time, "Get current time") + .property("trans_external", &SEIRdet111::get_trans_external, &SEIRdet111::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet111::get_trans_type, &SEIRdet111::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet3NN = SEIRmodel; + class_("SEIRdet3NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet3NN::show, "The show/print method") + .method("update", &SEIRdet3NN::update, "The update method") + .method("run", &SEIRdet3NN::run, "The run method") + .method("save", &SEIRdet3NN::save, "The save method") + .method("reset", &SEIRdet3NN::reset, "The reset method") + + .property("state", &SEIRdet3NN::get_state, "Get current state") + .property("S", &SEIRdet3NN::get_S, &SEIRdet3NN::set_S, "Get/set current S") + .property("E", &SEIRdet3NN::get_E, &SEIRdet3NN::set_E, "Get/set current E") + .property("I", &SEIRdet3NN::get_I, &SEIRdet3NN::set_I, "Get/set current I") + .property("R", &SEIRdet3NN::get_R, &SEIRdet3NN::set_R, "Get/set current R") + .property("N", &SEIRdet3NN::get_N, "Get current N") + .property("beta", &SEIRdet3NN::get_beta, &SEIRdet3NN::set_beta, "Get/set current beta") + .property("omega", &SEIRdet3NN::get_omega, &SEIRdet3NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet3NN::get_gamma, &SEIRdet3NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet3NN::get_delta, &SEIRdet3NN::set_delta, "Get/set current delta") + .property("repl", &SEIRdet3NN::get_repl, &SEIRdet3NN::set_repl, "Get/set current repl") + .property("cull", &SEIRdet3NN::get_cull, &SEIRdet3NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet3NN::get_vacc, &SEIRdet3NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet3NN::get_time, "Get current time") + .property("trans_external", &SEIRdet3NN::get_trans_external, &SEIRdet3NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet3NN::get_trans_type, &SEIRdet3NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet3N0 = SEIRmodel; + class_("SEIRdet3N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet3N0::show, "The show/print method") + .method("update", &SEIRdet3N0::update, "The update method") + .method("run", &SEIRdet3N0::run, "The run method") + .method("save", &SEIRdet3N0::save, "The save method") + .method("reset", &SEIRdet3N0::reset, "The reset method") + + .property("state", &SEIRdet3N0::get_state, "Get current state") + .property("S", &SEIRdet3N0::get_S, &SEIRdet3N0::set_S, "Get/set current S") + .property("E", &SEIRdet3N0::get_E, &SEIRdet3N0::set_E, "Get/set current E") + .property("I", &SEIRdet3N0::get_I, &SEIRdet3N0::set_I, "Get/set current I") + .property("R", &SEIRdet3N0::get_R, &SEIRdet3N0::set_R, "Get/set current R") + .property("N", &SEIRdet3N0::get_N, "Get current N") + .property("beta", &SEIRdet3N0::get_beta, &SEIRdet3N0::set_beta, "Get/set current beta") + .property("omega", &SEIRdet3N0::get_omega, &SEIRdet3N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet3N0::get_gamma, &SEIRdet3N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet3N0::get_delta, &SEIRdet3N0::set_delta, "Get/set current delta") + .property("repl", &SEIRdet3N0::get_repl, &SEIRdet3N0::set_repl, "Get/set current repl") + .property("cull", &SEIRdet3N0::get_cull, &SEIRdet3N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet3N0::get_vacc, &SEIRdet3N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet3N0::get_time, "Get current time") + .property("trans_external", &SEIRdet3N0::get_trans_external, &SEIRdet3N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet3N0::get_trans_type, &SEIRdet3N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet3N1 = SEIRmodel; + class_("SEIRdet3N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet3N1::show, "The show/print method") + .method("update", &SEIRdet3N1::update, "The update method") + .method("run", &SEIRdet3N1::run, "The run method") + .method("save", &SEIRdet3N1::save, "The save method") + .method("reset", &SEIRdet3N1::reset, "The reset method") + + .property("state", &SEIRdet3N1::get_state, "Get current state") + .property("S", &SEIRdet3N1::get_S, &SEIRdet3N1::set_S, "Get/set current S") + .property("E", &SEIRdet3N1::get_E, &SEIRdet3N1::set_E, "Get/set current E") + .property("I", &SEIRdet3N1::get_I, &SEIRdet3N1::set_I, "Get/set current I") + .property("R", &SEIRdet3N1::get_R, &SEIRdet3N1::set_R, "Get/set current R") + .property("N", &SEIRdet3N1::get_N, "Get current N") + .property("beta", &SEIRdet3N1::get_beta, &SEIRdet3N1::set_beta, "Get/set current beta") + .property("omega", &SEIRdet3N1::get_omega, &SEIRdet3N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet3N1::get_gamma, &SEIRdet3N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet3N1::get_delta, &SEIRdet3N1::set_delta, "Get/set current delta") + .property("repl", &SEIRdet3N1::get_repl, &SEIRdet3N1::set_repl, "Get/set current repl") + .property("cull", &SEIRdet3N1::get_cull, &SEIRdet3N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet3N1::get_vacc, &SEIRdet3N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet3N1::get_time, "Get current time") + .property("trans_external", &SEIRdet3N1::get_trans_external, &SEIRdet3N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet3N1::get_trans_type, &SEIRdet3N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet31N = SEIRmodel; + class_("SEIRdet31N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet31N::show, "The show/print method") + .method("update", &SEIRdet31N::update, "The update method") + .method("run", &SEIRdet31N::run, "The run method") + .method("save", &SEIRdet31N::save, "The save method") + .method("reset", &SEIRdet31N::reset, "The reset method") + + .property("state", &SEIRdet31N::get_state, "Get current state") + .property("S", &SEIRdet31N::get_S, &SEIRdet31N::set_S, "Get/set current S") + .property("E", &SEIRdet31N::get_E, &SEIRdet31N::set_E, "Get/set current E") + .property("I", &SEIRdet31N::get_I, &SEIRdet31N::set_I, "Get/set current I") + .property("R", &SEIRdet31N::get_R, &SEIRdet31N::set_R, "Get/set current R") + .property("N", &SEIRdet31N::get_N, "Get current N") + .property("beta", &SEIRdet31N::get_beta, &SEIRdet31N::set_beta, "Get/set current beta") + .property("omega", &SEIRdet31N::get_omega, &SEIRdet31N::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet31N::get_gamma, &SEIRdet31N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet31N::get_delta, &SEIRdet31N::set_delta, "Get/set current delta") + .property("repl", &SEIRdet31N::get_repl, &SEIRdet31N::set_repl, "Get/set current repl") + .property("cull", &SEIRdet31N::get_cull, &SEIRdet31N::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet31N::get_vacc, &SEIRdet31N::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet31N::get_time, "Get current time") + .property("trans_external", &SEIRdet31N::get_trans_external, &SEIRdet31N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet31N::get_trans_type, &SEIRdet31N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet310 = SEIRmodel; + class_("SEIRdet310") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet310::show, "The show/print method") + .method("update", &SEIRdet310::update, "The update method") + .method("run", &SEIRdet310::run, "The run method") + .method("save", &SEIRdet310::save, "The save method") + .method("reset", &SEIRdet310::reset, "The reset method") + + .property("state", &SEIRdet310::get_state, "Get current state") + .property("S", &SEIRdet310::get_S, &SEIRdet310::set_S, "Get/set current S") + .property("E", &SEIRdet310::get_E, &SEIRdet310::set_E, "Get/set current E") + .property("I", &SEIRdet310::get_I, &SEIRdet310::set_I, "Get/set current I") + .property("R", &SEIRdet310::get_R, &SEIRdet310::set_R, "Get/set current R") + .property("N", &SEIRdet310::get_N, "Get current N") + .property("beta", &SEIRdet310::get_beta, &SEIRdet310::set_beta, "Get/set current beta") + .property("omega", &SEIRdet310::get_omega, &SEIRdet310::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet310::get_gamma, &SEIRdet310::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet310::get_delta, &SEIRdet310::set_delta, "Get/set current delta") + .property("repl", &SEIRdet310::get_repl, &SEIRdet310::set_repl, "Get/set current repl") + .property("cull", &SEIRdet310::get_cull, &SEIRdet310::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet310::get_vacc, &SEIRdet310::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet310::get_time, "Get current time") + .property("trans_external", &SEIRdet310::get_trans_external, &SEIRdet310::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet310::get_trans_type, &SEIRdet310::set_trans_type, "Get/set current trans_type") + ; + + using SEIRdet311 = SEIRmodel; + class_("SEIRdet311") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRdet311::show, "The show/print method") + .method("update", &SEIRdet311::update, "The update method") + .method("run", &SEIRdet311::run, "The run method") + .method("save", &SEIRdet311::save, "The save method") + .method("reset", &SEIRdet311::reset, "The reset method") + + .property("state", &SEIRdet311::get_state, "Get current state") + .property("S", &SEIRdet311::get_S, &SEIRdet311::set_S, "Get/set current S") + .property("E", &SEIRdet311::get_E, &SEIRdet311::set_E, "Get/set current E") + .property("I", &SEIRdet311::get_I, &SEIRdet311::set_I, "Get/set current I") + .property("R", &SEIRdet311::get_R, &SEIRdet311::set_R, "Get/set current R") + .property("N", &SEIRdet311::get_N, "Get current N") + .property("beta", &SEIRdet311::get_beta, &SEIRdet311::set_beta, "Get/set current beta") + .property("omega", &SEIRdet311::get_omega, &SEIRdet311::set_omega, "Get/set current omega") + .property("gamma", &SEIRdet311::get_gamma, &SEIRdet311::set_gamma, "Get/set current gamma") + .property("delta", &SEIRdet311::get_delta, &SEIRdet311::set_delta, "Get/set current delta") + .property("repl", &SEIRdet311::get_repl, &SEIRdet311::set_repl, "Get/set current repl") + .property("cull", &SEIRdet311::get_cull, &SEIRdet311::set_cull, "Get/set current cull") + .property("vacc", &SEIRdet311::get_vacc, &SEIRdet311::set_vacc, "Get/set current vacc") + .property("time", &SEIRdet311::get_time, "Get current time") + .property("trans_external", &SEIRdet311::get_trans_external, &SEIRdet311::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRdet311::get_trans_type, &SEIRdet311::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocNNN = SEIRmodel; + class_("SEIRstocNNN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocNNN::show, "The show/print method") + .method("update", &SEIRstocNNN::update, "The update method") + .method("run", &SEIRstocNNN::run, "The run method") + .method("save", &SEIRstocNNN::save, "The save method") + .method("reset", &SEIRstocNNN::reset, "The reset method") + + .property("state", &SEIRstocNNN::get_state, "Get current state") + .property("S", &SEIRstocNNN::get_S, &SEIRstocNNN::set_S, "Get/set current S") + .property("E", &SEIRstocNNN::get_E, &SEIRstocNNN::set_E, "Get/set current E") + .property("I", &SEIRstocNNN::get_I, &SEIRstocNNN::set_I, "Get/set current I") + .property("R", &SEIRstocNNN::get_R, &SEIRstocNNN::set_R, "Get/set current R") + .property("N", &SEIRstocNNN::get_N, "Get current N") + .property("beta", &SEIRstocNNN::get_beta, &SEIRstocNNN::set_beta, "Get/set current beta") + .property("omega", &SEIRstocNNN::get_omega, &SEIRstocNNN::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocNNN::get_gamma, &SEIRstocNNN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocNNN::get_delta, &SEIRstocNNN::set_delta, "Get/set current delta") + .property("repl", &SEIRstocNNN::get_repl, &SEIRstocNNN::set_repl, "Get/set current repl") + .property("cull", &SEIRstocNNN::get_cull, &SEIRstocNNN::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocNNN::get_vacc, &SEIRstocNNN::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocNNN::get_time, "Get current time") + .property("trans_external", &SEIRstocNNN::get_trans_external, &SEIRstocNNN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocNNN::get_trans_type, &SEIRstocNNN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocNN0 = SEIRmodel; + class_("SEIRstocNN0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocNN0::show, "The show/print method") + .method("update", &SEIRstocNN0::update, "The update method") + .method("run", &SEIRstocNN0::run, "The run method") + .method("save", &SEIRstocNN0::save, "The save method") + .method("reset", &SEIRstocNN0::reset, "The reset method") + + .property("state", &SEIRstocNN0::get_state, "Get current state") + .property("S", &SEIRstocNN0::get_S, &SEIRstocNN0::set_S, "Get/set current S") + .property("E", &SEIRstocNN0::get_E, &SEIRstocNN0::set_E, "Get/set current E") + .property("I", &SEIRstocNN0::get_I, &SEIRstocNN0::set_I, "Get/set current I") + .property("R", &SEIRstocNN0::get_R, &SEIRstocNN0::set_R, "Get/set current R") + .property("N", &SEIRstocNN0::get_N, "Get current N") + .property("beta", &SEIRstocNN0::get_beta, &SEIRstocNN0::set_beta, "Get/set current beta") + .property("omega", &SEIRstocNN0::get_omega, &SEIRstocNN0::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocNN0::get_gamma, &SEIRstocNN0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocNN0::get_delta, &SEIRstocNN0::set_delta, "Get/set current delta") + .property("repl", &SEIRstocNN0::get_repl, &SEIRstocNN0::set_repl, "Get/set current repl") + .property("cull", &SEIRstocNN0::get_cull, &SEIRstocNN0::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocNN0::get_vacc, &SEIRstocNN0::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocNN0::get_time, "Get current time") + .property("trans_external", &SEIRstocNN0::get_trans_external, &SEIRstocNN0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocNN0::get_trans_type, &SEIRstocNN0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocNN1 = SEIRmodel; + class_("SEIRstocNN1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocNN1::show, "The show/print method") + .method("update", &SEIRstocNN1::update, "The update method") + .method("run", &SEIRstocNN1::run, "The run method") + .method("save", &SEIRstocNN1::save, "The save method") + .method("reset", &SEIRstocNN1::reset, "The reset method") + + .property("state", &SEIRstocNN1::get_state, "Get current state") + .property("S", &SEIRstocNN1::get_S, &SEIRstocNN1::set_S, "Get/set current S") + .property("E", &SEIRstocNN1::get_E, &SEIRstocNN1::set_E, "Get/set current E") + .property("I", &SEIRstocNN1::get_I, &SEIRstocNN1::set_I, "Get/set current I") + .property("R", &SEIRstocNN1::get_R, &SEIRstocNN1::set_R, "Get/set current R") + .property("N", &SEIRstocNN1::get_N, "Get current N") + .property("beta", &SEIRstocNN1::get_beta, &SEIRstocNN1::set_beta, "Get/set current beta") + .property("omega", &SEIRstocNN1::get_omega, &SEIRstocNN1::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocNN1::get_gamma, &SEIRstocNN1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocNN1::get_delta, &SEIRstocNN1::set_delta, "Get/set current delta") + .property("repl", &SEIRstocNN1::get_repl, &SEIRstocNN1::set_repl, "Get/set current repl") + .property("cull", &SEIRstocNN1::get_cull, &SEIRstocNN1::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocNN1::get_vacc, &SEIRstocNN1::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocNN1::get_time, "Get current time") + .property("trans_external", &SEIRstocNN1::get_trans_external, &SEIRstocNN1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocNN1::get_trans_type, &SEIRstocNN1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocN1N = SEIRmodel; + class_("SEIRstocN1N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocN1N::show, "The show/print method") + .method("update", &SEIRstocN1N::update, "The update method") + .method("run", &SEIRstocN1N::run, "The run method") + .method("save", &SEIRstocN1N::save, "The save method") + .method("reset", &SEIRstocN1N::reset, "The reset method") + + .property("state", &SEIRstocN1N::get_state, "Get current state") + .property("S", &SEIRstocN1N::get_S, &SEIRstocN1N::set_S, "Get/set current S") + .property("E", &SEIRstocN1N::get_E, &SEIRstocN1N::set_E, "Get/set current E") + .property("I", &SEIRstocN1N::get_I, &SEIRstocN1N::set_I, "Get/set current I") + .property("R", &SEIRstocN1N::get_R, &SEIRstocN1N::set_R, "Get/set current R") + .property("N", &SEIRstocN1N::get_N, "Get current N") + .property("beta", &SEIRstocN1N::get_beta, &SEIRstocN1N::set_beta, "Get/set current beta") + .property("omega", &SEIRstocN1N::get_omega, &SEIRstocN1N::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocN1N::get_gamma, &SEIRstocN1N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocN1N::get_delta, &SEIRstocN1N::set_delta, "Get/set current delta") + .property("repl", &SEIRstocN1N::get_repl, &SEIRstocN1N::set_repl, "Get/set current repl") + .property("cull", &SEIRstocN1N::get_cull, &SEIRstocN1N::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocN1N::get_vacc, &SEIRstocN1N::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocN1N::get_time, "Get current time") + .property("trans_external", &SEIRstocN1N::get_trans_external, &SEIRstocN1N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocN1N::get_trans_type, &SEIRstocN1N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocN10 = SEIRmodel; + class_("SEIRstocN10") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocN10::show, "The show/print method") + .method("update", &SEIRstocN10::update, "The update method") + .method("run", &SEIRstocN10::run, "The run method") + .method("save", &SEIRstocN10::save, "The save method") + .method("reset", &SEIRstocN10::reset, "The reset method") + + .property("state", &SEIRstocN10::get_state, "Get current state") + .property("S", &SEIRstocN10::get_S, &SEIRstocN10::set_S, "Get/set current S") + .property("E", &SEIRstocN10::get_E, &SEIRstocN10::set_E, "Get/set current E") + .property("I", &SEIRstocN10::get_I, &SEIRstocN10::set_I, "Get/set current I") + .property("R", &SEIRstocN10::get_R, &SEIRstocN10::set_R, "Get/set current R") + .property("N", &SEIRstocN10::get_N, "Get current N") + .property("beta", &SEIRstocN10::get_beta, &SEIRstocN10::set_beta, "Get/set current beta") + .property("omega", &SEIRstocN10::get_omega, &SEIRstocN10::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocN10::get_gamma, &SEIRstocN10::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocN10::get_delta, &SEIRstocN10::set_delta, "Get/set current delta") + .property("repl", &SEIRstocN10::get_repl, &SEIRstocN10::set_repl, "Get/set current repl") + .property("cull", &SEIRstocN10::get_cull, &SEIRstocN10::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocN10::get_vacc, &SEIRstocN10::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocN10::get_time, "Get current time") + .property("trans_external", &SEIRstocN10::get_trans_external, &SEIRstocN10::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocN10::get_trans_type, &SEIRstocN10::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstocN11 = SEIRmodel; + class_("SEIRstocN11") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstocN11::show, "The show/print method") + .method("update", &SEIRstocN11::update, "The update method") + .method("run", &SEIRstocN11::run, "The run method") + .method("save", &SEIRstocN11::save, "The save method") + .method("reset", &SEIRstocN11::reset, "The reset method") + + .property("state", &SEIRstocN11::get_state, "Get current state") + .property("S", &SEIRstocN11::get_S, &SEIRstocN11::set_S, "Get/set current S") + .property("E", &SEIRstocN11::get_E, &SEIRstocN11::set_E, "Get/set current E") + .property("I", &SEIRstocN11::get_I, &SEIRstocN11::set_I, "Get/set current I") + .property("R", &SEIRstocN11::get_R, &SEIRstocN11::set_R, "Get/set current R") + .property("N", &SEIRstocN11::get_N, "Get current N") + .property("beta", &SEIRstocN11::get_beta, &SEIRstocN11::set_beta, "Get/set current beta") + .property("omega", &SEIRstocN11::get_omega, &SEIRstocN11::set_omega, "Get/set current omega") + .property("gamma", &SEIRstocN11::get_gamma, &SEIRstocN11::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstocN11::get_delta, &SEIRstocN11::set_delta, "Get/set current delta") + .property("repl", &SEIRstocN11::get_repl, &SEIRstocN11::set_repl, "Get/set current repl") + .property("cull", &SEIRstocN11::get_cull, &SEIRstocN11::set_cull, "Get/set current cull") + .property("vacc", &SEIRstocN11::get_vacc, &SEIRstocN11::set_vacc, "Get/set current vacc") + .property("time", &SEIRstocN11::get_time, "Get current time") + .property("trans_external", &SEIRstocN11::get_trans_external, &SEIRstocN11::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstocN11::get_trans_type, &SEIRstocN11::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc0NN = SEIRmodel; + class_("SEIRstoc0NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc0NN::show, "The show/print method") + .method("update", &SEIRstoc0NN::update, "The update method") + .method("run", &SEIRstoc0NN::run, "The run method") + .method("save", &SEIRstoc0NN::save, "The save method") + .method("reset", &SEIRstoc0NN::reset, "The reset method") + + .property("state", &SEIRstoc0NN::get_state, "Get current state") + .property("S", &SEIRstoc0NN::get_S, &SEIRstoc0NN::set_S, "Get/set current S") + .property("E", &SEIRstoc0NN::get_E, &SEIRstoc0NN::set_E, "Get/set current E") + .property("I", &SEIRstoc0NN::get_I, &SEIRstoc0NN::set_I, "Get/set current I") + .property("R", &SEIRstoc0NN::get_R, &SEIRstoc0NN::set_R, "Get/set current R") + .property("N", &SEIRstoc0NN::get_N, "Get current N") + .property("beta", &SEIRstoc0NN::get_beta, &SEIRstoc0NN::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc0NN::get_omega, &SEIRstoc0NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc0NN::get_gamma, &SEIRstoc0NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc0NN::get_delta, &SEIRstoc0NN::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc0NN::get_repl, &SEIRstoc0NN::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc0NN::get_cull, &SEIRstoc0NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc0NN::get_vacc, &SEIRstoc0NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc0NN::get_time, "Get current time") + .property("trans_external", &SEIRstoc0NN::get_trans_external, &SEIRstoc0NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc0NN::get_trans_type, &SEIRstoc0NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc0N0 = SEIRmodel; + class_("SEIRstoc0N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc0N0::show, "The show/print method") + .method("update", &SEIRstoc0N0::update, "The update method") + .method("run", &SEIRstoc0N0::run, "The run method") + .method("save", &SEIRstoc0N0::save, "The save method") + .method("reset", &SEIRstoc0N0::reset, "The reset method") + + .property("state", &SEIRstoc0N0::get_state, "Get current state") + .property("S", &SEIRstoc0N0::get_S, &SEIRstoc0N0::set_S, "Get/set current S") + .property("E", &SEIRstoc0N0::get_E, &SEIRstoc0N0::set_E, "Get/set current E") + .property("I", &SEIRstoc0N0::get_I, &SEIRstoc0N0::set_I, "Get/set current I") + .property("R", &SEIRstoc0N0::get_R, &SEIRstoc0N0::set_R, "Get/set current R") + .property("N", &SEIRstoc0N0::get_N, "Get current N") + .property("beta", &SEIRstoc0N0::get_beta, &SEIRstoc0N0::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc0N0::get_omega, &SEIRstoc0N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc0N0::get_gamma, &SEIRstoc0N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc0N0::get_delta, &SEIRstoc0N0::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc0N0::get_repl, &SEIRstoc0N0::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc0N0::get_cull, &SEIRstoc0N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc0N0::get_vacc, &SEIRstoc0N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc0N0::get_time, "Get current time") + .property("trans_external", &SEIRstoc0N0::get_trans_external, &SEIRstoc0N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc0N0::get_trans_type, &SEIRstoc0N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc0N1 = SEIRmodel; + class_("SEIRstoc0N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc0N1::show, "The show/print method") + .method("update", &SEIRstoc0N1::update, "The update method") + .method("run", &SEIRstoc0N1::run, "The run method") + .method("save", &SEIRstoc0N1::save, "The save method") + .method("reset", &SEIRstoc0N1::reset, "The reset method") + + .property("state", &SEIRstoc0N1::get_state, "Get current state") + .property("S", &SEIRstoc0N1::get_S, &SEIRstoc0N1::set_S, "Get/set current S") + .property("E", &SEIRstoc0N1::get_E, &SEIRstoc0N1::set_E, "Get/set current E") + .property("I", &SEIRstoc0N1::get_I, &SEIRstoc0N1::set_I, "Get/set current I") + .property("R", &SEIRstoc0N1::get_R, &SEIRstoc0N1::set_R, "Get/set current R") + .property("N", &SEIRstoc0N1::get_N, "Get current N") + .property("beta", &SEIRstoc0N1::get_beta, &SEIRstoc0N1::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc0N1::get_omega, &SEIRstoc0N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc0N1::get_gamma, &SEIRstoc0N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc0N1::get_delta, &SEIRstoc0N1::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc0N1::get_repl, &SEIRstoc0N1::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc0N1::get_cull, &SEIRstoc0N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc0N1::get_vacc, &SEIRstoc0N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc0N1::get_time, "Get current time") + .property("trans_external", &SEIRstoc0N1::get_trans_external, &SEIRstoc0N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc0N1::get_trans_type, &SEIRstoc0N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc01N = SEIRmodel; + class_("SEIRstoc01N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc01N::show, "The show/print method") + .method("update", &SEIRstoc01N::update, "The update method") + .method("run", &SEIRstoc01N::run, "The run method") + .method("save", &SEIRstoc01N::save, "The save method") + .method("reset", &SEIRstoc01N::reset, "The reset method") + + .property("state", &SEIRstoc01N::get_state, "Get current state") + .property("S", &SEIRstoc01N::get_S, &SEIRstoc01N::set_S, "Get/set current S") + .property("E", &SEIRstoc01N::get_E, &SEIRstoc01N::set_E, "Get/set current E") + .property("I", &SEIRstoc01N::get_I, &SEIRstoc01N::set_I, "Get/set current I") + .property("R", &SEIRstoc01N::get_R, &SEIRstoc01N::set_R, "Get/set current R") + .property("N", &SEIRstoc01N::get_N, "Get current N") + .property("beta", &SEIRstoc01N::get_beta, &SEIRstoc01N::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc01N::get_omega, &SEIRstoc01N::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc01N::get_gamma, &SEIRstoc01N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc01N::get_delta, &SEIRstoc01N::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc01N::get_repl, &SEIRstoc01N::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc01N::get_cull, &SEIRstoc01N::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc01N::get_vacc, &SEIRstoc01N::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc01N::get_time, "Get current time") + .property("trans_external", &SEIRstoc01N::get_trans_external, &SEIRstoc01N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc01N::get_trans_type, &SEIRstoc01N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc010 = SEIRmodel; + class_("SEIRstoc010") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc010::show, "The show/print method") + .method("update", &SEIRstoc010::update, "The update method") + .method("run", &SEIRstoc010::run, "The run method") + .method("save", &SEIRstoc010::save, "The save method") + .method("reset", &SEIRstoc010::reset, "The reset method") + + .property("state", &SEIRstoc010::get_state, "Get current state") + .property("S", &SEIRstoc010::get_S, &SEIRstoc010::set_S, "Get/set current S") + .property("E", &SEIRstoc010::get_E, &SEIRstoc010::set_E, "Get/set current E") + .property("I", &SEIRstoc010::get_I, &SEIRstoc010::set_I, "Get/set current I") + .property("R", &SEIRstoc010::get_R, &SEIRstoc010::set_R, "Get/set current R") + .property("N", &SEIRstoc010::get_N, "Get current N") + .property("beta", &SEIRstoc010::get_beta, &SEIRstoc010::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc010::get_omega, &SEIRstoc010::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc010::get_gamma, &SEIRstoc010::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc010::get_delta, &SEIRstoc010::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc010::get_repl, &SEIRstoc010::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc010::get_cull, &SEIRstoc010::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc010::get_vacc, &SEIRstoc010::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc010::get_time, "Get current time") + .property("trans_external", &SEIRstoc010::get_trans_external, &SEIRstoc010::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc010::get_trans_type, &SEIRstoc010::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc011 = SEIRmodel; + class_("SEIRstoc011") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc011::show, "The show/print method") + .method("update", &SEIRstoc011::update, "The update method") + .method("run", &SEIRstoc011::run, "The run method") + .method("save", &SEIRstoc011::save, "The save method") + .method("reset", &SEIRstoc011::reset, "The reset method") + + .property("state", &SEIRstoc011::get_state, "Get current state") + .property("S", &SEIRstoc011::get_S, &SEIRstoc011::set_S, "Get/set current S") + .property("E", &SEIRstoc011::get_E, &SEIRstoc011::set_E, "Get/set current E") + .property("I", &SEIRstoc011::get_I, &SEIRstoc011::set_I, "Get/set current I") + .property("R", &SEIRstoc011::get_R, &SEIRstoc011::set_R, "Get/set current R") + .property("N", &SEIRstoc011::get_N, "Get current N") + .property("beta", &SEIRstoc011::get_beta, &SEIRstoc011::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc011::get_omega, &SEIRstoc011::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc011::get_gamma, &SEIRstoc011::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc011::get_delta, &SEIRstoc011::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc011::get_repl, &SEIRstoc011::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc011::get_cull, &SEIRstoc011::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc011::get_vacc, &SEIRstoc011::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc011::get_time, "Get current time") + .property("trans_external", &SEIRstoc011::get_trans_external, &SEIRstoc011::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc011::get_trans_type, &SEIRstoc011::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc1NN = SEIRmodel; + class_("SEIRstoc1NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc1NN::show, "The show/print method") + .method("update", &SEIRstoc1NN::update, "The update method") + .method("run", &SEIRstoc1NN::run, "The run method") + .method("save", &SEIRstoc1NN::save, "The save method") + .method("reset", &SEIRstoc1NN::reset, "The reset method") + + .property("state", &SEIRstoc1NN::get_state, "Get current state") + .property("S", &SEIRstoc1NN::get_S, &SEIRstoc1NN::set_S, "Get/set current S") + .property("E", &SEIRstoc1NN::get_E, &SEIRstoc1NN::set_E, "Get/set current E") + .property("I", &SEIRstoc1NN::get_I, &SEIRstoc1NN::set_I, "Get/set current I") + .property("R", &SEIRstoc1NN::get_R, &SEIRstoc1NN::set_R, "Get/set current R") + .property("N", &SEIRstoc1NN::get_N, "Get current N") + .property("beta", &SEIRstoc1NN::get_beta, &SEIRstoc1NN::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc1NN::get_omega, &SEIRstoc1NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc1NN::get_gamma, &SEIRstoc1NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc1NN::get_delta, &SEIRstoc1NN::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc1NN::get_repl, &SEIRstoc1NN::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc1NN::get_cull, &SEIRstoc1NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc1NN::get_vacc, &SEIRstoc1NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc1NN::get_time, "Get current time") + .property("trans_external", &SEIRstoc1NN::get_trans_external, &SEIRstoc1NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc1NN::get_trans_type, &SEIRstoc1NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc1N0 = SEIRmodel; + class_("SEIRstoc1N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc1N0::show, "The show/print method") + .method("update", &SEIRstoc1N0::update, "The update method") + .method("run", &SEIRstoc1N0::run, "The run method") + .method("save", &SEIRstoc1N0::save, "The save method") + .method("reset", &SEIRstoc1N0::reset, "The reset method") + + .property("state", &SEIRstoc1N0::get_state, "Get current state") + .property("S", &SEIRstoc1N0::get_S, &SEIRstoc1N0::set_S, "Get/set current S") + .property("E", &SEIRstoc1N0::get_E, &SEIRstoc1N0::set_E, "Get/set current E") + .property("I", &SEIRstoc1N0::get_I, &SEIRstoc1N0::set_I, "Get/set current I") + .property("R", &SEIRstoc1N0::get_R, &SEIRstoc1N0::set_R, "Get/set current R") + .property("N", &SEIRstoc1N0::get_N, "Get current N") + .property("beta", &SEIRstoc1N0::get_beta, &SEIRstoc1N0::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc1N0::get_omega, &SEIRstoc1N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc1N0::get_gamma, &SEIRstoc1N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc1N0::get_delta, &SEIRstoc1N0::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc1N0::get_repl, &SEIRstoc1N0::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc1N0::get_cull, &SEIRstoc1N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc1N0::get_vacc, &SEIRstoc1N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc1N0::get_time, "Get current time") + .property("trans_external", &SEIRstoc1N0::get_trans_external, &SEIRstoc1N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc1N0::get_trans_type, &SEIRstoc1N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc1N1 = SEIRmodel; + class_("SEIRstoc1N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc1N1::show, "The show/print method") + .method("update", &SEIRstoc1N1::update, "The update method") + .method("run", &SEIRstoc1N1::run, "The run method") + .method("save", &SEIRstoc1N1::save, "The save method") + .method("reset", &SEIRstoc1N1::reset, "The reset method") + + .property("state", &SEIRstoc1N1::get_state, "Get current state") + .property("S", &SEIRstoc1N1::get_S, &SEIRstoc1N1::set_S, "Get/set current S") + .property("E", &SEIRstoc1N1::get_E, &SEIRstoc1N1::set_E, "Get/set current E") + .property("I", &SEIRstoc1N1::get_I, &SEIRstoc1N1::set_I, "Get/set current I") + .property("R", &SEIRstoc1N1::get_R, &SEIRstoc1N1::set_R, "Get/set current R") + .property("N", &SEIRstoc1N1::get_N, "Get current N") + .property("beta", &SEIRstoc1N1::get_beta, &SEIRstoc1N1::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc1N1::get_omega, &SEIRstoc1N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc1N1::get_gamma, &SEIRstoc1N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc1N1::get_delta, &SEIRstoc1N1::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc1N1::get_repl, &SEIRstoc1N1::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc1N1::get_cull, &SEIRstoc1N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc1N1::get_vacc, &SEIRstoc1N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc1N1::get_time, "Get current time") + .property("trans_external", &SEIRstoc1N1::get_trans_external, &SEIRstoc1N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc1N1::get_trans_type, &SEIRstoc1N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc11N = SEIRmodel; + class_("SEIRstoc11N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc11N::show, "The show/print method") + .method("update", &SEIRstoc11N::update, "The update method") + .method("run", &SEIRstoc11N::run, "The run method") + .method("save", &SEIRstoc11N::save, "The save method") + .method("reset", &SEIRstoc11N::reset, "The reset method") + + .property("state", &SEIRstoc11N::get_state, "Get current state") + .property("S", &SEIRstoc11N::get_S, &SEIRstoc11N::set_S, "Get/set current S") + .property("E", &SEIRstoc11N::get_E, &SEIRstoc11N::set_E, "Get/set current E") + .property("I", &SEIRstoc11N::get_I, &SEIRstoc11N::set_I, "Get/set current I") + .property("R", &SEIRstoc11N::get_R, &SEIRstoc11N::set_R, "Get/set current R") + .property("N", &SEIRstoc11N::get_N, "Get current N") + .property("beta", &SEIRstoc11N::get_beta, &SEIRstoc11N::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc11N::get_omega, &SEIRstoc11N::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc11N::get_gamma, &SEIRstoc11N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc11N::get_delta, &SEIRstoc11N::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc11N::get_repl, &SEIRstoc11N::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc11N::get_cull, &SEIRstoc11N::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc11N::get_vacc, &SEIRstoc11N::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc11N::get_time, "Get current time") + .property("trans_external", &SEIRstoc11N::get_trans_external, &SEIRstoc11N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc11N::get_trans_type, &SEIRstoc11N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc110 = SEIRmodel; + class_("SEIRstoc110") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc110::show, "The show/print method") + .method("update", &SEIRstoc110::update, "The update method") + .method("run", &SEIRstoc110::run, "The run method") + .method("save", &SEIRstoc110::save, "The save method") + .method("reset", &SEIRstoc110::reset, "The reset method") + + .property("state", &SEIRstoc110::get_state, "Get current state") + .property("S", &SEIRstoc110::get_S, &SEIRstoc110::set_S, "Get/set current S") + .property("E", &SEIRstoc110::get_E, &SEIRstoc110::set_E, "Get/set current E") + .property("I", &SEIRstoc110::get_I, &SEIRstoc110::set_I, "Get/set current I") + .property("R", &SEIRstoc110::get_R, &SEIRstoc110::set_R, "Get/set current R") + .property("N", &SEIRstoc110::get_N, "Get current N") + .property("beta", &SEIRstoc110::get_beta, &SEIRstoc110::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc110::get_omega, &SEIRstoc110::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc110::get_gamma, &SEIRstoc110::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc110::get_delta, &SEIRstoc110::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc110::get_repl, &SEIRstoc110::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc110::get_cull, &SEIRstoc110::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc110::get_vacc, &SEIRstoc110::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc110::get_time, "Get current time") + .property("trans_external", &SEIRstoc110::get_trans_external, &SEIRstoc110::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc110::get_trans_type, &SEIRstoc110::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc111 = SEIRmodel; + class_("SEIRstoc111") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc111::show, "The show/print method") + .method("update", &SEIRstoc111::update, "The update method") + .method("run", &SEIRstoc111::run, "The run method") + .method("save", &SEIRstoc111::save, "The save method") + .method("reset", &SEIRstoc111::reset, "The reset method") + + .property("state", &SEIRstoc111::get_state, "Get current state") + .property("S", &SEIRstoc111::get_S, &SEIRstoc111::set_S, "Get/set current S") + .property("E", &SEIRstoc111::get_E, &SEIRstoc111::set_E, "Get/set current E") + .property("I", &SEIRstoc111::get_I, &SEIRstoc111::set_I, "Get/set current I") + .property("R", &SEIRstoc111::get_R, &SEIRstoc111::set_R, "Get/set current R") + .property("N", &SEIRstoc111::get_N, "Get current N") + .property("beta", &SEIRstoc111::get_beta, &SEIRstoc111::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc111::get_omega, &SEIRstoc111::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc111::get_gamma, &SEIRstoc111::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc111::get_delta, &SEIRstoc111::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc111::get_repl, &SEIRstoc111::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc111::get_cull, &SEIRstoc111::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc111::get_vacc, &SEIRstoc111::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc111::get_time, "Get current time") + .property("trans_external", &SEIRstoc111::get_trans_external, &SEIRstoc111::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc111::get_trans_type, &SEIRstoc111::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc3NN = SEIRmodel; + class_("SEIRstoc3NN") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc3NN::show, "The show/print method") + .method("update", &SEIRstoc3NN::update, "The update method") + .method("run", &SEIRstoc3NN::run, "The run method") + .method("save", &SEIRstoc3NN::save, "The save method") + .method("reset", &SEIRstoc3NN::reset, "The reset method") + + .property("state", &SEIRstoc3NN::get_state, "Get current state") + .property("S", &SEIRstoc3NN::get_S, &SEIRstoc3NN::set_S, "Get/set current S") + .property("E", &SEIRstoc3NN::get_E, &SEIRstoc3NN::set_E, "Get/set current E") + .property("I", &SEIRstoc3NN::get_I, &SEIRstoc3NN::set_I, "Get/set current I") + .property("R", &SEIRstoc3NN::get_R, &SEIRstoc3NN::set_R, "Get/set current R") + .property("N", &SEIRstoc3NN::get_N, "Get current N") + .property("beta", &SEIRstoc3NN::get_beta, &SEIRstoc3NN::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc3NN::get_omega, &SEIRstoc3NN::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc3NN::get_gamma, &SEIRstoc3NN::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc3NN::get_delta, &SEIRstoc3NN::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc3NN::get_repl, &SEIRstoc3NN::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc3NN::get_cull, &SEIRstoc3NN::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc3NN::get_vacc, &SEIRstoc3NN::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc3NN::get_time, "Get current time") + .property("trans_external", &SEIRstoc3NN::get_trans_external, &SEIRstoc3NN::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc3NN::get_trans_type, &SEIRstoc3NN::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc3N0 = SEIRmodel; + class_("SEIRstoc3N0") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc3N0::show, "The show/print method") + .method("update", &SEIRstoc3N0::update, "The update method") + .method("run", &SEIRstoc3N0::run, "The run method") + .method("save", &SEIRstoc3N0::save, "The save method") + .method("reset", &SEIRstoc3N0::reset, "The reset method") + + .property("state", &SEIRstoc3N0::get_state, "Get current state") + .property("S", &SEIRstoc3N0::get_S, &SEIRstoc3N0::set_S, "Get/set current S") + .property("E", &SEIRstoc3N0::get_E, &SEIRstoc3N0::set_E, "Get/set current E") + .property("I", &SEIRstoc3N0::get_I, &SEIRstoc3N0::set_I, "Get/set current I") + .property("R", &SEIRstoc3N0::get_R, &SEIRstoc3N0::set_R, "Get/set current R") + .property("N", &SEIRstoc3N0::get_N, "Get current N") + .property("beta", &SEIRstoc3N0::get_beta, &SEIRstoc3N0::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc3N0::get_omega, &SEIRstoc3N0::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc3N0::get_gamma, &SEIRstoc3N0::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc3N0::get_delta, &SEIRstoc3N0::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc3N0::get_repl, &SEIRstoc3N0::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc3N0::get_cull, &SEIRstoc3N0::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc3N0::get_vacc, &SEIRstoc3N0::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc3N0::get_time, "Get current time") + .property("trans_external", &SEIRstoc3N0::get_trans_external, &SEIRstoc3N0::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc3N0::get_trans_type, &SEIRstoc3N0::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc3N1 = SEIRmodel; + class_("SEIRstoc3N1") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc3N1::show, "The show/print method") + .method("update", &SEIRstoc3N1::update, "The update method") + .method("run", &SEIRstoc3N1::run, "The run method") + .method("save", &SEIRstoc3N1::save, "The save method") + .method("reset", &SEIRstoc3N1::reset, "The reset method") + + .property("state", &SEIRstoc3N1::get_state, "Get current state") + .property("S", &SEIRstoc3N1::get_S, &SEIRstoc3N1::set_S, "Get/set current S") + .property("E", &SEIRstoc3N1::get_E, &SEIRstoc3N1::set_E, "Get/set current E") + .property("I", &SEIRstoc3N1::get_I, &SEIRstoc3N1::set_I, "Get/set current I") + .property("R", &SEIRstoc3N1::get_R, &SEIRstoc3N1::set_R, "Get/set current R") + .property("N", &SEIRstoc3N1::get_N, "Get current N") + .property("beta", &SEIRstoc3N1::get_beta, &SEIRstoc3N1::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc3N1::get_omega, &SEIRstoc3N1::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc3N1::get_gamma, &SEIRstoc3N1::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc3N1::get_delta, &SEIRstoc3N1::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc3N1::get_repl, &SEIRstoc3N1::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc3N1::get_cull, &SEIRstoc3N1::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc3N1::get_vacc, &SEIRstoc3N1::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc3N1::get_time, "Get current time") + .property("trans_external", &SEIRstoc3N1::get_trans_external, &SEIRstoc3N1::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc3N1::get_trans_type, &SEIRstoc3N1::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc31N = SEIRmodel; + class_("SEIRstoc31N") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc31N::show, "The show/print method") + .method("update", &SEIRstoc31N::update, "The update method") + .method("run", &SEIRstoc31N::run, "The run method") + .method("save", &SEIRstoc31N::save, "The save method") + .method("reset", &SEIRstoc31N::reset, "The reset method") + + .property("state", &SEIRstoc31N::get_state, "Get current state") + .property("S", &SEIRstoc31N::get_S, &SEIRstoc31N::set_S, "Get/set current S") + .property("E", &SEIRstoc31N::get_E, &SEIRstoc31N::set_E, "Get/set current E") + .property("I", &SEIRstoc31N::get_I, &SEIRstoc31N::set_I, "Get/set current I") + .property("R", &SEIRstoc31N::get_R, &SEIRstoc31N::set_R, "Get/set current R") + .property("N", &SEIRstoc31N::get_N, "Get current N") + .property("beta", &SEIRstoc31N::get_beta, &SEIRstoc31N::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc31N::get_omega, &SEIRstoc31N::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc31N::get_gamma, &SEIRstoc31N::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc31N::get_delta, &SEIRstoc31N::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc31N::get_repl, &SEIRstoc31N::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc31N::get_cull, &SEIRstoc31N::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc31N::get_vacc, &SEIRstoc31N::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc31N::get_time, "Get current time") + .property("trans_external", &SEIRstoc31N::get_trans_external, &SEIRstoc31N::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc31N::get_trans_type, &SEIRstoc31N::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc310 = SEIRmodel; + class_("SEIRstoc310") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc310::show, "The show/print method") + .method("update", &SEIRstoc310::update, "The update method") + .method("run", &SEIRstoc310::run, "The run method") + .method("save", &SEIRstoc310::save, "The save method") + .method("reset", &SEIRstoc310::reset, "The reset method") + + .property("state", &SEIRstoc310::get_state, "Get current state") + .property("S", &SEIRstoc310::get_S, &SEIRstoc310::set_S, "Get/set current S") + .property("E", &SEIRstoc310::get_E, &SEIRstoc310::set_E, "Get/set current E") + .property("I", &SEIRstoc310::get_I, &SEIRstoc310::set_I, "Get/set current I") + .property("R", &SEIRstoc310::get_R, &SEIRstoc310::set_R, "Get/set current R") + .property("N", &SEIRstoc310::get_N, "Get current N") + .property("beta", &SEIRstoc310::get_beta, &SEIRstoc310::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc310::get_omega, &SEIRstoc310::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc310::get_gamma, &SEIRstoc310::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc310::get_delta, &SEIRstoc310::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc310::get_repl, &SEIRstoc310::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc310::get_cull, &SEIRstoc310::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc310::get_vacc, &SEIRstoc310::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc310::get_time, "Get current time") + .property("trans_external", &SEIRstoc310::get_trans_external, &SEIRstoc310::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc310::get_trans_type, &SEIRstoc310::set_trans_type, "Get/set current trans_type") + ; + + using SEIRstoc311 = SEIRmodel; + class_("SEIRstoc311") + .constructor("Constructor") + .factory(invalidate_default_constructor) + + .method("show", &SEIRstoc311::show, "The show/print method") + .method("update", &SEIRstoc311::update, "The update method") + .method("run", &SEIRstoc311::run, "The run method") + .method("save", &SEIRstoc311::save, "The save method") + .method("reset", &SEIRstoc311::reset, "The reset method") + + .property("state", &SEIRstoc311::get_state, "Get current state") + .property("S", &SEIRstoc311::get_S, &SEIRstoc311::set_S, "Get/set current S") + .property("E", &SEIRstoc311::get_E, &SEIRstoc311::set_E, "Get/set current E") + .property("I", &SEIRstoc311::get_I, &SEIRstoc311::set_I, "Get/set current I") + .property("R", &SEIRstoc311::get_R, &SEIRstoc311::set_R, "Get/set current R") + .property("N", &SEIRstoc311::get_N, "Get current N") + .property("beta", &SEIRstoc311::get_beta, &SEIRstoc311::set_beta, "Get/set current beta") + .property("omega", &SEIRstoc311::get_omega, &SEIRstoc311::set_omega, "Get/set current omega") + .property("gamma", &SEIRstoc311::get_gamma, &SEIRstoc311::set_gamma, "Get/set current gamma") + .property("delta", &SEIRstoc311::get_delta, &SEIRstoc311::set_delta, "Get/set current delta") + .property("repl", &SEIRstoc311::get_repl, &SEIRstoc311::set_repl, "Get/set current repl") + .property("cull", &SEIRstoc311::get_cull, &SEIRstoc311::set_cull, "Get/set current cull") + .property("vacc", &SEIRstoc311::get_vacc, &SEIRstoc311::set_vacc, "Get/set current vacc") + .property("time", &SEIRstoc311::get_time, "Get current time") + .property("trans_external", &SEIRstoc311::get_trans_external, &SEIRstoc311::set_trans_external, "Get/set current trans_external") + .property("transmission_type", &SEIRstoc311::get_trans_type, &SEIRstoc311::set_trans_type, "Get/set current trans_type") ; diff --git a/src/module/class_template.cpp b/src/module/class_template.cpp index 11935cf..8a76cea 100644 --- a/src/module/class_template.cpp +++ b/src/module/class_template.cpp @@ -1,5 +1,5 @@ class_("NAME") - .constructor("Constructor") + .constructor("Constructor") .factory(invalidate_default_constructor) .method("show", &NAME::show, "The show/print method") diff --git a/src/module/generate_module.R b/src/module/generate_module.R index b758f84..7b01719 100644 --- a/src/module/generate_module.R +++ b/src/module/generate_module.R @@ -11,12 +11,15 @@ cat(readLines("src/module/ipdmr_module_template.cpp"), sep="\n", file="src/ipdmr ct <- paste0("\t", readLines("src/module/class_template.cpp")) |> paste(collapse="\n") -tribble(~Name, ~Template, - "SEIRdetN", "SEIRmodel", - "SEIRstocN", "SEIRmodel", - "SEIRdet3", "SEIRmodel", - "SEIRstoc3", "SEIRmodel", -) |> +expand_grid(ut=c("deterministic","stochastic"), ne=c(-1,0,1,3), ni=c(-1,1), nr=c(-1,0,1)) |> + mutate(Debug = "true") |> + mutate(Name = str_c("SEIR", + if_else(ut=="deterministic", "det", "stoc"), + if_else(ne==-1, "N", as.character(ne)), + if_else(ni==-1, "N", as.character(ni)), + if_else(nr==-1, "N", as.character(nr)) + )) |> + mutate(Template = str_c("SEIRmodel")) |> rowwise() |> group_split() |> lapply(function(x){