diff --git a/DESCRIPTION b/DESCRIPTION index c7a3f78..9bf3883 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: individual Title: Framework for Specifying and Simulating Individual Based Models -Version: 0.1.15 +Version: 0.1.16 Authors@R: c( person( given = "Giovanni", diff --git a/NAMESPACE b/NAMESPACE index f0d4aa4..687b7c4 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -18,6 +18,8 @@ export(infection_age_process) export(multi_probability_bernoulli_process) export(multi_probability_multinomial_process) export(reschedule_listener) +export(restore_object_state) +export(save_object_state) export(simulation_loop) export(update_category_listener) importFrom(R6,R6Class) diff --git a/NEWS.md b/NEWS.md index e4d72cf..7887165 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,7 @@ +# individual 0.1.16 + + * Allow events and variables to be added and removed when restoring the simulation. + # individual 0.1.15 * Added an `all.equal` implementation for bitsets. diff --git a/R/RcppExports.R b/R/RcppExports.R index f67a6e6..1773e95 100644 --- a/R/RcppExports.R +++ b/R/RcppExports.R @@ -165,8 +165,8 @@ double_variable_queue_shrink_bitset <- function(variable, index) { invisible(.Call(`_individual_double_variable_queue_shrink_bitset`, variable, index)) } -create_event <- function(restoreable) { - .Call(`_individual_create_event`, restoreable) +create_event <- function() { + .Call(`_individual_create_event`) } create_targeted_event <- function(size) { @@ -181,6 +181,10 @@ event_base_get_timestep <- function(event) { .Call(`_individual_event_base_get_timestep`, event) } +event_base_set_timestep <- function(event, time) { + invisible(.Call(`_individual_event_base_set_timestep`, event, time)) +} + event_base_should_trigger <- function(event) { .Call(`_individual_event_base_should_trigger`, event) } @@ -197,8 +201,8 @@ event_checkpoint <- function(event) { .Call(`_individual_event_checkpoint`, event) } -event_restore <- function(event, time, schedule) { - invisible(.Call(`_individual_event_restore`, event, time, schedule)) +event_restore <- function(event, schedule) { + invisible(.Call(`_individual_event_restore`, event, schedule)) } targeted_event_clear_schedule_vector <- function(event, target) { @@ -257,8 +261,8 @@ targeted_event_checkpoint <- function(event) { .Call(`_individual_targeted_event_checkpoint`, event) } -targeted_event_restore <- function(event, time, state) { - invisible(.Call(`_individual_targeted_event_restore`, event, time, state)) +targeted_event_restore <- function(event, state) { + invisible(.Call(`_individual_targeted_event_restore`, event, state)) } process_listener <- function(event, listener) { diff --git a/R/categorical_variable.R b/R/categorical_variable.R index f20acfb..8a172b1 100644 --- a/R/categorical_variable.R +++ b/R/categorical_variable.R @@ -96,21 +96,31 @@ CategoricalVariable <- R6Class( .update = function() variable_update(self$.variable), .resize = function() variable_resize(self$.variable), - .checkpoint = function() { + #' @description save the state of the variable + save_state = function() { categories <- self$get_categories() values <- lapply(categories, function(c) self$get_index_of(c)$to_vector()) names(values) <- categories values }, - .restore = function(values) { - stopifnot(names(values) == self$get_categories()) - stopifnot(sum(sapply(values, length)) == categorical_variable_get_size(self$.variable)) + #' @description restore the variable from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. This + #' parameter's value is ignored, it only exists to conform to a uniform + #' interface with events. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + if (!is.null(state)) { + stopifnot(names(state) == self$get_categories()) + stopifnot(sum(sapply(state, length)) == categorical_variable_get_size(self$.variable)) - for (c in names(values)) { - self$queue_update(c, values[[c]]) + for (c in names(state)) { + self$queue_update(c, state[[c]]) + } + self$.update() } - self$.update() } ) ) diff --git a/R/double_variable.R b/R/double_variable.R index 74dab45..a3e132d 100644 --- a/R/double_variable.R +++ b/R/double_variable.R @@ -147,11 +147,22 @@ DoubleVariable <- R6Class( .update = function() variable_update(self$.variable), .resize = function() variable_resize(self$.variable), - .checkpoint = function() self$get_values(), - .restore = function(values) { - stopifnot(length(values) == variable_get_size(self$.variable)) - self$queue_update(values) - self$.update() + #' @description save the state of the variable + save_state = function() self$get_values(), + + #' @description restore the variable from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. This + #' parameter's value is ignored, it only exists to conform to a uniform + #' interface with events. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + if (!is.null(state)) { + stopifnot(length(state) == variable_get_size(self$.variable)) + self$queue_update(state) + self$.update() + } } ) ) diff --git a/R/event.R b/R/event.R index dc60cd5..9c621e4 100644 --- a/R/event.R +++ b/R/event.R @@ -39,12 +39,16 @@ EventBase <- R6Class( Event <- R6Class( 'Event', inherit = EventBase, + private = list( + should_restore = FALSE + ), public = list( #' @description Initialise an Event. - #' @param restore if true, the schedule of this event is restored when restoring from a saved - #' simulation. + #' @param restore if true, the schedule of this event is restored when + #' restoring from a saved simulation. initialize = function(restore = TRUE) { - self$.event <- create_event(restore) + self$.event <- create_event() + private$should_restore = restore }, #' @description Schedule this event to occur in the future. @@ -74,11 +78,23 @@ Event <- R6Class( # NOTE: intentionally empty .resize = function() {}, - .checkpoint = function() { + #' @description save the state of the event + save_state = function() { event_checkpoint(self$.event) }, - .restore = function(time, schedule) { - event_restore(self$.event, time, schedule) + + #' @description restore the event from a previously saved state. + #' If the event was constructed with \code{restore = FALSE}, the state + #' argument is ignored. + #' @param timestep the timestep at which simulation is resumed. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + event_base_set_timestep(self$.event, timestep) + if (private$should_restore && !is.null(state)) { + event_restore(self$.event, state) + } } ) ) diff --git a/R/integer_variable.R b/R/integer_variable.R index dd322ac..2e3543e 100644 --- a/R/integer_variable.R +++ b/R/integer_variable.R @@ -190,11 +190,22 @@ IntegerVariable <- R6Class( .update = function() variable_update(self$.variable), .resize = function() variable_resize(self$.variable), - .checkpoint = function() self$get_values(), - .restore = function(values) { - stopifnot(length(values) == variable_get_size(self$.variable)) - self$queue_update(values) - self$.update() + #' @description save the state of the variable + save_state = function() self$get_values(), + + #' @description restore the variable from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. This + #' parameter's value is ignored, it only exists to conform to a uniform + #' interface with events. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + if (!is.null(state)) { + stopifnot(length(state) == variable_get_size(self$.variable)) + self$queue_update(state) + self$.update() + } } ) ) diff --git a/R/ragged_double.R b/R/ragged_double.R index df541db..e28fc96 100644 --- a/R/ragged_double.R +++ b/R/ragged_double.R @@ -152,11 +152,22 @@ RaggedDouble <- R6Class( .update = function() variable_update(self$.variable), .resize = function() variable_resize(self$.variable), - .checkpoint = function() self$get_values(), - .restore = function(values) { - stopifnot(length(values) == variable_get_size(self$.variable)) - self$queue_update(values) - self$.update() + #' @description save the state of the variable + save_state = function() self$get_values(), + + #' @description restore the variable from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. This + #' parameter's value is ignored, it only exists to conform to a uniform + #' interface with events. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + if (!is.null(state)) { + stopifnot(length(state) == variable_get_size(self$.variable)) + self$queue_update(state) + self$.update() + } } ) ) diff --git a/R/ragged_integer.R b/R/ragged_integer.R index 02ff318..1c21264 100644 --- a/R/ragged_integer.R +++ b/R/ragged_integer.R @@ -152,11 +152,22 @@ RaggedInteger <- R6Class( .update = function() variable_update(self$.variable), .resize = function() variable_resize(self$.variable), - .checkpoint = function() self$get_values(), - .restore = function(values) { - stopifnot(length(values) == variable_get_size(self$.variable)) - self$queue_update(values) - self$.update() + #' @description save the state of the variable + save_state = function() self$get_values(), + + #' @description restore the variable from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. This + #' parameter's value is ignored, it only exists to conform to a uniform + #' interface with events. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + if (!is.null(state)) { + stopifnot(length(state) == variable_get_size(self$.variable)) + self$queue_update(state) + self$.update() + } } ) ) diff --git a/R/simulation.R b/R/simulation.R index cee2cb0..50c58e7 100644 --- a/R/simulation.R +++ b/R/simulation.R @@ -7,6 +7,7 @@ #' @param timesteps the end timestep of the simulation. If `state` is not NULL, timesteps must be greater than `state$timestep` #' @param state a checkpoint from which to resume the simulation #' @param restore_random_state if TRUE, restore R's global random number generator's state from the checkpoint. +#' @return Invisibly, the saved state at the end of the simulation, suitable for later resuming. #' @examples #' population <- 4 #' timesteps <- 5 @@ -47,77 +48,92 @@ simulation_loop <- function( start <- 1 if (!is.null(state)) { - start <- restore_state(state, variables, events, restore_random_state) + start <- restore_simulation_state(state, variables, events, restore_random_state) if (start > timesteps) { stop("Restored state is already longer than timesteps") } } + flat_events <- unlist(events) + flat_variables <- unlist(variables) + for (t in seq(start, timesteps)) { for (process in processes) { execute_any_process(process, t) } - for (event in events) { + for (event in flat_events) { event$.process() } - for (variable in variables) { + for (variable in flat_variables) { variable$.update() } - for (event in events) { + for (event in flat_events) { event$.resize() } - for (variable in variables) { + for (variable in flat_variables) { variable$.resize() } - for (event in events) { + for (event in flat_events) { event$.tick() } } - invisible(checkpoint_state(timesteps, variables, events)) + invisible(save_simulation_state(timesteps, variables, events)) } #' @title Save the simulation state #' @description Save the simulation state in an R object, allowing it to be -#' resumed later using \code{\link[individual]{restore_state}}. -#' @param timesteps <- the number of time steps that have already been simulated +#' resumed later using \code{\link[individual]{restore_simulation_state}}. +#' @param timesteps the number of time steps that have already been simulated #' @param variables the list of Variables #' @param events the list of Events -checkpoint_state <- function(timesteps, variables, events) { +#' @return the saved simulation state. +save_simulation_state <- function(timesteps, variables, events) { random_state <- .GlobalEnv$.Random.seed list( - variables=lapply(variables, function(v) v$.checkpoint()), - events=lapply(events, function(e) e$.checkpoint()), + variables=save_object_state(variables), + events=save_object_state(events), timesteps=timesteps, random_state=random_state ) } +#' @title Save the state of a simulation object or set of objects. +#' @param objects a simulation object (eg. a variable or event) or an +#' arbitrarily nested list structure of such objects. +#' @return the saved states of the objects. This has the same shape as the given +#' \code{objects}: if a list was passed as an argument, this returns the +#' corresponding list of saved states. If a singular object was passed, this +#' returns just that particular object's state. +#' @export +save_object_state <- function(objects) { + if (is.list(objects)) { + lapply(objects, save_object_state) + } else { + objects$save_state() + } +} + #' @title Restore the simulation state #' @description Restore the simulation state from a previous checkpoint. -#' The state of passed events and variables is overwritten to match the state they -#' had when the simulation was checkpointed. Returns the time step at which the -#' simulation should resume. -#' @param state the simulation state to restore, as returned by \code{\link[individual]{restore_state}}. +#' The state of passed events and variables is overwritten to match the state +#' they had when the simulation was checkpointed. +#' @param state the simulation state to restore, as returned by +#' \code{\link[individual]{save_simulation_state}}. #' @param variables the list of Variables #' @param events the list of Events -#' @param restore_random_state if TRUE, restore R's global random number generator's state from the checkpoint. -restore_state <- function(state, variables, events, restore_random_state) { +#' @param restore_random_state if TRUE, restore R's global random number +#' generator's state from the checkpoint. +#' @return the time step at which the simulation should resume. +restore_simulation_state <- function( + state, + variables, + events, + restore_random_state) { timesteps <- state$timesteps + 1 - if (length(variables) != length(state$variables)) { - stop("Checkpoint's variables do not match simulation's") - } - for (i in seq_along(variables)) { - variables[[i]]$.restore(state$variables[[i]]) - } - - if (length(events) != length(state$events)) { - stop("Checkpoint's events do not match simulation's") - } - for (i in seq_along(events)) { - events[[i]]$.restore(timesteps, state$events[[i]]) - } + restore_object_state(timesteps, variables, state$variables) + restore_object_state(timesteps, events, state$events) if (restore_random_state) { .GlobalEnv$.Random.seed <- state$random_state @@ -126,6 +142,58 @@ restore_state <- function(state, variables, events, restore_random_state) { timesteps } +is_uniquely_named <- function(x) { + !is.null(names(x)) && all(names(x) != "") && !anyDuplicated(names(x)) +} + +#' @title Restore the state of simulation objects. +#' @description Restore the state of one or more simulation objects. The +#' specified objects are paired up with the relevant part of the state object, +#' and the \code{restore_state} method of each object is called. +#' +#' If the list of object is named, more objects may be specified than were +#' originally present in the saved simulation, allowing a simulation to be +#' extended with more features upon resuming. In this case, the +#' \code{restore_state} method of the new objects is called with a \code{NULL} +#' argument. Conversly, the list of objects may omit certain entries, in which +#' case their state to be restored is ignored. +#' +#' @param timesteps the number of time steps that have already been simulated +#' @param objects a simulation object (eg. a variable or event) or an +#' arbitrarily nested list structure of such objects. +#' @param state a saved simulation state for the given objects, as returned by +#' \code{\link[individual]{save_object_state}}. This should have the same shape +#' as the \code{objects} argument: if a list of objects is given, then +#' \code{state} should be a list of corresponding states. If NULL is passed, +#' then each object's \code{restore_state} method is called with NULL as +#' its argument. +#' @export +restore_object_state <- function(timesteps, objects, state) { + if (is.list(objects)) { + if (is.null(state)) { + keys <- NULL + reset <- seq_along(objects) + } else if (is_uniquely_named(objects) && is_uniquely_named(state)) { + keys <- intersect(names(objects), names(state)) + reset <- setdiff(names(objects), names(state)) + } else if (length(state) == length(objects)) { + keys <- seq_along(state) + reset <- NULL + } else { + stop("Saved state does not match resumed objects") + } + + for (k in keys) { + restore_object_state(timesteps, objects[[k]], state[[k]]) + } + for (k in reset) { + restore_object_state(timesteps, objects[[k]], NULL) + } + } else { + objects$restore_state(timesteps, state) + } +} + #' @title Execute a C++ or R process in the simulation #' @param p the process to execute #' @param t the timestep to pass to the process diff --git a/R/targeted_event.R b/R/targeted_event.R index e265b27..9492239 100644 --- a/R/targeted_event.R +++ b/R/targeted_event.R @@ -118,11 +118,21 @@ TargetedEvent <- R6Class( .resize = function() targeted_event_resize(self$.event), - .checkpoint = function() { + #' @description save the state of the event + save_state = function() { targeted_event_checkpoint(self$.event) }, - .restore = function(time, schedule) { - targeted_event_restore(self$.event, time, schedule) + + #' @description restore the event from a previously saved state. + #' @param timestep the timestep at which simulation is resumed. + #' @param state the previously saved state, as returned by the + #' \code{save_state} method. NULL is passed when restoring from a saved + #' simulation in which this variable did not exist. + restore_state = function(timestep, state) { + event_base_set_timestep(self$.event, timestep) + if (!is.null(state)) { + targeted_event_restore(self$.event, state) + } } ) ) diff --git a/_pkgdown.yml b/_pkgdown.yml index ec7d65a..1283d2a 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -27,5 +27,7 @@ reference: - title: "Simulation" - contents: - simulation_loop - - checkpoint_state - - restore_state + - restore_simulation_state + - save_simulation_state + - save_object_state + - restore_object_state diff --git a/inst/include/Event.h b/inst/include/Event.h index 73596e7..9d064e3 100644 --- a/inst/include/Event.h +++ b/inst/include/Event.h @@ -46,6 +46,7 @@ class EventBase { public: virtual void tick(); virtual size_t get_time() const; + virtual void set_time(size_t time) = 0; virtual bool should_trigger() = 0; virtual ~EventBase() = default; @@ -70,10 +71,8 @@ inline size_t EventBase::get_time() const { class Event : public EventBase { std::set simple_schedule; - bool restoreable; public: - Event(bool restoreable); virtual ~Event() = default; virtual void process(Rcpp::XPtr listener); @@ -83,8 +82,9 @@ class Event : public EventBase { virtual void schedule(std::vector delays); virtual void clear_schedule(); + virtual void set_time(size_t time) override; virtual std::vector checkpoint(); - virtual void restore(size_t time, std::vector schedule); + virtual void restore(std::vector schedule); }; //' @title process an event by calling a listener @@ -92,9 +92,6 @@ inline void Event::process(Rcpp::XPtr listener) { (*listener)(get_time()); } -inline Event::Event(bool restoreable) : restoreable(restoreable) { -} - //' @title should first event fire on this timestep? inline bool Event::should_trigger() { if (simple_schedule.empty()) { @@ -126,18 +123,16 @@ inline std::vector Event::checkpoint() { return {simple_schedule.begin(), simple_schedule.end()}; } -//' @title restore this event's state from a previous checkpoint -inline void Event::restore(size_t time, std::vector schedule) { +inline void Event::set_time(size_t time) { t = time; - if (restoreable) { - simple_schedule.clear(); - simple_schedule.insert(schedule.begin(), schedule.end()); - } else { - // We don't restore the event, but it is possible that the resume time - // is beyond some already scheduled timesteps. These need to be removed. - auto it = simple_schedule.lower_bound(time); - simple_schedule.erase(simple_schedule.begin(), it); - } + auto it = simple_schedule.lower_bound(time); + simple_schedule.erase(simple_schedule.begin(), it); +} + +//' @title restore this event's state from a previous checkpoint +inline void Event::restore(std::vector schedule) { + simple_schedule.clear(); + simple_schedule.insert(schedule.begin(), schedule.end()); } //' @title a targeted event in the simulation @@ -186,7 +181,8 @@ class TargetedEvent : public EventBase { virtual individual_index_t get_scheduled() const; virtual std::vector> checkpoint() const; - virtual void restore(size_t time, std::vector> schedule); + virtual void set_time(size_t time) override; + virtual void restore(std::vector> schedule); }; inline TargetedEvent::TargetedEvent(size_t size) @@ -402,12 +398,16 @@ TargetedEvent::checkpoint() const { return {targeted_schedule.begin(), targeted_schedule.end()}; } +inline void TargetedEvent::set_time(size_t time) { + t = time; + auto it = targeted_schedule.lower_bound(time); + targeted_schedule.erase(targeted_schedule.begin(), it); +} + //' @title restore this event's state from a previous checkpoint inline void TargetedEvent::restore( - size_t time, std::vector> schedule ) { - t = time; targeted_schedule.clear(); targeted_schedule.insert(schedule.begin(), schedule.end()); } diff --git a/man/CategoricalVariable.Rd b/man/CategoricalVariable.Rd index c286f4b..09bbb5d 100644 --- a/man/CategoricalVariable.Rd +++ b/man/CategoricalVariable.Rd @@ -23,8 +23,8 @@ if possible because certain operations will be faster. \item \href{#method-CategoricalVariable-size}{\code{CategoricalVariable$size()}} \item \href{#method-CategoricalVariable-.update}{\code{CategoricalVariable$.update()}} \item \href{#method-CategoricalVariable-.resize}{\code{CategoricalVariable$.resize()}} -\item \href{#method-CategoricalVariable-.checkpoint}{\code{CategoricalVariable$.checkpoint()}} -\item \href{#method-CategoricalVariable-.restore}{\code{CategoricalVariable$.restore()}} +\item \href{#method-CategoricalVariable-save_state}{\code{CategoricalVariable$save_state()}} +\item \href{#method-CategoricalVariable-restore_state}{\code{CategoricalVariable$restore_state()}} \item \href{#method-CategoricalVariable-clone}{\code{CategoricalVariable$clone()}} } } @@ -179,22 +179,37 @@ get the size of the variable } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-CategoricalVariable-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-CategoricalVariable-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the variable \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{CategoricalVariable$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{CategoricalVariable$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-CategoricalVariable-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-CategoricalVariable-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the variable from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{CategoricalVariable$.restore(values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{CategoricalVariable$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed. This +parameter's value is ignored, it only exists to conform to a uniform +interface with events.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/DoubleVariable.Rd b/man/DoubleVariable.Rd index 3540898..4cec895 100644 --- a/man/DoubleVariable.Rd +++ b/man/DoubleVariable.Rd @@ -19,8 +19,8 @@ Represents a continuous variable for an individual. \item \href{#method-DoubleVariable-size}{\code{DoubleVariable$size()}} \item \href{#method-DoubleVariable-.update}{\code{DoubleVariable$.update()}} \item \href{#method-DoubleVariable-.resize}{\code{DoubleVariable$.resize()}} -\item \href{#method-DoubleVariable-.checkpoint}{\code{DoubleVariable$.checkpoint()}} -\item \href{#method-DoubleVariable-.restore}{\code{DoubleVariable$.restore()}} +\item \href{#method-DoubleVariable-save_state}{\code{DoubleVariable$save_state()}} +\item \href{#method-DoubleVariable-restore_state}{\code{DoubleVariable$restore_state()}} \item \href{#method-DoubleVariable-clone}{\code{DoubleVariable$clone()}} } } @@ -199,22 +199,37 @@ get the size of the variable } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-DoubleVariable-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-DoubleVariable-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the variable \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{DoubleVariable$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{DoubleVariable$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-DoubleVariable-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-DoubleVariable-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the variable from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{DoubleVariable$.restore(values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{DoubleVariable$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed. This +parameter's value is ignored, it only exists to conform to a uniform +interface with events.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/Event.Rd b/man/Event.Rd index 4183357..aca4384 100644 --- a/man/Event.Rd +++ b/man/Event.Rd @@ -18,8 +18,8 @@ Describes a general event in the simulation. \item \href{#method-Event-.process_listener}{\code{Event$.process_listener()}} \item \href{#method-Event-.process_listener_cpp}{\code{Event$.process_listener_cpp()}} \item \href{#method-Event-.resize}{\code{Event$.resize()}} -\item \href{#method-Event-.checkpoint}{\code{Event$.checkpoint()}} -\item \href{#method-Event-.restore}{\code{Event$.restore()}} +\item \href{#method-Event-save_state}{\code{Event$save_state()}} +\item \href{#method-Event-restore_state}{\code{Event$restore_state()}} \item \href{#method-Event-clone}{\code{Event$clone()}} } } @@ -45,8 +45,8 @@ Initialise an Event. \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{restore}}{if true, the schedule of this event is restored when restoring from a saved -simulation.} +\item{\code{restore}}{if true, the schedule of this event is restored when +restoring from a saved simulation.} } \if{html}{\out{
}} } @@ -108,22 +108,37 @@ Stop a future event from triggering. } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Event-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-Event-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the event \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Event$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{Event$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Event-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-Event-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the event from a previously saved state. +If the event was constructed with \code{restore = FALSE}, the state +argument is ignored. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Event$.restore(time, schedule)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{Event$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/IntegerVariable.Rd b/man/IntegerVariable.Rd index 761c50b..1215f6a 100644 --- a/man/IntegerVariable.Rd +++ b/man/IntegerVariable.Rd @@ -23,8 +23,8 @@ household or age bin. \item \href{#method-IntegerVariable-size}{\code{IntegerVariable$size()}} \item \href{#method-IntegerVariable-.update}{\code{IntegerVariable$.update()}} \item \href{#method-IntegerVariable-.resize}{\code{IntegerVariable$.resize()}} -\item \href{#method-IntegerVariable-.checkpoint}{\code{IntegerVariable$.checkpoint()}} -\item \href{#method-IntegerVariable-.restore}{\code{IntegerVariable$.restore()}} +\item \href{#method-IntegerVariable-save_state}{\code{IntegerVariable$save_state()}} +\item \href{#method-IntegerVariable-restore_state}{\code{IntegerVariable$restore_state()}} \item \href{#method-IntegerVariable-clone}{\code{IntegerVariable$clone()}} } } @@ -211,22 +211,37 @@ get the size of the variable } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-IntegerVariable-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-IntegerVariable-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the variable \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{IntegerVariable$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{IntegerVariable$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-IntegerVariable-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-IntegerVariable-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the variable from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{IntegerVariable$.restore(values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{IntegerVariable$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed. This +parameter's value is ignored, it only exists to conform to a uniform +interface with events.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/RaggedDouble.Rd b/man/RaggedDouble.Rd index 86cb049..c402e79 100644 --- a/man/RaggedDouble.Rd +++ b/man/RaggedDouble.Rd @@ -18,8 +18,8 @@ This is a ragged array which stores doubles (numeric values). \item \href{#method-RaggedDouble-size}{\code{RaggedDouble$size()}} \item \href{#method-RaggedDouble-.update}{\code{RaggedDouble$.update()}} \item \href{#method-RaggedDouble-.resize}{\code{RaggedDouble$.resize()}} -\item \href{#method-RaggedDouble-.checkpoint}{\code{RaggedDouble$.checkpoint()}} -\item \href{#method-RaggedDouble-.restore}{\code{RaggedDouble$.restore()}} +\item \href{#method-RaggedDouble-save_state}{\code{RaggedDouble$save_state()}} +\item \href{#method-RaggedDouble-restore_state}{\code{RaggedDouble$restore_state()}} \item \href{#method-RaggedDouble-clone}{\code{RaggedDouble$clone()}} } } @@ -177,22 +177,37 @@ get the size of the variable } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-RaggedDouble-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-RaggedDouble-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the variable \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{RaggedDouble$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{RaggedDouble$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-RaggedDouble-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-RaggedDouble-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the variable from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{RaggedDouble$.restore(values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{RaggedDouble$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed. This +parameter's value is ignored, it only exists to conform to a uniform +interface with events.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/RaggedInteger.Rd b/man/RaggedInteger.Rd index 24e3556..9ec4aa3 100644 --- a/man/RaggedInteger.Rd +++ b/man/RaggedInteger.Rd @@ -18,8 +18,8 @@ This is a ragged array which stores integers (numeric values). \item \href{#method-RaggedInteger-size}{\code{RaggedInteger$size()}} \item \href{#method-RaggedInteger-.update}{\code{RaggedInteger$.update()}} \item \href{#method-RaggedInteger-.resize}{\code{RaggedInteger$.resize()}} -\item \href{#method-RaggedInteger-.checkpoint}{\code{RaggedInteger$.checkpoint()}} -\item \href{#method-RaggedInteger-.restore}{\code{RaggedInteger$.restore()}} +\item \href{#method-RaggedInteger-save_state}{\code{RaggedInteger$save_state()}} +\item \href{#method-RaggedInteger-restore_state}{\code{RaggedInteger$restore_state()}} \item \href{#method-RaggedInteger-clone}{\code{RaggedInteger$clone()}} } } @@ -177,22 +177,37 @@ get the size of the variable } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-RaggedInteger-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-RaggedInteger-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the variable \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{RaggedInteger$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{RaggedInteger$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-RaggedInteger-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-RaggedInteger-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the variable from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{RaggedInteger$.restore(values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{RaggedInteger$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed. This +parameter's value is ignored, it only exists to conform to a uniform +interface with events.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/TargetedEvent.Rd b/man/TargetedEvent.Rd index d12f2c0..26dfe7d 100644 --- a/man/TargetedEvent.Rd +++ b/man/TargetedEvent.Rd @@ -23,8 +23,8 @@ This is useful for events which are triggered for a sub-population. \item \href{#method-TargetedEvent-.process_listener}{\code{TargetedEvent$.process_listener()}} \item \href{#method-TargetedEvent-.process_listener_cpp}{\code{TargetedEvent$.process_listener_cpp()}} \item \href{#method-TargetedEvent-.resize}{\code{TargetedEvent$.resize()}} -\item \href{#method-TargetedEvent-.checkpoint}{\code{TargetedEvent$.checkpoint()}} -\item \href{#method-TargetedEvent-.restore}{\code{TargetedEvent$.restore()}} +\item \href{#method-TargetedEvent-save_state}{\code{TargetedEvent$save_state()}} +\item \href{#method-TargetedEvent-restore_state}{\code{TargetedEvent$restore_state()}} \item \href{#method-TargetedEvent-clone}{\code{TargetedEvent$clone()}} } } @@ -185,22 +185,35 @@ Shrink the TargetedEvent. } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-TargetedEvent-.checkpoint}{}}} -\subsection{Method \code{.checkpoint()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-TargetedEvent-save_state}{}}} +\subsection{Method \code{save_state()}}{ +save the state of the event \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{TargetedEvent$.checkpoint()}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{TargetedEvent$save_state()}\if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-TargetedEvent-.restore}{}}} -\subsection{Method \code{.restore()}}{ +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-TargetedEvent-restore_state}{}}} +\subsection{Method \code{restore_state()}}{ +restore the event from a previously saved state. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{TargetedEvent$.restore(time, schedule)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{TargetedEvent$restore_state(timestep, state)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{timestep}}{the timestep at which simulation is resumed.} + +\item{\code{state}}{the previously saved state, as returned by the +\code{save_state} method. NULL is passed when restoring from a saved +simulation in which this variable did not exist.} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/restore_object_state.Rd b/man/restore_object_state.Rd new file mode 100644 index 0000000..f9a600a --- /dev/null +++ b/man/restore_object_state.Rd @@ -0,0 +1,31 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/simulation.R +\name{restore_object_state} +\alias{restore_object_state} +\title{Restore the state of simulation objects.} +\usage{ +restore_object_state(timesteps, objects, state) +} +\arguments{ +\item{timesteps}{the number of time steps that have already been simulated} + +\item{objects}{a simulation object (eg. a variable or event) or an +arbitrarily nested list structure of such objects.} + +\item{state}{a saved simulation state for the given objects, as returned by +\code{\link[individual]{save_object_state}}. This should have the same shape +as the \code{objects} argument: if a list of objects is given, then +\code{state} should be a list of corresponding states. If NULL is passed, +then each object's \code{restore_state} method is called with NULL as +its argument.} +} +\description{ +Restore the state of one or more simulation objects. The +specified objects are paired up with the relevant part of the state object, +and the \code{restore_state} method of each object is called. + +If the list of object is named, more objects may be specified than were +originally present in the saved simulation, allowing a simulation to be +extended with more features upon resuming. In this case, the +\code{restore_state} method is called with a \code{NULL} argument. +} diff --git a/man/restore_state.Rd b/man/restore_simulation_state.Rd similarity index 50% rename from man/restore_state.Rd rename to man/restore_simulation_state.Rd index abfdfe1..24d36b3 100644 --- a/man/restore_state.Rd +++ b/man/restore_simulation_state.Rd @@ -1,23 +1,27 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/simulation.R -\name{restore_state} -\alias{restore_state} +\name{restore_simulation_state} +\alias{restore_simulation_state} \title{Restore the simulation state} \usage{ -restore_state(state, variables, events, restore_random_state) +restore_simulation_state(state, variables, events, restore_random_state) } \arguments{ -\item{state}{the simulation state to restore, as returned by \code{\link[individual]{restore_state}}.} +\item{state}{the simulation state to restore, as returned by +\code{\link[individual]{save_simulation_state}}.} \item{variables}{the list of Variables} \item{events}{the list of Events} -\item{restore_random_state}{if TRUE, restore R's global random number generator's state from the checkpoint.} +\item{restore_random_state}{if TRUE, restore R's global random number +generator's state from the checkpoint.} +} +\value{ +the time step at which the simulation should resume. } \description{ Restore the simulation state from a previous checkpoint. -The state of passed events and variables is overwritten to match the state they -had when the simulation was checkpointed. Returns the time step at which the -simulation should resume. +The state of passed events and variables is overwritten to match the state +they had when the simulation was checkpointed. } diff --git a/man/save_object_state.Rd b/man/save_object_state.Rd new file mode 100644 index 0000000..8169dd2 --- /dev/null +++ b/man/save_object_state.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/simulation.R +\name{save_object_state} +\alias{save_object_state} +\title{Save the state of a simulation object or set of objects.} +\usage{ +save_object_state(objects) +} +\arguments{ +\item{objects}{a simulation object (eg. a variable or event) or an +arbitrarily nested list structure of such objects.} +} +\value{ +the saved states of the objects. This has the same shape as the given +\code{objects}: if a list was passed as an argument, this returns the +corresponding list of saved states. If a singular object was passed, this +returns just that particular object's state. +} +\description{ +Save the state of a simulation object or set of objects. +} diff --git a/man/checkpoint_state.Rd b/man/save_simulation_state.Rd similarity index 50% rename from man/checkpoint_state.Rd rename to man/save_simulation_state.Rd index cdc96c9..23eb6e1 100644 --- a/man/checkpoint_state.Rd +++ b/man/save_simulation_state.Rd @@ -1,19 +1,22 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/simulation.R -\name{checkpoint_state} -\alias{checkpoint_state} +\name{save_simulation_state} +\alias{save_simulation_state} \title{Save the simulation state} \usage{ -checkpoint_state(timesteps, variables, events) +save_simulation_state(timesteps, variables, events) } \arguments{ -\item{timesteps}{<- the number of time steps that have already been simulated} +\item{timesteps}{the number of time steps that have already been simulated} \item{variables}{the list of Variables} \item{events}{the list of Events} } +\value{ +the saved simulation state. +} \description{ Save the simulation state in an R object, allowing it to be -resumed later using \code{\link[individual]{restore_state}}. +resumed later using \code{\link[individual]{restore_simulation_state}}. } diff --git a/man/simulation_loop.Rd b/man/simulation_loop.Rd index 5b2b887..96d6e89 100644 --- a/man/simulation_loop.Rd +++ b/man/simulation_loop.Rd @@ -26,6 +26,9 @@ simulation_loop( \item{restore_random_state}{if TRUE, restore R's global random number generator's state from the checkpoint.} } +\value{ +Invisibly, the saved state at the end of the simulation, suitable for later resuming. +} \description{ Run a simulation where event listeners take precedence over processes for state changes. diff --git a/src/RcppExports.cpp b/src/RcppExports.cpp index 3ac7d5c..139554e 100644 --- a/src/RcppExports.cpp +++ b/src/RcppExports.cpp @@ -512,13 +512,12 @@ BEGIN_RCPP END_RCPP } // create_event -Rcpp::XPtr create_event(bool restoreable); -RcppExport SEXP _individual_create_event(SEXP restoreableSEXP) { +Rcpp::XPtr create_event(); +RcppExport SEXP _individual_create_event() { BEGIN_RCPP Rcpp::RObject rcpp_result_gen; Rcpp::RNGScope rcpp_rngScope_gen; - Rcpp::traits::input_parameter< bool >::type restoreable(restoreableSEXP); - rcpp_result_gen = Rcpp::wrap(create_event(restoreable)); + rcpp_result_gen = Rcpp::wrap(create_event()); return rcpp_result_gen; END_RCPP } @@ -554,6 +553,17 @@ BEGIN_RCPP return rcpp_result_gen; END_RCPP } +// event_base_set_timestep +void event_base_set_timestep(const Rcpp::XPtr event, size_t time); +RcppExport SEXP _individual_event_base_set_timestep(SEXP eventSEXP, SEXP timeSEXP) { +BEGIN_RCPP + Rcpp::RNGScope rcpp_rngScope_gen; + Rcpp::traits::input_parameter< const Rcpp::XPtr >::type event(eventSEXP); + Rcpp::traits::input_parameter< size_t >::type time(timeSEXP); + event_base_set_timestep(event, time); + return R_NilValue; +END_RCPP +} // event_base_should_trigger bool event_base_should_trigger(const Rcpp::XPtr event); RcppExport SEXP _individual_event_base_should_trigger(SEXP eventSEXP) { @@ -598,14 +608,13 @@ BEGIN_RCPP END_RCPP } // event_restore -void event_restore(const Rcpp::XPtr event, size_t time, std::vector schedule); -RcppExport SEXP _individual_event_restore(SEXP eventSEXP, SEXP timeSEXP, SEXP scheduleSEXP) { +void event_restore(const Rcpp::XPtr event, std::vector schedule); +RcppExport SEXP _individual_event_restore(SEXP eventSEXP, SEXP scheduleSEXP) { BEGIN_RCPP Rcpp::RNGScope rcpp_rngScope_gen; Rcpp::traits::input_parameter< const Rcpp::XPtr >::type event(eventSEXP); - Rcpp::traits::input_parameter< size_t >::type time(timeSEXP); Rcpp::traits::input_parameter< std::vector >::type schedule(scheduleSEXP); - event_restore(event, time, schedule); + event_restore(event, schedule); return R_NilValue; END_RCPP } @@ -767,14 +776,13 @@ BEGIN_RCPP END_RCPP } // targeted_event_restore -void targeted_event_restore(const Rcpp::XPtr event, size_t time, Rcpp::List state); -RcppExport SEXP _individual_targeted_event_restore(SEXP eventSEXP, SEXP timeSEXP, SEXP stateSEXP) { +void targeted_event_restore(const Rcpp::XPtr event, Rcpp::List state); +RcppExport SEXP _individual_targeted_event_restore(SEXP eventSEXP, SEXP stateSEXP) { BEGIN_RCPP Rcpp::RNGScope rcpp_rngScope_gen; Rcpp::traits::input_parameter< const Rcpp::XPtr >::type event(eventSEXP); - Rcpp::traits::input_parameter< size_t >::type time(timeSEXP); Rcpp::traits::input_parameter< Rcpp::List >::type state(stateSEXP); - targeted_event_restore(event, time, state); + targeted_event_restore(event, state); return R_NilValue; END_RCPP } @@ -1488,15 +1496,16 @@ static const R_CallMethodDef CallEntries[] = { {"_individual_double_variable_queue_extend", (DL_FUNC) &_individual_double_variable_queue_extend, 2}, {"_individual_double_variable_queue_shrink", (DL_FUNC) &_individual_double_variable_queue_shrink, 2}, {"_individual_double_variable_queue_shrink_bitset", (DL_FUNC) &_individual_double_variable_queue_shrink_bitset, 2}, - {"_individual_create_event", (DL_FUNC) &_individual_create_event, 1}, + {"_individual_create_event", (DL_FUNC) &_individual_create_event, 0}, {"_individual_create_targeted_event", (DL_FUNC) &_individual_create_targeted_event, 1}, {"_individual_event_base_tick", (DL_FUNC) &_individual_event_base_tick, 1}, {"_individual_event_base_get_timestep", (DL_FUNC) &_individual_event_base_get_timestep, 1}, + {"_individual_event_base_set_timestep", (DL_FUNC) &_individual_event_base_set_timestep, 2}, {"_individual_event_base_should_trigger", (DL_FUNC) &_individual_event_base_should_trigger, 1}, {"_individual_event_schedule", (DL_FUNC) &_individual_event_schedule, 2}, {"_individual_event_clear_schedule", (DL_FUNC) &_individual_event_clear_schedule, 1}, {"_individual_event_checkpoint", (DL_FUNC) &_individual_event_checkpoint, 1}, - {"_individual_event_restore", (DL_FUNC) &_individual_event_restore, 3}, + {"_individual_event_restore", (DL_FUNC) &_individual_event_restore, 2}, {"_individual_targeted_event_clear_schedule_vector", (DL_FUNC) &_individual_targeted_event_clear_schedule_vector, 2}, {"_individual_targeted_event_clear_schedule", (DL_FUNC) &_individual_targeted_event_clear_schedule, 2}, {"_individual_targeted_event_get_scheduled", (DL_FUNC) &_individual_targeted_event_get_scheduled, 1}, @@ -1511,7 +1520,7 @@ static const R_CallMethodDef CallEntries[] = { {"_individual_targeted_event_get_target", (DL_FUNC) &_individual_targeted_event_get_target, 1}, {"_individual_targeted_event_resize", (DL_FUNC) &_individual_targeted_event_resize, 1}, {"_individual_targeted_event_checkpoint", (DL_FUNC) &_individual_targeted_event_checkpoint, 1}, - {"_individual_targeted_event_restore", (DL_FUNC) &_individual_targeted_event_restore, 3}, + {"_individual_targeted_event_restore", (DL_FUNC) &_individual_targeted_event_restore, 2}, {"_individual_process_listener", (DL_FUNC) &_individual_process_listener, 2}, {"_individual_process_targeted_listener", (DL_FUNC) &_individual_process_targeted_listener, 3}, {"_individual_create_integer_variable", (DL_FUNC) &_individual_create_integer_variable, 1}, diff --git a/src/event.cpp b/src/event.cpp index ef8fd7a..fb341b4 100644 --- a/src/event.cpp +++ b/src/event.cpp @@ -9,8 +9,8 @@ #include "utils.h" //[[Rcpp::export]] -Rcpp::XPtr create_event(bool restoreable) { - return Rcpp::XPtr(new Event(restoreable), true); +Rcpp::XPtr create_event() { + return Rcpp::XPtr(new Event(), true); } //[[Rcpp::export]] @@ -28,6 +28,11 @@ size_t event_base_get_timestep(const Rcpp::XPtr event) { return event->get_time(); } +//[[Rcpp::export]] +void event_base_set_timestep(const Rcpp::XPtr event, size_t time) { + return event->set_time(time); +} + //[[Rcpp::export]] bool event_base_should_trigger(const Rcpp::XPtr event) { return event->should_trigger(); @@ -49,13 +54,13 @@ std::vector event_checkpoint(const Rcpp::XPtr event) { } //[[Rcpp::export]] -void event_restore(const Rcpp::XPtr event, size_t time, std::vector schedule) { +void event_restore(const Rcpp::XPtr event, std::vector schedule) { for (size_t event_ts: schedule) { - if (event_ts < time) { + if (event_ts < event->get_time()) { Rcpp::stop("schedule is in the past"); } } - event->restore(time, schedule); + event->restore(schedule); } //[[Rcpp::export]] @@ -202,7 +207,7 @@ Rcpp::List targeted_event_checkpoint(const Rcpp::XPtr event) { } //[[Rcpp::export]] -void targeted_event_restore(const Rcpp::XPtr event, size_t time, Rcpp::List state) { +void targeted_event_restore(const Rcpp::XPtr event, Rcpp::List state) { std::vector timesteps = state["timesteps"]; std::vector> targets = state["targets"];; @@ -212,7 +217,7 @@ void targeted_event_restore(const Rcpp::XPtr event, size_t time, std::vector> schedule; for (size_t i = 0; i < timesteps.size(); i++) { - if (timesteps[i] < time) { + if (timesteps[i] < event->get_time()) { Rcpp::stop("schedule is in the past"); } decrement(targets[i]); @@ -221,7 +226,7 @@ void targeted_event_restore(const Rcpp::XPtr event, size_t time, schedule.push_back({timesteps[i], bitmap}); } - event->restore(time, schedule); + event->restore(schedule); } // [[Rcpp::export]] diff --git a/tests/testthat/test-categoricalvariable.R b/tests/testthat/test-categoricalvariable.R index dcd1f9b..d748076 100644 --- a/tests/testthat/test-categoricalvariable.R +++ b/tests/testthat/test-categoricalvariable.R @@ -91,13 +91,13 @@ test_that("CategoricalVariables supports checkpoint and restore", { old_variable$queue_update('R', c(2, 7)) old_variable$.update() - state <- old_variable$.checkpoint() + state <- old_variable$save_state() new_variable <- CategoricalVariable$new(SIR, rep('S', size)) - new_variable$.restore(state) + new_variable$restore_state(1, state) expect_equal(new_variable$get_index_of('S')$to_vector(), c(4,5,6,8,9,10)) expect_equal(new_variable$get_index_of('I')$to_vector(), c(1,3)) expect_equal(new_variable$get_index_of('R')$to_vector(), c(2,7)) - expect_equal(new_variable$.checkpoint(), state) + expect_equal(new_variable$save_state(), state) }) diff --git a/tests/testthat/test-checkpoint.R b/tests/testthat/test-checkpoint.R index 80dd3c8..edd7d62 100644 --- a/tests/testthat/test-checkpoint.R +++ b/tests/testthat/test-checkpoint.R @@ -153,19 +153,47 @@ test_that("stochastic simulation can be resumed deterministically", { expect_mapequal(contiguous_run[6:10,], second_run[6:10,]) }) -test_that("cannot add nor remove variables when resuming", { - make_variables <- function(count) { - lapply(seq_len(count), function(i) DoubleVariable$new(1:10)) - } +test_that("can add named variables when resuming", { + state <- simulation_loop(timesteps = 5, variables = list( + a = DoubleVariable$new(1:10) + )) + expect_no_error(simulation_loop(timesteps = 10, state = state, variables = list( + a = DoubleVariable$new(1:10), + b = DoubleVariable$new(1:10) + ))) +}) - state <- simulation_loop(timesteps = 5, variables = make_variables(2)) +test_that("cannot add unnamed variables when resuming", { + state <- simulation_loop(timesteps = 5, variables = list( + DoubleVariable$new(1:10) + )) + expect_error(simulation_loop(timesteps = 10, state = state, variables = list( + DoubleVariable$new(1:10), + DoubleVariable$new(1:10) + )), "Saved state does not match resumed objects") +}) - expect_error( - simulation_loop(timesteps = 10, variables = make_variables(1), state = state), - "Checkpoint's variables do not match simulation's") - expect_error( - simulation_loop(timesteps = 10, variables = make_variables(3), state = state), - "Checkpoint's variables do not match simulation's") +test_that("can remove variables when resuming", { + state <- simulation_loop(timesteps = 5, variables = list( + a = DoubleVariable$new(1:10), + b = DoubleVariable$new(1:10) + )) + expect_no_error(simulation_loop(timesteps = 10, state = state, variables = list( + a = DoubleVariable$new(1:10) + ))) +}) + +test_that("can add events when resuming", { + state <- simulation_loop(timesteps = 5, events = list()) + + listener <- mockery::mock() + event <- Event$new() + event$schedule(7) + event$add_listener(listener) + simulation_loop(timesteps = 10, events = list(a=event)) + + mockery::expect_called(listener, 1) + mockery::expect_args(listener, 1, t = 8) }) test_that("cannot resume with smaller timesteps", { @@ -179,3 +207,185 @@ test_that("cannot resume with smaller timesteps", { simulation_loop(timesteps = 10, state = state), "Restored state is already longer than timesteps") }) + +MockState <- R6Class( + 'MockState', + private = list(value = NULL), + public = list( + save_state = function() private$value, + restore_state = NULL, + initialize = function(value = NULL) { + private$value <- value + self$restore_state <- mockery::mock() + } + ) +) + +test_that("saved object's state is returned", { + o <- MockState$new("foo") + state <- save_object_state(o) + expect_identical(state, "foo") +}) + +test_that("saved objects' state is returned as list", { + o1 <- MockState$new("foo") + o2 <- MockState$new("bar") + state <- save_object_state(list(o1, o2)) + expect_identical(state, list("foo", "bar")) +}) + +test_that("saved objects' state preserves names", { + o1 <- MockState$new("foo") + o2 <- MockState$new("bar") + state <- save_object_state(list(x=o1, y=o2)) + expect_identical(state, list(x="foo", y="bar")) +}) + +test_that("saved objects' state preserves nested structure", { + o1 <- MockState$new("foo") + o2 <- MockState$new("bar") + o3 <- MockState$new("baz") + + state <- save_object_state(list(x=o1, y=list(o2, o3))) + expect_identical(state, list(x="foo", y=list("bar", "baz"))) +}) + +test_that("empty list is returned for empty list of objects", { + state <- save_object_state(list()) + expect_identical(state, list()) +}) + +test_that("restore_state method is called on object", { + o <- MockState$new() + restore_object_state(123, o, "state") + mockery::expect_called(o$restore_state, 1) + mockery::expect_args(o$restore_state, 1, 123, "state") +}) + +test_that("restore_state method is called on object list", { + o1 <- MockState$new() + o2 <- MockState$new() + restore_object_state(123, list(o1, o2), list("hello", "world")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "hello") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, "world") +}) + +test_that("restore_state method is called on named object list", { + o1 <- MockState$new() + o2 <- MockState$new() + + # Lists get paired up by name, even if the order is different + restore_object_state(123, list(x=o1, y=o2), list(y="world", x="hello")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "hello") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, "world") +}) + +test_that("restore_state method is called on nested object list", { + o1 <- MockState$new() + o2 <- MockState$new() + o3 <- MockState$new() + + restore_object_state( + 123, + list(list(o1, o2), o3), + list(list("foo", "bar"), "baz")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "foo") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, "bar") + + mockery::expect_called(o3$restore_state, 1) + mockery::expect_args(o3$restore_state, 1, 123, "baz") +}) + +test_that("restore_state method is called with NULL for new objects", { + o1 <- MockState$new() + o2 <- MockState$new() + o3 <- MockState$new() + + restore_object_state( + 123, + list(x=o1, y=o2, z=o3), + list(x="foo", z="baz")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "foo") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, NULL) + + mockery::expect_called(o3$restore_state, 1) + mockery::expect_args(o3$restore_state, 1, 123, "baz") +}) + +test_that("cannot restore objects with partial unnamed list", { + o1 <- MockState$new() + o2 <- MockState$new() + + expect_error( + restore_object_state(123, list(o1, o2), list("foo")), + "Saved state does not match resumed objects") +}) + +test_that("restore_state method is called with NULL for new list of objects", { + o1 <- MockState$new() + o2 <- MockState$new() + o3 <- MockState$new() + + restore_object_state( + 123, + list(x=o1, y=list(o2, o3)), + list(x="foo")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "foo") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, NULL) + + mockery::expect_called(o3$restore_state, 1) + mockery::expect_args(o3$restore_state, 1, 123, NULL) +}) + +test_that("restore_state method is called with NULL for all objects", { + o1 <- MockState$new() + o2 <- MockState$new() + o3 <- MockState$new() + + restore_object_state(123, list(x=o1, y=o2, z=o3), NULL) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, NULL) + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, NULL) + + mockery::expect_called(o3$restore_state, 1) + mockery::expect_args(o3$restore_state, 1, 123, NULL) +}) + +test_that("restore_state method is called even when other objects are absent", { + o1 <- MockState$new() + o2 <- MockState$new() + + restore_object_state( + 123, + list(x=o1, z=o2), + list(x="foo", y="bar", z="baz")) + + mockery::expect_called(o1$restore_state, 1) + mockery::expect_args(o1$restore_state, 1, 123, "foo") + + mockery::expect_called(o2$restore_state, 1) + mockery::expect_args(o2$restore_state, 1, 123, "baz") +}) diff --git a/tests/testthat/test-doublevariable.R b/tests/testthat/test-doublevariable.R index d351c39..38c710a 100644 --- a/tests/testthat/test-doublevariable.R +++ b/tests/testthat/test-doublevariable.R @@ -160,11 +160,11 @@ test_that("DoubleVariable supports checkpoint and restore", { old_variable$queue_update(values = seq_len(size)) old_variable$.update() - state <- old_variable$.checkpoint() + state <- old_variable$save_state() new_variable <- DoubleVariable$new(rep(0, size)) - new_variable$.restore(state) + new_variable$restore_state(1, state) expect_equal(new_variable$get_values(), seq_len(size)) - expect_equal(new_variable$.checkpoint(), state) + expect_equal(new_variable$save_state(), state) }) diff --git a/tests/testthat/test-events.R b/tests/testthat/test-events.R index 2045b2e..b6329af 100644 --- a/tests/testthat/test-events.R +++ b/tests/testthat/test-events.R @@ -123,9 +123,9 @@ test_that("events can be saved and restored", { new_event <- Event$new() new_event$add_listener(listener) - new_event$.restore( + new_event$restore_state( old_event$.timestep(), - old_event$.checkpoint()) + old_event$save_state()) expect_equal(new_event$.timestep(), 3) @@ -152,9 +152,9 @@ test_that("events are cleared when restored", { # Schedule at t=2. This will be cleared and overridden when restoring, # replaced by the earlier t=4 schedule. new_event$schedule(1) - new_event$.restore( + new_event$restore_state( old_event$.timestep(), - old_event$.checkpoint()) + old_event$save_state()) #time=1 new_event$.process() @@ -197,9 +197,9 @@ test_that("event is not cleared when restore is disabled", { new_event$schedule(5) # t=6, this will trigger # This should restore the timestep, but not any of the old event's schedule. - new_event$.restore( + new_event$restore_state( old_event$.timestep(), - old_event$.checkpoint()) + old_event$save_state()) expect_equal(new_event$.timestep(), 3) @@ -226,6 +226,38 @@ test_that("event is not cleared when restore is disabled", { new_event$.tick() }) +test_that("event can be restored from NULL state", { + listener <- mockery::mock() + + event <- Event$new() + event$schedule(6) # t=7 + event$add_listener(listener) + + event$restore_state(5, NULL) + expect_equal(event$.timestep(), 5) + + # time = 5 + event$.process() + mockery::expect_called(listener, 0) + event$.tick() + + # time = 6 + event$.process() + mockery::expect_called(listener, 0) + event$.tick() + + # time = 7 + event$.process() + mockery::expect_called(listener, 1) + mockery::expect_args(listener, 1, t = 7) + event$.tick() + + # time = 8 + event$.process() + mockery::expect_called(listener, 1) + event$.tick() +}) + test_that("empty event never triggers", { event <- Event$new() listener <- mockery::mock() diff --git a/tests/testthat/test-integervariable.R b/tests/testthat/test-integervariable.R index ccef08e..d79e994 100644 --- a/tests/testthat/test-integervariable.R +++ b/tests/testthat/test-integervariable.R @@ -197,11 +197,11 @@ test_that("IntegerVariable supports checkpoint and restore", { old_variable$queue_update(values = seq_len(size)) old_variable$.update() - state <- old_variable$.checkpoint() + state <- old_variable$save_state() new_variable <- IntegerVariable$new(rep(0, size)) - new_variable$.restore(state) + new_variable$restore_state(1, state) expect_equal(new_variable$get_values(), seq_len(size)) - expect_equal(new_variable$.checkpoint(), state) + expect_equal(new_variable$save_state(), state) }) diff --git a/tests/testthat/test-raggeddouble.R b/tests/testthat/test-raggeddouble.R index c7004c2..9194571 100644 --- a/tests/testthat/test-raggeddouble.R +++ b/tests/testthat/test-raggeddouble.R @@ -101,13 +101,13 @@ test_that("RaggedDouble supports checkpoint and restore", { old_variable$queue_update(values = list(c(7.1,3.2)), index = c(6,8)) old_variable$.update() - state <- old_variable$.checkpoint() + state <- old_variable$save_state() new_variable <- RaggedDouble$new(rep(list(0), size)) - new_variable$.restore(state) + new_variable$restore_state(1, state) expect_equal(new_variable$get_values(), list( 0, 0, c(1.1,2.2), c(1.1,2.2), 0, c(7.1,3.2), 0, c(7.1,3.2), 0, 0 )) - expect_equal(new_variable$.checkpoint(), state) + expect_equal(new_variable$save_state(), state) }) diff --git a/tests/testthat/test-raggedinteger.R b/tests/testthat/test-raggedinteger.R index 63895fc..9782b32 100644 --- a/tests/testthat/test-raggedinteger.R +++ b/tests/testthat/test-raggedinteger.R @@ -100,13 +100,13 @@ test_that("RaggedInteger supports checkpoint and restore", { old_variable$queue_update(values = list(c(1,2)), index = c(3,4)) old_variable$queue_update(values = list(c(7,3)), index = c(6,8)) old_variable$.update() - state <- old_variable$.checkpoint() + state <- old_variable$save_state() new_variable <- RaggedInteger$new(rep(list(0), size)) - new_variable$.restore(state) + new_variable$restore_state(1, state) expect_equal(new_variable$get_values(), list( 0, 0, c(1,2), c(1,2), 0, c(7,3), 0, c(7,3), 0, 0 )) - expect_equal(new_variable$.checkpoint(), state) + expect_equal(new_variable$save_state(), state) }) diff --git a/tests/testthat/test-targetedevent.R b/tests/testthat/test-targetedevent.R index b46ef28..0437cb8 100644 --- a/tests/testthat/test-targetedevent.R +++ b/tests/testthat/test-targetedevent.R @@ -552,9 +552,9 @@ test_that("targeted events can be saved and restored", { new_event <- TargetedEvent$new(10) new_event$add_listener(listener) - new_event$.restore( + new_event$restore_state( old_event$.timestep(), - old_event$.checkpoint()) + old_event$save_state()) #time = 4 new_event$.process() @@ -577,9 +577,9 @@ test_that("targeted events are cleared when restored", { new_event$schedule(c(1, 3), 2) new_event$schedule(c(5), 3) - new_event$.restore( + new_event$restore_state( old_event$.timestep(), - old_event$.checkpoint()) + old_event$save_state()) #time=1 new_event$.process() @@ -603,6 +603,12 @@ test_that("targeted events are cleared when restored", { mockery::expect_called(listener, 1) }) +test_that("targeted event can be restored from NULL state", { + event <- TargetedEvent$new(10) + event$restore_state(5, NULL) + expect_equal(event$.timestep(), 5) +}) + test_that("empty targeted event never triggers", { event <- TargetedEvent$new(5) listener <- mockery::mock()