From 45df936b86b6f2df4d63d3289c31027e68999083 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Sun, 15 Nov 2020 21:51:20 +0100 Subject: [PATCH 01/21] initial version of mpi support --- R/model.R | 100 ++++++++++++++++++++++++++++++++++++++++++++++++++++++ R/run.R | 22 +++++++++--- 2 files changed, 117 insertions(+), 5 deletions(-) diff --git a/R/model.R b/R/model.R index be4f727f4..71b472122 100644 --- a/R/model.R +++ b/R/model.R @@ -490,6 +490,7 @@ compile_method <- function(quiet = TRUE, stderr_line_callback = function(x,p) { if (!startsWith(x, paste0(make_cmd(), ": *** No rule to make target"))) message(x) }, + echo_cmd = TRUE, error_on_status = FALSE ) if (run_log$status != 0) { @@ -915,6 +916,105 @@ sample_method <- function(data = NULL, CmdStanModel$set("public", name = "sample", value = sample_method) +mpi_sample_method <- function(data = NULL, + nprocess = 1, + mpicmd = "mpiexec", + seed = NULL, + refresh = NULL, + init = NULL, + save_latent_dynamics = FALSE, + output_dir = NULL, + chains = 4, + parallel_chains = getOption("mc.cores", 1), + chain_ids = seq_len(chains), + threads_per_chain = NULL, + iter_warmup = NULL, + iter_sampling = NULL, + save_warmup = FALSE, + thin = NULL, + max_treedepth = NULL, + adapt_engaged = TRUE, + adapt_delta = NULL, + step_size = NULL, + metric = NULL, + metric_file = NULL, + inv_metric = NULL, + init_buffer = NULL, + term_buffer = NULL, + window = NULL, + fixed_param = FALSE, + sig_figs = NULL, + validate_csv = TRUE, + show_messages = TRUE) { + + if (fixed_param) { + chains <- 1 + parallel_chains <- 1 + save_warmup <- FALSE + } + + checkmate::assert_integerish(chains, lower = 1, len = 1) + checkmate::assert_integerish(parallel_chains, lower = 1, null.ok = TRUE) + checkmate::assert_integerish(threads_per_chain, lower = 1, len = 1, null.ok = TRUE) + checkmate::assert_integerish(chain_ids, lower = 1, len = chains, unique = TRUE, null.ok = FALSE) + if (is.null(self$cpp_options()[["stan_threads"]])) { + if (!is.null(threads_per_chain)) { + warning("'threads_per_chain' is set but the model was not compiled with ", + "'cpp_options = list(stan_threads = TRUE)' so 'threads_per_chain' will have no effect!", + call. = FALSE) + threads_per_chain <- NULL + } + } else { + if (is.null(threads_per_chain)) { + stop("The model was compiled with 'cpp_options = list(stan_threads = TRUE)' ", + "but 'threads_per_chain' was not set!", + call. = FALSE) + } + } + sample_args <- SampleArgs$new( + iter_warmup = iter_warmup, + iter_sampling = iter_sampling, + save_warmup = save_warmup, + thin = thin, + max_treedepth = max_treedepth, + adapt_engaged = adapt_engaged, + adapt_delta = adapt_delta, + step_size = step_size, + metric = metric, + metric_file = metric_file, + inv_metric = inv_metric, + init_buffer = init_buffer, + term_buffer = term_buffer, + window = window, + fixed_param = fixed_param + ) + cmdstan_args <- CmdStanArgs$new( + method_args = sample_args, + model_name = strip_ext(basename(self$exe_file())), + exe_file = self$exe_file(), + proc_ids = chain_ids, + data_file = process_data(data), + save_latent_dynamics = save_latent_dynamics, + seed = seed, + init = init, + refresh = refresh, + output_dir = output_dir, + validate_csv = validate_csv, + sig_figs = sig_figs + ) + cmdstan_args$nprocess <- nprocess + cmdstan_procs <- CmdStanMCMCProcs$new( + num_procs = chains, + parallel_procs = parallel_chains, + threads_per_proc = threads_per_chain, + show_stderr_messages = show_messages + ) + runset <- CmdStanRun$new(args = cmdstan_args, procs = cmdstan_procs) + runset$run_cmdstan_mpi(nprocess, mpicmd) + CmdStanMCMC$new(runset) +} +CmdStanModel$set("public", name = "mpi_sample", value = mpi_sample_method) + #' Run Stan's optimization algorithms #' #' @name model-method-optimize diff --git a/R/run.R b/R/run.R index 60feaca45..500696fd5 100644 --- a/R/run.R +++ b/R/run.R @@ -20,7 +20,8 @@ CmdStanRun <- R6::R6Class( } invisible(self) }, - + mpi = function() self$args$mpi, + nprocess = function() self$args$nprocess, num_procs = function() self$procs$num_procs(), proc_ids = function() self$procs$proc_ids(), exe_file = function() self$args$exe_file, @@ -150,6 +151,10 @@ CmdStanRun <- R6::R6Class( } }, + run_cmdstan_mpi = function(nprocess, mpicmd) { + private$run_sample_(nprocess, mpicmd) + }, + # run bin/stansummary or bin/diagnose # @param tool The name of the tool in `bin/` to run. # @param flags An optional character vector of flags (e.g. c("--sig_figs=1")). @@ -222,7 +227,7 @@ CmdStanRun <- R6::R6Class( # run helpers ------------------------------------------------- -.run_sample <- function() { +.run_sample <- function(nprocess = NULL, mpicmd = NULL) { procs <- self$procs on.exit(procs$cleanup(), add = TRUE) @@ -261,7 +266,10 @@ CmdStanRun <- R6::R6Class( id = chain_id, command = self$command(), args = self$command_args()[[chain_id]], - wd = dirname(self$exe_file()) + wd = dirname(self$exe_file()), + mpi_nprocess = nprocess, + mpicmd = mpicmd, + name = self$exe_file() ) procs$mark_proc_start(chain_id) procs$set_active_procs(procs$active_procs() + 1) @@ -475,12 +483,16 @@ CmdStanProcs <- R6::R6Class( get_proc = function(id) { private$processes_[[id]] }, - new_proc = function(id, command, args, wd) { + new_proc = function(id, command, args, wd, name = NULL, mpi_nprocess = NULL, mpicmd = "mpiexec") { + if (!is.null(mpi_nprocess)) { + args = c("-n", mpi_nprocess, name, args) + command <- mpicmd + } private$processes_[[id]] <- processx::process$new( command = command, args = args, wd = wd, - echo_cmd = FALSE, + echo_cmd = TRUE, stdout = "|", stderr = "|" ) From 00d2ddca0b9f74266321dd96f1edd260a4b23634 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Wed, 18 Nov 2020 20:47:58 +0100 Subject: [PATCH 02/21] mpi_args is a list now --- R/model.R | 7 +++---- R/run.R | 10 +++++----- 2 files changed, 8 insertions(+), 9 deletions(-) diff --git a/R/model.R b/R/model.R index 71b472122..30dd87324 100644 --- a/R/model.R +++ b/R/model.R @@ -917,8 +917,8 @@ CmdStanModel$set("public", name = "sample", value = sample_method) mpi_sample_method <- function(data = NULL, - nprocess = 1, - mpicmd = "mpiexec", + mpi_cmd = "mpiexec", + mpi_args = NULL, seed = NULL, refresh = NULL, init = NULL, @@ -1002,7 +1002,6 @@ mpi_sample_method <- function(data = NULL, validate_csv = validate_csv, sig_figs = sig_figs ) - cmdstan_args$nprocess <- nprocess cmdstan_procs <- CmdStanMCMCProcs$new( num_procs = chains, parallel_procs = parallel_chains, @@ -1010,7 +1009,7 @@ mpi_sample_method <- function(data = NULL, show_stderr_messages = show_messages ) runset <- CmdStanRun$new(args = cmdstan_args, procs = cmdstan_procs) - runset$run_cmdstan_mpi(nprocess, mpicmd) + runset$run_cmdstan_mpi(mpi_cmd, mpi_args) CmdStanMCMC$new(runset) } CmdStanModel$set("public", name = "mpi_sample", value = mpi_sample_method) diff --git a/R/run.R b/R/run.R index 500696fd5..946b05731 100644 --- a/R/run.R +++ b/R/run.R @@ -151,8 +151,8 @@ CmdStanRun <- R6::R6Class( } }, - run_cmdstan_mpi = function(nprocess, mpicmd) { - private$run_sample_(nprocess, mpicmd) + run_cmdstan_mpi = function(mpi_cmd, mpi_args) { + private$run_sample_(mpi_cmd, mpi_args) }, # run bin/stansummary or bin/diagnose @@ -227,7 +227,7 @@ CmdStanRun <- R6::R6Class( # run helpers ------------------------------------------------- -.run_sample <- function(nprocess = NULL, mpicmd = NULL) { +.run_sample <- function(mpi_cmd = NULL, mpi_args = NULL) { procs <- self$procs on.exit(procs$cleanup(), add = TRUE) @@ -267,8 +267,8 @@ CmdStanRun <- R6::R6Class( command = self$command(), args = self$command_args()[[chain_id]], wd = dirname(self$exe_file()), - mpi_nprocess = nprocess, - mpicmd = mpicmd, + mpi_cmd = mpi_cmd, + mpi_args = mpi_args, name = self$exe_file() ) procs$mark_proc_start(chain_id) From e2df1658f2f416195d38380be334a0622e52e566 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Wed, 18 Nov 2020 21:33:04 +0100 Subject: [PATCH 03/21] convert list to args vector --- R/run.R | 25 +++++++++++++++++-------- 1 file changed, 17 insertions(+), 8 deletions(-) diff --git a/R/run.R b/R/run.R index 946b05731..3dd425b17 100644 --- a/R/run.R +++ b/R/run.R @@ -230,7 +230,12 @@ CmdStanRun <- R6::R6Class( .run_sample <- function(mpi_cmd = NULL, mpi_args = NULL) { procs <- self$procs on.exit(procs$cleanup(), add = TRUE) - + if (!is.null(mpi_cmd)) { + if (is.null(mpi_args)) { + mpi_args = list() + } + mpi_args[["exe"]] <- self$exe_file() + } # add path to the TBB library to the PATH variable if (cmdstan_version() >= "2.21" && os_is_windows()) { path_to_TBB <- file.path(cmdstan_path(), "stan", "lib", "stan_math", "lib", "tbb") @@ -268,8 +273,7 @@ CmdStanRun <- R6::R6Class( args = self$command_args()[[chain_id]], wd = dirname(self$exe_file()), mpi_cmd = mpi_cmd, - mpi_args = mpi_args, - name = self$exe_file() + mpi_args = mpi_args ) procs$mark_proc_start(chain_id) procs$set_active_procs(procs$active_procs() + 1) @@ -483,16 +487,21 @@ CmdStanProcs <- R6::R6Class( get_proc = function(id) { private$processes_[[id]] }, - new_proc = function(id, command, args, wd, name = NULL, mpi_nprocess = NULL, mpicmd = "mpiexec") { - if (!is.null(mpi_nprocess)) { - args = c("-n", mpi_nprocess, name, args) - command <- mpicmd + new_proc = function(id, command, args, wd, mpi_cmd = NULL, mpi_args = NULL) { + if (!is.null(mpi_cmd)) { + exe_name <- mpi_args[["exe"]] + mpi_args[["exe"]] <- NULL + mpi_args_vector <- c() + for (i in names(mpi_args)) { + mpi_args_vector <- c(paste0("-", i), mpi_args[[i]], mpi_args_vector) + } + args = c(mpi_args_vector, exe_name, args) + command <- mpi_cmd } private$processes_[[id]] <- processx::process$new( command = command, args = args, wd = wd, - echo_cmd = TRUE, stdout = "|", stderr = "|" ) From 393efacf63eb576153459fc0c509a7990f057378 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Wed, 18 Nov 2020 21:33:39 +0100 Subject: [PATCH 04/21] remove echoing cmd --- R/model.R | 1 - 1 file changed, 1 deletion(-) diff --git a/R/model.R b/R/model.R index 30dd87324..8082f0edc 100644 --- a/R/model.R +++ b/R/model.R @@ -490,7 +490,6 @@ compile_method <- function(quiet = TRUE, stderr_line_callback = function(x,p) { if (!startsWith(x, paste0(make_cmd(), ": *** No rule to make target"))) message(x) }, - echo_cmd = TRUE, error_on_status = FALSE ) if (run_log$status != 0) { From 75c6dc7b7299b78e2ba1f937f93bbf365fb40cdb Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Thu, 19 Nov 2020 11:19:13 +0100 Subject: [PATCH 05/21] added basic docs --- R/model.R | 112 +++++++++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 95 insertions(+), 17 deletions(-) diff --git a/R/model.R b/R/model.R index 8082f0edc..fec05653c 100644 --- a/R/model.R +++ b/R/model.R @@ -914,7 +914,100 @@ sample_method <- function(data = NULL, } CmdStanModel$set("public", name = "sample", value = sample_method) - +#' Run Stan's MCMC algorithms with MPI +#' +#' @name model-method-mpi-sample +#' @aliases mpi_sample +#' @family CmdStanModel methods +#' +#' @description The `$mpi_sample()` method of a [`CmdStanModel`] object runs the +#' default MCMC algorithm in CmdStan (`algorithm=hmc engine=nuts`) with MPI +#' (STAN_MPI makefile flag), to produce a set of draws from the posterior +#' distribution of a model conditioned on some data. +#' +#' In order to use MPI with Stan, an MPI implementation must be installed. +#' For Unix systems the most commonly used implementations are MPICH and OpenMPI. +#' The implementations provide an MPI C++ compiler wrapper (for example mpicxx), +#' which is required to compile the model. +#' +#' An example of compiling with STAN_MPI: +#' ``` +#' cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +#' mod <- cmdstan_model("model.stan", cpp_options = cpp_options) +#' ``` +#' The C++ options that need supplied to the compile call are: +#' - `STAN_MPI`: Enables the use of MPI with Stan +#' - `CXX`: The name of the MPI C++ compiler wrapper (typicall mpicxx) +#' - `TBB_CXX_TYPE`: The C++ compiler the MPI wrapper wraps. Typically gcc on +#' Linux and clang on macOS. +#' +#' In the call to the `$mpi_sample()` method, we can additionally provide +#' the name of the MPI launcher (`mpi_cmd`), which defaults to "mpiexec", +#' and any other MPI launch arguments. In most cases, it is enough to +#' only define the number of processes with `mpi_args = list("n" = 4)`. +#' +#' An example of a call of `$mpi_sample()`: +#' ``` +#' cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +#' fit <- mod$mpi_sample(data_list, mpi_args = c("-n", 4)) +#' ``` +#' +#' @section Usage: +#' ``` +#' $mpi_sample( +#' data = NULL, +#' mpi_cmd = "mpiexec", +#' mpi_args = NULL, +#' seed = NULL, +#' refresh = NULL, +#' init = NULL, +#' save_latent_dynamics = FALSE, +#' output_dir = NULL, +#' chains = 4, +#' parallel_chains = getOption("mc.cores", 1), +#' chain_ids = seq_len(chains), +#' iter_warmup = NULL, +#' iter_sampling = NULL, +#' save_warmup = FALSE, +#' thin = NULL, +#' max_treedepth = NULL, +#' adapt_engaged = TRUE, +#' adapt_delta = NULL, +#' step_size = NULL, +#' metric = NULL, +#' metric_file = NULL, +#' inv_metric = NULL, +#' init_buffer = NULL, +#' term_buffer = NULL, +#' window = NULL, +#' fixed_param = FALSE, +#' sig_figs = NULL, +#' validate_csv = TRUE, +#' show_messages = TRUE +#' ) +#' ``` +#' +#' @section Arguments: +#' * `mpi_cmd`: (character vector) The MPI launcher used for launching MPI processes. +#' The default launcher is `mpiexec`. +#' * `mpi_args`: (list) A list of arguments to use when launching MPI processes. +#' For example, mpi_args = list("n" = 4) launches the executable as +#' `mpiexec -n 4 model_executable`, followed by CmdStan arguments +#' for the model executable. +#' * `data`, `seed`, `refresh`, `init`, `save_latent_dynamics`, `output_dir`, +#' `chains`, `parallel_chains`, `chain_ids`, `iter_warmup`, `iter_sampling`, +#' `save_warmup`, `thin`, `max_treedepth`, `adapt_engaged`, `adapt_delta`, +#' `step_size`, `metric`, `metric_file`, `inv_metric`, `init_buffer`, +#' `term_buffer`, `window`, `fixed_param`, `sig_figs`, `validate_csv`, +#' `show_messages`: +#' Same as for the [`$sample()`][model-method-sample] method. +#' +#' @section Value: The `$mpi_sample()` method returns a [`CmdStanMCMC`] object. +#' +#' @template seealso-docs +#' @inherit cmdstan_model examples +#' +NULL mpi_sample_method <- function(data = NULL, mpi_cmd = "mpiexec", mpi_args = NULL, @@ -923,10 +1016,9 @@ mpi_sample_method <- function(data = NULL, init = NULL, save_latent_dynamics = FALSE, output_dir = NULL, - chains = 4, + chains = 1, parallel_chains = getOption("mc.cores", 1), chain_ids = seq_len(chains), - threads_per_chain = NULL, iter_warmup = NULL, iter_sampling = NULL, save_warmup = FALSE, @@ -956,20 +1048,6 @@ mpi_sample_method <- function(data = NULL, checkmate::assert_integerish(parallel_chains, lower = 1, null.ok = TRUE) checkmate::assert_integerish(threads_per_chain, lower = 1, len = 1, null.ok = TRUE) checkmate::assert_integerish(chain_ids, lower = 1, len = chains, unique = TRUE, null.ok = FALSE) - if (is.null(self$cpp_options()[["stan_threads"]])) { - if (!is.null(threads_per_chain)) { - warning("'threads_per_chain' is set but the model was not compiled with ", - "'cpp_options = list(stan_threads = TRUE)' so 'threads_per_chain' will have no effect!", - call. = FALSE) - threads_per_chain <- NULL - } - } else { - if (is.null(threads_per_chain)) { - stop("The model was compiled with 'cpp_options = list(stan_threads = TRUE)' ", - "but 'threads_per_chain' was not set!", - call. = FALSE) - } - } sample_args <- SampleArgs$new( iter_warmup = iter_warmup, iter_sampling = iter_sampling, From c1e82075a887f8198ca0efd08e8af981d3e6a411 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 17:48:26 +0100 Subject: [PATCH 06/21] add tests --- .github/workflows/R-CMD-check.yaml | 6 +++++ .github/workflows/Test-coverage.yaml | 6 ++++- R/model.R | 2 -- tests/testthat/test-mpi.R | 38 ++++++++++++++++++++++++++++ 4 files changed, 49 insertions(+), 3 deletions(-) create mode 100644 tests/testthat/test-mpi.R diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index de156a92c..55b05ea2d 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -53,6 +53,12 @@ jobs: mingw32-make --version Get-Command mingw32-make | Select-Object -ExpandProperty Definition shell: powershell + + - name: Install MPI + if: runner.os == 'Linux' + run: | + sudo apt-get install -y mpi + echo "CMDSTANR_RUN_MPI_TESTS=TRUE" >> $GITHUB_ENV - uses: r-lib/actions/setup-r@master with: diff --git a/.github/workflows/Test-coverage.yaml b/.github/workflows/Test-coverage.yaml index d1a259eed..f552eb6ea 100644 --- a/.github/workflows/Test-coverage.yaml +++ b/.github/workflows/Test-coverage.yaml @@ -27,7 +27,11 @@ jobs: - uses: r-lib/actions/setup-pandoc@master - name: Install Ubuntu dependencies - run: sudo apt-get install libcurl4-openssl-dev + run: | + sudo apt-get install libcurl4-openssl-dev + sudo apt-get install -y mpi + echo "CMDSTANR_RUN_MPI_TESTS=TRUE" >> $GITHUB_ENV + - name: Query dependencies run: | install.packages('remotes') diff --git a/R/model.R b/R/model.R index fec05653c..0d46ca6c0 100644 --- a/R/model.R +++ b/R/model.R @@ -1046,7 +1046,6 @@ mpi_sample_method <- function(data = NULL, checkmate::assert_integerish(chains, lower = 1, len = 1) checkmate::assert_integerish(parallel_chains, lower = 1, null.ok = TRUE) - checkmate::assert_integerish(threads_per_chain, lower = 1, len = 1, null.ok = TRUE) checkmate::assert_integerish(chain_ids, lower = 1, len = chains, unique = TRUE, null.ok = FALSE) sample_args <- SampleArgs$new( iter_warmup = iter_warmup, @@ -1082,7 +1081,6 @@ mpi_sample_method <- function(data = NULL, cmdstan_procs <- CmdStanMCMCProcs$new( num_procs = chains, parallel_procs = parallel_chains, - threads_per_proc = threads_per_chain, show_stderr_messages = show_messages ) runset <- CmdStanRun$new(args = cmdstan_args, procs = cmdstan_procs) diff --git a/tests/testthat/test-mpi.R b/tests/testthat/test-mpi.R new file mode 100644 index 000000000..6c44c7fb6 --- /dev/null +++ b/tests/testthat/test-mpi.R @@ -0,0 +1,38 @@ +context("mpi") + +test_that("mpi_sample() works", { + skip_on_cran() + skip_if(!nzchar(Sys.getenv("CMDSTANR_RUN_MPI_TESTS"))) + mpi_file <- write_stan_file(" + functions { + vector test(vector beta, vector theta, real[] x, int[] y) { + return theta; + } + } + transformed data { + vector[4] a; + vector[5] b[4] = {[1,1,1,1,1]', [2,2,2,2,2]', [3,3,3,3,3]', [4,4,4,4,4]'}; + real x[4,4]; + int y[4,4]; + } + parameters { + real beta; + } + model { + beta ~ std_normal(); + } + generated quantities { + vector[20] c = map_rect(test, a, b, x, y); + } + ") + cpp_options = list(cxx="mpicxx", stan_mpi = TRUE, tbb_cxx_type="gcc") + mod_mpi <- cmdstan_model(mpi_file, cpp_options = cpp_options) + utils::capture.output( + f <- mod_mpi$mpi_sample(chains = 1, mpi_args = list("n" = 4)) + ) + expect_equal(f$metadata()$mpi_enable, 1) + expect_equal( + as.numeric(posterior::subset_draws(f$draws("c"), iteration = 1)), + c(1,1,1,1,1,2,2,2,2,2,3,3,3,3,3,4,4,4,4,4) + ) +}) From 8175c5a554166ffb6996339ff0941e880bd2c923 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 18:12:56 +0100 Subject: [PATCH 07/21] use openmpi on GA --- .github/workflows/R-CMD-check.yaml | 2 +- .github/workflows/Test-coverage.yaml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index 55b05ea2d..4227ce931 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -57,7 +57,7 @@ jobs: - name: Install MPI if: runner.os == 'Linux' run: | - sudo apt-get install -y mpi + sudo apt-get install -y openmpi-bin echo "CMDSTANR_RUN_MPI_TESTS=TRUE" >> $GITHUB_ENV - uses: r-lib/actions/setup-r@master diff --git a/.github/workflows/Test-coverage.yaml b/.github/workflows/Test-coverage.yaml index f552eb6ea..c41952bfa 100644 --- a/.github/workflows/Test-coverage.yaml +++ b/.github/workflows/Test-coverage.yaml @@ -29,7 +29,7 @@ jobs: - name: Install Ubuntu dependencies run: | sudo apt-get install libcurl4-openssl-dev - sudo apt-get install -y mpi + sudo apt-get install -y openmpi-bin echo "CMDSTANR_RUN_MPI_TESTS=TRUE" >> $GITHUB_ENV - name: Query dependencies From 8a35242f1ff790f954d43e2b68936289307273d7 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 18:34:34 +0100 Subject: [PATCH 08/21] cleanup --- R/run.R | 2 -- 1 file changed, 2 deletions(-) diff --git a/R/run.R b/R/run.R index 3dd425b17..600561c9a 100644 --- a/R/run.R +++ b/R/run.R @@ -20,8 +20,6 @@ CmdStanRun <- R6::R6Class( } invisible(self) }, - mpi = function() self$args$mpi, - nprocess = function() self$args$nprocess, num_procs = function() self$procs$num_procs(), proc_ids = function() self$procs$proc_ids(), exe_file = function() self$args$exe_file, From 1a6d40d8dbffea8d059762839df35cddc72b2d3b Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 18:40:03 +0100 Subject: [PATCH 09/21] set n=1 for test --- tests/testthat/test-mpi.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-mpi.R b/tests/testthat/test-mpi.R index 6c44c7fb6..339e96084 100644 --- a/tests/testthat/test-mpi.R +++ b/tests/testthat/test-mpi.R @@ -28,7 +28,7 @@ test_that("mpi_sample() works", { cpp_options = list(cxx="mpicxx", stan_mpi = TRUE, tbb_cxx_type="gcc") mod_mpi <- cmdstan_model(mpi_file, cpp_options = cpp_options) utils::capture.output( - f <- mod_mpi$mpi_sample(chains = 1, mpi_args = list("n" = 4)) + f <- mod_mpi$mpi_sample(chains = 1, mpi_args = list("n" = 1)) ) expect_equal(f$metadata()$mpi_enable, 1) expect_equal( From 6bd2b4e729697c660ebf32bba90e0cb04a1b27fe Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 19:13:26 +0100 Subject: [PATCH 10/21] add .Rd --- man/model-method-check_syntax.Rd | 1 + man/model-method-compile.Rd | 1 + man/model-method-generate-quantities.Rd | 1 + man/model-method-mpi-sample.Rd | 229 ++++++++++++++++++++++++ man/model-method-optimize.Rd | 1 + man/model-method-sample.Rd | 1 + man/model-method-variational.Rd | 1 + 7 files changed, 235 insertions(+) create mode 100644 man/model-method-mpi-sample.Rd diff --git a/man/model-method-check_syntax.Rd b/man/model-method-check_syntax.Rd index a216df948..5f5743d0e 100644 --- a/man/model-method-check_syntax.Rd +++ b/man/model-method-check_syntax.Rd @@ -62,6 +62,7 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} diff --git a/man/model-method-compile.Rd b/man/model-method-compile.Rd index 4fc9e14f7..f997aaea6 100644 --- a/man/model-method-compile.Rd +++ b/man/model-method-compile.Rd @@ -113,6 +113,7 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-generate-quantities}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} diff --git a/man/model-method-generate-quantities.Rd b/man/model-method-generate-quantities.Rd index a158e046f..e8271dadd 100644 --- a/man/model-method-generate-quantities.Rd +++ b/man/model-method-generate-quantities.Rd @@ -98,6 +98,7 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} diff --git a/man/model-method-mpi-sample.Rd b/man/model-method-mpi-sample.Rd new file mode 100644 index 000000000..778d5115b --- /dev/null +++ b/man/model-method-mpi-sample.Rd @@ -0,0 +1,229 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/model.R +\name{model-method-mpi-sample} +\alias{model-method-mpi-sample} +\alias{mpi_sample} +\title{Run Stan's MCMC algorithms with MPI} +\description{ +The \verb{$mpi_sample()} method of a \code{\link{CmdStanModel}} object runs the +default MCMC algorithm in CmdStan (\verb{algorithm=hmc engine=nuts}) with MPI +(STAN_MPI makefile flag), to produce a set of draws from the posterior +distribution of a model conditioned on some data. + +In order to use MPI with Stan, an MPI implementation must be installed. +For Unix systems the most commonly used implementations are MPICH and OpenMPI. +The implementations provide an MPI C++ compiler wrapper (for example mpicxx), +which is required to compile the model. + +An example of compiling with STAN_MPI:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +mod <- cmdstan_model("model.stan", cpp_options = cpp_options) +} + +The C++ options that need supplied to the compile call are: +\itemize{ +\item \code{STAN_MPI}: Enables the use of MPI with Stan +\item \code{CXX}: The name of the MPI C++ compiler wrapper (typicall mpicxx) +\item \code{TBB_CXX_TYPE}: The C++ compiler the MPI wrapper wraps. Typically gcc on +Linux and clang on macOS. +} + +In the call to the \verb{$mpi_sample()} method, we can additionally provide +the name of the MPI launcher (\code{mpi_cmd}), which defaults to "mpiexec", +and any other MPI launch arguments. In most cases, it is enough to +only define the number of processes with \code{mpi_args = list("n" = 4)}. + +An example of a call of \verb{$mpi_sample()}:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +fit <- mod$mpi_sample(data_list, mpi_args = c("-n", 4)) +} +} +\section{Usage}{ +\preformatted{$mpi_sample( + data = NULL, + mpi_cmd = "mpiexec", + mpi_args = NULL, + seed = NULL, + refresh = NULL, + init = NULL, + save_latent_dynamics = FALSE, + output_dir = NULL, + chains = 4, + parallel_chains = getOption("mc.cores", 1), + chain_ids = seq_len(chains), + iter_warmup = NULL, + iter_sampling = NULL, + save_warmup = FALSE, + thin = NULL, + max_treedepth = NULL, + adapt_engaged = TRUE, + adapt_delta = NULL, + step_size = NULL, + metric = NULL, + metric_file = NULL, + inv_metric = NULL, + init_buffer = NULL, + term_buffer = NULL, + window = NULL, + fixed_param = FALSE, + sig_figs = NULL, + validate_csv = TRUE, + show_messages = TRUE +) +} +} + +\section{Arguments}{ + +\itemize{ +\item \code{mpi_cmd}: (character vector) The MPI launcher used for launching MPI processes. +The default launcher is \code{mpiexec}. +\item \code{mpi_args}: (list) A list of arguments to use when launching MPI processes. +For example, mpi_args = list("n" = 4) launches the executable as +\verb{mpiexec -n 4 model_executable}, followed by CmdStan arguments +for the model executable. +\item \code{data}, \code{seed}, \code{refresh}, \code{init}, \code{save_latent_dynamics}, \code{output_dir}, +\code{chains}, \code{parallel_chains}, \code{chain_ids}, \code{iter_warmup}, \code{iter_sampling}, +\code{save_warmup}, \code{thin}, \code{max_treedepth}, \code{adapt_engaged}, \code{adapt_delta}, +\code{step_size}, \code{metric}, \code{metric_file}, \code{inv_metric}, \code{init_buffer}, +\code{term_buffer}, \code{window}, \code{fixed_param}, \code{sig_figs}, \code{validate_csv}, +\code{show_messages}: +Same as for the \code{\link[=model-method-sample]{$sample()}} method. +} +} + +\section{Value}{ + The \verb{$mpi_sample()} method returns a \code{\link{CmdStanMCMC}} object. +} + +\examples{ +\dontrun{ +library(cmdstanr) +library(posterior) +library(bayesplot) +color_scheme_set("brightblue") + +# Set path to cmdstan +# (Note: if you installed CmdStan via install_cmdstan() with default settings +# then setting the path is unnecessary but the default below should still work. +# Otherwise use the `path` argument to specify the location of your +# CmdStan installation.) +set_cmdstan_path(path = NULL) + +# Create a CmdStanModel object from a Stan program, +# here using the example model that comes with CmdStan +file <- file.path(cmdstan_path(), "examples/bernoulli/bernoulli.stan") +mod <- cmdstan_model(file) +mod$print() + +# Data as a named list (like RStan) +stan_data <- list(N = 10, y = c(0,1,0,0,0,0,0,0,0,1)) + +# Run MCMC using the 'sample' method +fit_mcmc <- mod$sample( + data = stan_data, + seed = 123, + chains = 2, + parallel_chains = 2 +) + +# Use 'posterior' package for summaries +fit_mcmc$summary() + +# Get posterior draws +draws <- fit_mcmc$draws() +print(draws) + +# Convert to data frame using posterior::as_draws_df +as_draws_df(draws) + +# Plot posterior using bayesplot (ggplot2) +mcmc_hist(fit_mcmc$draws("theta")) + +# Call CmdStan's diagnose and stansummary utilities +fit_mcmc$cmdstan_diagnose() +fit_mcmc$cmdstan_summary() + +# For models fit using MCMC, if you like working with RStan's stanfit objects +# then you can create one with rstan::read_stan_csv() + +# stanfit <- rstan::read_stan_csv(fit_mcmc$output_files()) + + +# Run 'optimize' method to get a point estimate (default is Stan's LBFGS algorithm) +# and also demonstrate specifying data as a path to a file instead of a list +my_data_file <- file.path(cmdstan_path(), "examples/bernoulli/bernoulli.data.json") +fit_optim <- mod$optimize(data = my_data_file, seed = 123) + +fit_optim$summary() + + +# Run 'variational' method to approximate the posterior (default is meanfield ADVI) +fit_vb <- mod$variational(data = stan_data, seed = 123) + +fit_vb$summary() + +# Plot approximate posterior using bayesplot +mcmc_hist(fit_vb$draws("theta")) + + +# Specifying initial values as a function +fit_mcmc_w_init_fun <- mod$sample( + data = stan_data, + seed = 123, + chains = 2, + refresh = 0, + init = function() list(theta = runif(1)) +) +fit_mcmc_w_init_fun_2 <- mod$sample( + data = stan_data, + seed = 123, + chains = 2, + refresh = 0, + init = function(chain_id) { + # silly but demonstrates optional use of chain_id + list(theta = 1 / (chain_id + 1)) + } +) +fit_mcmc_w_init_fun_2$init() + +# Specifying initial values as a list of lists +fit_mcmc_w_init_list <- mod$sample( + data = stan_data, + seed = 123, + chains = 2, + refresh = 0, + init = list( + list(theta = 0.75), # chain 1 + list(theta = 0.25) # chain 2 + ) +) +fit_optim_w_init_list <- mod$optimize( + data = stan_data, + seed = 123, + init = list( + list(theta = 0.75) + ) +) +fit_optim_w_init_list$init() +} + +} +\seealso{ +The CmdStanR website +(\href{https://mc-stan.org/cmdstanr/}{mc-stan.org/cmdstanr}) for online +documentation and tutorials. + +The Stan and CmdStan documentation: +\itemize{ +\item Stan documentation: \href{https://mc-stan.org/users/documentation/}{mc-stan.org/users/documentation} +\item CmdStan User’s Guide: \href{https://mc-stan.org/docs/cmdstan-guide/}{mc-stan.org/docs/cmdstan-guide} +} + +Other CmdStanModel methods: +\code{\link{model-method-check_syntax}}, +\code{\link{model-method-compile}}, +\code{\link{model-method-generate-quantities}}, +\code{\link{model-method-optimize}}, +\code{\link{model-method-sample}}, +\code{\link{model-method-variational}} +} +\concept{CmdStanModel methods} diff --git a/man/model-method-optimize.Rd b/man/model-method-optimize.Rd index 76b84edef..745526e33 100644 --- a/man/model-method-optimize.Rd +++ b/man/model-method-optimize.Rd @@ -250,6 +250,7 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-sample.Rd b/man/model-method-sample.Rd index 48f636c9a..792b18174 100644 --- a/man/model-method-sample.Rd +++ b/man/model-method-sample.Rd @@ -345,6 +345,7 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-variational.Rd b/man/model-method-variational.Rd index e3ad66b84..a8aa9c79a 100644 --- a/man/model-method-variational.Rd +++ b/man/model-method-variational.Rd @@ -267,6 +267,7 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, +\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, \code{\link{model-method-sample}} } From 918b66c153117584e7e70e0e69c0895944a34e64 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Fri, 20 Nov 2020 19:23:39 +0100 Subject: [PATCH 11/21] skip mpi in codecov --- tests/testthat/test-mpi.R | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/testthat/test-mpi.R b/tests/testthat/test-mpi.R index 339e96084..93fc153d6 100644 --- a/tests/testthat/test-mpi.R +++ b/tests/testthat/test-mpi.R @@ -2,6 +2,7 @@ context("mpi") test_that("mpi_sample() works", { skip_on_cran() + skip_on_covr() skip_if(!nzchar(Sys.getenv("CMDSTANR_RUN_MPI_TESTS"))) mpi_file <- write_stan_file(" functions { From e51d0777c7d405fd46b2b16f2988f77cdc8d6dad Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Wed, 25 Nov 2020 09:33:28 +0100 Subject: [PATCH 12/21] parallel_chains = 1 added NEWS.md --- NEWS.md | 8 ++++++++ R/model.R | 4 +--- 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/NEWS.md b/NEWS.md index 4f7eba285..c8a6b2340 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,11 @@ +# Items for next tagged release + +### Bug fixes + +### New features + +* Added `$mpi_sample()` for MCMC sampling with MPI. (#350) + # cmdstanr 0.2.1 ### Bug fixes diff --git a/R/model.R b/R/model.R index e4c2a30a7..5f3ca0960 100644 --- a/R/model.R +++ b/R/model.R @@ -1062,7 +1062,6 @@ mpi_sample_method <- function(data = NULL, save_latent_dynamics = FALSE, output_dir = NULL, chains = 1, - parallel_chains = getOption("mc.cores", 1), chain_ids = seq_len(chains), iter_warmup = NULL, iter_sampling = NULL, @@ -1082,10 +1081,9 @@ mpi_sample_method <- function(data = NULL, sig_figs = NULL, validate_csv = TRUE, show_messages = TRUE) { - + parallel_chains <- 1 if (fixed_param) { chains <- 1 - parallel_chains <- 1 save_warmup <- FALSE } From cf33b34a7ad1540ab0a145c2a058a767bca73a90 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Wed, 25 Nov 2020 10:16:38 +0100 Subject: [PATCH 13/21] change starting tests --- R/run.R | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) diff --git a/R/run.R b/R/run.R index 8af02573b..b00df6a52 100644 --- a/R/run.R +++ b/R/run.R @@ -247,7 +247,20 @@ CmdStanRun <- R6::R6Class( start_msg <- paste0("Running MCMC with ", procs$num_procs(), " parallel chains") } else { if (procs$parallel_procs() == 1) { - start_msg <- paste0("Running MCMC with ", procs$num_procs(), " sequential chains") + if (!is.null(mpi_cmd)) { + if (!is.null(mpi_args[["n"]])) { + mpi_n_process <- mpi_args[["n"]] + } else if (!is.null(mpi_args[["np"]])) { + mpi_n_process <- mpi_args[["np"]] + } + if (is.null(mpi_n_process)) { + start_msg <- paste0("Running MCMC with ", procs$num_procs(), " chains using MPI") + } else { + start_msg <- paste0("Running MCMC with ", procs$num_procs(), " chains using MPI with ", mpi_n_process, " processes") + } + } else { + start_msg <- paste0("Running MCMC with ", procs$num_procs(), " sequential chains") + } } else { start_msg <- paste0("Running MCMC with ", procs$num_procs(), " chains, at most ", procs$parallel_procs(), " in parallel") } From 3228380b7ea43d9415f649aa8a107f319ec3351b Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Sun, 29 Nov 2020 21:55:45 +0100 Subject: [PATCH 14/21] mpi_sample -> sample_mpi --- R/model.R | 18 +++++++++--------- man/model-method-mpi-sample.Rd | 14 +++++++------- tests/testthat/test-mpi.R | 4 ++-- 3 files changed, 18 insertions(+), 18 deletions(-) diff --git a/R/model.R b/R/model.R index 5f3ca0960..e2f161300 100644 --- a/R/model.R +++ b/R/model.R @@ -962,10 +962,10 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' Run Stan's MCMC algorithms with MPI #' #' @name model-method-mpi-sample -#' @aliases mpi_sample +#' @aliases sample_mpi #' @family CmdStanModel methods #' -#' @description The `$mpi_sample()` method of a [`CmdStanModel`] object runs the +#' @description The `$sample_mpi()` method of a [`CmdStanModel`] object runs the #' default MCMC algorithm in CmdStan (`algorithm=hmc engine=nuts`) with MPI #' (STAN_MPI makefile flag), to produce a set of draws from the posterior #' distribution of a model conditioned on some data. @@ -986,20 +986,20 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' - `TBB_CXX_TYPE`: The C++ compiler the MPI wrapper wraps. Typically gcc on #' Linux and clang on macOS. #' -#' In the call to the `$mpi_sample()` method, we can additionally provide +#' In the call to the `$sample_mpi()` method, we can additionally provide #' the name of the MPI launcher (`mpi_cmd`), which defaults to "mpiexec", #' and any other MPI launch arguments. In most cases, it is enough to #' only define the number of processes with `mpi_args = list("n" = 4)`. #' -#' An example of a call of `$mpi_sample()`: +#' An example of a call of `$sample_mpi()`: #' ``` #' cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -#' fit <- mod$mpi_sample(data_list, mpi_args = c("-n", 4)) +#' fit <- mod$sample_mpi(data_list, mpi_args = c("-n", 4)) #' ``` #' #' @section Usage: #' ``` -#' $mpi_sample( +#' $sample_mpi( #' data = NULL, #' mpi_cmd = "mpiexec", #' mpi_args = NULL, @@ -1047,13 +1047,13 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' `show_messages`: #' Same as for the [`$sample()`][model-method-sample] method. #' -#' @section Value: The `$mpi_sample()` method returns a [`CmdStanMCMC`] object. +#' @section Value: The `$sample_mpi()` method returns a [`CmdStanMCMC`] object. #' #' @template seealso-docs #' @inherit cmdstan_model examples #' NULL -mpi_sample_method <- function(data = NULL, +sample_mpi_method <- function(data = NULL, mpi_cmd = "mpiexec", mpi_args = NULL, seed = NULL, @@ -1130,7 +1130,7 @@ mpi_sample_method <- function(data = NULL, runset$run_cmdstan_mpi(mpi_cmd, mpi_args) CmdStanMCMC$new(runset) } -CmdStanModel$set("public", name = "mpi_sample", value = mpi_sample_method) +CmdStanModel$set("public", name = "sample_mpi", value = sample_mpi_method) #' Run Stan's optimization algorithms #' diff --git a/man/model-method-mpi-sample.Rd b/man/model-method-mpi-sample.Rd index 778d5115b..d42eb3d95 100644 --- a/man/model-method-mpi-sample.Rd +++ b/man/model-method-mpi-sample.Rd @@ -2,10 +2,10 @@ % Please edit documentation in R/model.R \name{model-method-mpi-sample} \alias{model-method-mpi-sample} -\alias{mpi_sample} +\alias{sample_mpi} \title{Run Stan's MCMC algorithms with MPI} \description{ -The \verb{$mpi_sample()} method of a \code{\link{CmdStanModel}} object runs the +The \verb{$sample_mpi()} method of a \code{\link{CmdStanModel}} object runs the default MCMC algorithm in CmdStan (\verb{algorithm=hmc engine=nuts}) with MPI (STAN_MPI makefile flag), to produce a set of draws from the posterior distribution of a model conditioned on some data. @@ -27,17 +27,17 @@ The C++ options that need supplied to the compile call are: Linux and clang on macOS. } -In the call to the \verb{$mpi_sample()} method, we can additionally provide +In the call to the \verb{$sample_mpi()} method, we can additionally provide the name of the MPI launcher (\code{mpi_cmd}), which defaults to "mpiexec", and any other MPI launch arguments. In most cases, it is enough to only define the number of processes with \code{mpi_args = list("n" = 4)}. -An example of a call of \verb{$mpi_sample()}:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -fit <- mod$mpi_sample(data_list, mpi_args = c("-n", 4)) +An example of a call of \verb{$sample_mpi()}:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +fit <- mod$sample_mpi(data_list, mpi_args = c("-n", 4)) } } \section{Usage}{ -\preformatted{$mpi_sample( +\preformatted{$sample_mpi( data = NULL, mpi_cmd = "mpiexec", mpi_args = NULL, @@ -91,7 +91,7 @@ Same as for the \code{\link[=model-method-sample]{$sample()}} method. } \section{Value}{ - The \verb{$mpi_sample()} method returns a \code{\link{CmdStanMCMC}} object. + The \verb{$sample_mpi()} method returns a \code{\link{CmdStanMCMC}} object. } \examples{ diff --git a/tests/testthat/test-mpi.R b/tests/testthat/test-mpi.R index 93fc153d6..688653108 100644 --- a/tests/testthat/test-mpi.R +++ b/tests/testthat/test-mpi.R @@ -1,6 +1,6 @@ context("mpi") -test_that("mpi_sample() works", { +test_that("sample_mpi() works", { skip_on_cran() skip_on_covr() skip_if(!nzchar(Sys.getenv("CMDSTANR_RUN_MPI_TESTS"))) @@ -29,7 +29,7 @@ test_that("mpi_sample() works", { cpp_options = list(cxx="mpicxx", stan_mpi = TRUE, tbb_cxx_type="gcc") mod_mpi <- cmdstan_model(mpi_file, cpp_options = cpp_options) utils::capture.output( - f <- mod_mpi$mpi_sample(chains = 1, mpi_args = list("n" = 1)) + f <- mod_mpi$sample_mpi(chains = 1, mpi_args = list("n" = 1)) ) expect_equal(f$metadata()$mpi_enable, 1) expect_equal( From 9121292cd2c96a071381022ab66bf0862f908dde Mon Sep 17 00:00:00 2001 From: jgabry Date: Tue, 1 Dec 2020 18:39:16 -0700 Subject: [PATCH 15/21] minor doc edits --- R/model.R | 170 ++++++++---------- man/CmdStanModel.Rd | 1 + man/model-method-check_syntax.Rd | 2 +- man/model-method-compile.Rd | 2 +- man/model-method-generate-quantities.Rd | 2 +- man/model-method-mpi-sample.Rd | 229 ------------------------ man/model-method-optimize.Rd | 2 +- man/model-method-sample.Rd | 2 +- man/model-method-sample_mpi.Rd | 98 ++++++++++ man/model-method-variational.Rd | 2 +- 10 files changed, 179 insertions(+), 331 deletions(-) delete mode 100644 man/model-method-mpi-sample.Rd create mode 100644 man/model-method-sample_mpi.Rd diff --git a/R/model.R b/R/model.R index 43e4c2dc1..237f0b500 100644 --- a/R/model.R +++ b/R/model.R @@ -172,6 +172,7 @@ cmdstan_model <- function(stan_file, compile = TRUE, ...) { #' |**Method**|**Description**| #' |:----------|:---------------| #' [`$sample()`][model-method-sample] | Run CmdStan's `"sample"` method, return [`CmdStanMCMC`] object. | +#' [`$sample_mpi()`][model-method-sample_mpi] | Run CmdStan's `"sample"` method with [MPI](https://mc-stan.org/math/mpi.html), return [`CmdStanMCMC`] object. | #' [`$optimize()`][model-method-optimize] | Run CmdStan's `"optimize"` method, return [`CmdStanMLE`] object. | #' [`$variational()`][model-method-variational] | Run CmdStan's `"variational"` method, return [`CmdStanVB`] object. | #' [`$generate_quantities()`][model-method-generate-quantities] | Run CmdStan's `"generate quantities"` method, return [`CmdStanGQ`] object. | @@ -961,126 +962,103 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' Run Stan's MCMC algorithms with MPI #' -#' @name model-method-mpi-sample +#' @name model-method-sample_mpi #' @aliases sample_mpi #' @family CmdStanModel methods #' -#' @description The `$sample_mpi()` method of a [`CmdStanModel`] object runs the -#' default MCMC algorithm in CmdStan (`algorithm=hmc engine=nuts`) with MPI -#' (STAN_MPI makefile flag), to produce a set of draws from the posterior -#' distribution of a model conditioned on some data. -#' -#' In order to use MPI with Stan, an MPI implementation must be installed. -#' For Unix systems the most commonly used implementations are MPICH and OpenMPI. -#' The implementations provide an MPI C++ compiler wrapper (for example mpicxx), -#' which is required to compile the model. -#' -#' An example of compiling with STAN_MPI: -#' ``` -#' cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -#' mod <- cmdstan_model("model.stan", cpp_options = cpp_options) -#' ``` -#' The C++ options that need supplied to the compile call are: -#' - `STAN_MPI`: Enables the use of MPI with Stan -#' - `CXX`: The name of the MPI C++ compiler wrapper (typicall mpicxx) -#' - `TBB_CXX_TYPE`: The C++ compiler the MPI wrapper wraps. Typically gcc on -#' Linux and clang on macOS. -#' -#' In the call to the `$sample_mpi()` method, we can additionally provide -#' the name of the MPI launcher (`mpi_cmd`), which defaults to "mpiexec", -#' and any other MPI launch arguments. In most cases, it is enough to -#' only define the number of processes with `mpi_args = list("n" = 4)`. -#' -#' An example of a call of `$sample_mpi()`: +#' @description The `$sample_mpi()` method of a [`CmdStanModel`] object is +#' identical to the `$sample()` method but with support for +#' [MPI](https://mc-stan.org/math/mpi.html). The target audience for MPI are +#' those with large computer clusters. For other users, the +#' [`$sample()`][model-method-sample] method provides both parallelization of +#' chains and threading support for within-chain parallelization. +#' +#' @details In order to use MPI with Stan, an MPI implementation must be +#' installed. For Unix systems the most commonly used implementations are +#' MPICH and OpenMPI. The implementations provide an MPI C++ compiler wrapper +#' (for example mpicxx), which is required to compile the model. +#' +#' An example of compiling with MPI: #' ``` -#' cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -#' fit <- mod$sample_mpi(data_list, mpi_args = c("-n", 4)) +#' mpi_options <- list(STAN_MPI=TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +#' mod <- cmdstan_model("model.stan", cpp_options = mpi_options) #' ``` +#' The C++ options that must be supplied to the +#' [compile][model-method-compile] call are: +#' - `STAN_MPI`: Enables the use of MPI with Stan if `TRUE`. +#' - `CXX`: The name of the MPI C++ compiler wrapper. Typically `"mpicxx"`. +#' - `TBB_CXX_TYPE`: The C++ compiler the MPI wrapper wraps. Typically `"gcc"` +#' on Linux and `"clang"` on macOS. +#' +#' In the call to the `$sample_mpi()` method we can also provide the name of +#' the MPI launcher (`mpi_cmd`, defaulting to `"mpiexec"`) and any other +#' MPI launch arguments. In most cases, it is enough to only define the number +#' of processes with `mpi_args = list("n" = 4)`. #' #' @section Usage: #' ``` #' $sample_mpi( -#' data = NULL, +#' ..., # same arguments as $sample() method #' mpi_cmd = "mpiexec", -#' mpi_args = NULL, -#' seed = NULL, -#' refresh = NULL, -#' init = NULL, -#' save_latent_dynamics = FALSE, -#' output_dir = NULL, -#' chains = 4, -#' parallel_chains = getOption("mc.cores", 1), -#' chain_ids = seq_len(chains), -#' iter_warmup = NULL, -#' iter_sampling = NULL, -#' save_warmup = FALSE, -#' thin = NULL, -#' max_treedepth = NULL, -#' adapt_engaged = TRUE, -#' adapt_delta = NULL, -#' step_size = NULL, -#' metric = NULL, -#' metric_file = NULL, -#' inv_metric = NULL, -#' init_buffer = NULL, -#' term_buffer = NULL, -#' window = NULL, -#' fixed_param = FALSE, -#' sig_figs = NULL, -#' validate_csv = TRUE, -#' show_messages = TRUE +#' mpi_args = NULL #' ) #' ``` #' -#' @section Arguments: +#' @section Arguments unique to the `sample_mpi` method: #' * `mpi_cmd`: (character vector) The MPI launcher used for launching MPI processes. -#' The default launcher is `mpiexec`. +#' The default launcher is `"mpiexec"`. #' * `mpi_args`: (list) A list of arguments to use when launching MPI processes. -#' For example, mpi_args = list("n" = 4) launches the executable as +#' For example, `mpi_args = list("n" = 4)` launches the executable as #' `mpiexec -n 4 model_executable`, followed by CmdStan arguments #' for the model executable. -#' * `data`, `seed`, `refresh`, `init`, `save_latent_dynamics`, `output_dir`, -#' `chains`, `parallel_chains`, `chain_ids`, `iter_warmup`, `iter_sampling`, -#' `save_warmup`, `thin`, `max_treedepth`, `adapt_engaged`, `adapt_delta`, -#' `step_size`, `metric`, `metric_file`, `inv_metric`, `init_buffer`, -#' `term_buffer`, `window`, `fixed_param`, `sig_figs`, `validate_csv`, -#' `show_messages`: -#' Same as for the [`$sample()`][model-method-sample] method. +#' +#' All other arguments are the same as for +#' [`$sample()`][model-method-sample]. #' #' @section Value: The `$sample_mpi()` method returns a [`CmdStanMCMC`] object. #' #' @template seealso-docs -#' @inherit cmdstan_model examples +#' @seealso The Stan Math Library's MPI documentation +#' ([mc-stan.org/math/mpi](https://mc-stan.org/math/mpi.html)) for more +#' details on MPI support in Stan. +#' +#' @examples +#' \dontrun{ +#' # mpi_options <- list(STAN_MPI=TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +#' # mod <- cmdstan_model("model.stan", cpp_options = mpi_options) +#' # fit <- mod$sample_mpi(..., mpi_args = list("n" = 4)) +#' } #' NULL + sample_mpi_method <- function(data = NULL, - mpi_cmd = "mpiexec", - mpi_args = NULL, - seed = NULL, - refresh = NULL, - init = NULL, - save_latent_dynamics = FALSE, - output_dir = NULL, - chains = 1, - chain_ids = seq_len(chains), - iter_warmup = NULL, - iter_sampling = NULL, - save_warmup = FALSE, - thin = NULL, - max_treedepth = NULL, - adapt_engaged = TRUE, - adapt_delta = NULL, - step_size = NULL, - metric = NULL, - metric_file = NULL, - inv_metric = NULL, - init_buffer = NULL, - term_buffer = NULL, - window = NULL, - fixed_param = FALSE, - sig_figs = NULL, - validate_csv = TRUE, - show_messages = TRUE) { + mpi_cmd = "mpiexec", + mpi_args = NULL, + seed = NULL, + refresh = NULL, + init = NULL, + save_latent_dynamics = FALSE, + output_dir = NULL, + chains = 1, + chain_ids = seq_len(chains), + iter_warmup = NULL, + iter_sampling = NULL, + save_warmup = FALSE, + thin = NULL, + max_treedepth = NULL, + adapt_engaged = TRUE, + adapt_delta = NULL, + step_size = NULL, + metric = NULL, + metric_file = NULL, + inv_metric = NULL, + init_buffer = NULL, + term_buffer = NULL, + window = NULL, + fixed_param = FALSE, + sig_figs = NULL, + validate_csv = TRUE, + show_messages = TRUE) { parallel_chains <- 1 if (fixed_param) { chains <- 1 diff --git a/man/CmdStanModel.Rd b/man/CmdStanModel.Rd index 268a072ee..aa0948cdc 100644 --- a/man/CmdStanModel.Rd +++ b/man/CmdStanModel.Rd @@ -35,6 +35,7 @@ methods, many of which have their own (linked) documentation pages: \subsection{Model fitting}{\tabular{ll}{ \strong{Method} \tab \strong{Description} \cr \code{\link[=model-method-sample]{$sample()}} \tab Run CmdStan's \code{"sample"} method, return \code{\link{CmdStanMCMC}} object. \cr + \code{\link[=model-method-sample_mpi]{$sample_mpi()}} \tab Run CmdStan's \code{"sample"} method with \href{https://mc-stan.org/math/mpi.html}{MPI}, return \code{\link{CmdStanMCMC}} object. \cr \code{\link[=model-method-optimize]{$optimize()}} \tab Run CmdStan's \code{"optimize"} method, return \code{\link{CmdStanMLE}} object. \cr \code{\link[=model-method-variational]{$variational()}} \tab Run CmdStan's \code{"variational"} method, return \code{\link{CmdStanVB}} object. \cr \code{\link[=model-method-generate-quantities]{$generate_quantities()}} \tab Run CmdStan's \code{"generate quantities"} method, return \code{\link{CmdStanGQ}} object. \cr diff --git a/man/model-method-check_syntax.Rd b/man/model-method-check_syntax.Rd index 00e404f4a..38b20345f 100644 --- a/man/model-method-check_syntax.Rd +++ b/man/model-method-check_syntax.Rd @@ -84,8 +84,8 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, -\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-compile.Rd b/man/model-method-compile.Rd index 72eeab0bd..c4a63aebb 100644 --- a/man/model-method-compile.Rd +++ b/man/model-method-compile.Rd @@ -120,8 +120,8 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-generate-quantities}}, -\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-generate-quantities.Rd b/man/model-method-generate-quantities.Rd index 2039cad71..8e86539cd 100644 --- a/man/model-method-generate-quantities.Rd +++ b/man/model-method-generate-quantities.Rd @@ -98,8 +98,8 @@ The Stan and CmdStan documentation: Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, -\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-mpi-sample.Rd b/man/model-method-mpi-sample.Rd deleted file mode 100644 index d42eb3d95..000000000 --- a/man/model-method-mpi-sample.Rd +++ /dev/null @@ -1,229 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/model.R -\name{model-method-mpi-sample} -\alias{model-method-mpi-sample} -\alias{sample_mpi} -\title{Run Stan's MCMC algorithms with MPI} -\description{ -The \verb{$sample_mpi()} method of a \code{\link{CmdStanModel}} object runs the -default MCMC algorithm in CmdStan (\verb{algorithm=hmc engine=nuts}) with MPI -(STAN_MPI makefile flag), to produce a set of draws from the posterior -distribution of a model conditioned on some data. - -In order to use MPI with Stan, an MPI implementation must be installed. -For Unix systems the most commonly used implementations are MPICH and OpenMPI. -The implementations provide an MPI C++ compiler wrapper (for example mpicxx), -which is required to compile the model. - -An example of compiling with STAN_MPI:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -mod <- cmdstan_model("model.stan", cpp_options = cpp_options) -} - -The C++ options that need supplied to the compile call are: -\itemize{ -\item \code{STAN_MPI}: Enables the use of MPI with Stan -\item \code{CXX}: The name of the MPI C++ compiler wrapper (typicall mpicxx) -\item \code{TBB_CXX_TYPE}: The C++ compiler the MPI wrapper wraps. Typically gcc on -Linux and clang on macOS. -} - -In the call to the \verb{$sample_mpi()} method, we can additionally provide -the name of the MPI launcher (\code{mpi_cmd}), which defaults to "mpiexec", -and any other MPI launch arguments. In most cases, it is enough to -only define the number of processes with \code{mpi_args = list("n" = 4)}. - -An example of a call of \verb{$sample_mpi()}:\preformatted{cpp_options = list(STAN_MPI = TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") -fit <- mod$sample_mpi(data_list, mpi_args = c("-n", 4)) -} -} -\section{Usage}{ -\preformatted{$sample_mpi( - data = NULL, - mpi_cmd = "mpiexec", - mpi_args = NULL, - seed = NULL, - refresh = NULL, - init = NULL, - save_latent_dynamics = FALSE, - output_dir = NULL, - chains = 4, - parallel_chains = getOption("mc.cores", 1), - chain_ids = seq_len(chains), - iter_warmup = NULL, - iter_sampling = NULL, - save_warmup = FALSE, - thin = NULL, - max_treedepth = NULL, - adapt_engaged = TRUE, - adapt_delta = NULL, - step_size = NULL, - metric = NULL, - metric_file = NULL, - inv_metric = NULL, - init_buffer = NULL, - term_buffer = NULL, - window = NULL, - fixed_param = FALSE, - sig_figs = NULL, - validate_csv = TRUE, - show_messages = TRUE -) -} -} - -\section{Arguments}{ - -\itemize{ -\item \code{mpi_cmd}: (character vector) The MPI launcher used for launching MPI processes. -The default launcher is \code{mpiexec}. -\item \code{mpi_args}: (list) A list of arguments to use when launching MPI processes. -For example, mpi_args = list("n" = 4) launches the executable as -\verb{mpiexec -n 4 model_executable}, followed by CmdStan arguments -for the model executable. -\item \code{data}, \code{seed}, \code{refresh}, \code{init}, \code{save_latent_dynamics}, \code{output_dir}, -\code{chains}, \code{parallel_chains}, \code{chain_ids}, \code{iter_warmup}, \code{iter_sampling}, -\code{save_warmup}, \code{thin}, \code{max_treedepth}, \code{adapt_engaged}, \code{adapt_delta}, -\code{step_size}, \code{metric}, \code{metric_file}, \code{inv_metric}, \code{init_buffer}, -\code{term_buffer}, \code{window}, \code{fixed_param}, \code{sig_figs}, \code{validate_csv}, -\code{show_messages}: -Same as for the \code{\link[=model-method-sample]{$sample()}} method. -} -} - -\section{Value}{ - The \verb{$sample_mpi()} method returns a \code{\link{CmdStanMCMC}} object. -} - -\examples{ -\dontrun{ -library(cmdstanr) -library(posterior) -library(bayesplot) -color_scheme_set("brightblue") - -# Set path to cmdstan -# (Note: if you installed CmdStan via install_cmdstan() with default settings -# then setting the path is unnecessary but the default below should still work. -# Otherwise use the `path` argument to specify the location of your -# CmdStan installation.) -set_cmdstan_path(path = NULL) - -# Create a CmdStanModel object from a Stan program, -# here using the example model that comes with CmdStan -file <- file.path(cmdstan_path(), "examples/bernoulli/bernoulli.stan") -mod <- cmdstan_model(file) -mod$print() - -# Data as a named list (like RStan) -stan_data <- list(N = 10, y = c(0,1,0,0,0,0,0,0,0,1)) - -# Run MCMC using the 'sample' method -fit_mcmc <- mod$sample( - data = stan_data, - seed = 123, - chains = 2, - parallel_chains = 2 -) - -# Use 'posterior' package for summaries -fit_mcmc$summary() - -# Get posterior draws -draws <- fit_mcmc$draws() -print(draws) - -# Convert to data frame using posterior::as_draws_df -as_draws_df(draws) - -# Plot posterior using bayesplot (ggplot2) -mcmc_hist(fit_mcmc$draws("theta")) - -# Call CmdStan's diagnose and stansummary utilities -fit_mcmc$cmdstan_diagnose() -fit_mcmc$cmdstan_summary() - -# For models fit using MCMC, if you like working with RStan's stanfit objects -# then you can create one with rstan::read_stan_csv() - -# stanfit <- rstan::read_stan_csv(fit_mcmc$output_files()) - - -# Run 'optimize' method to get a point estimate (default is Stan's LBFGS algorithm) -# and also demonstrate specifying data as a path to a file instead of a list -my_data_file <- file.path(cmdstan_path(), "examples/bernoulli/bernoulli.data.json") -fit_optim <- mod$optimize(data = my_data_file, seed = 123) - -fit_optim$summary() - - -# Run 'variational' method to approximate the posterior (default is meanfield ADVI) -fit_vb <- mod$variational(data = stan_data, seed = 123) - -fit_vb$summary() - -# Plot approximate posterior using bayesplot -mcmc_hist(fit_vb$draws("theta")) - - -# Specifying initial values as a function -fit_mcmc_w_init_fun <- mod$sample( - data = stan_data, - seed = 123, - chains = 2, - refresh = 0, - init = function() list(theta = runif(1)) -) -fit_mcmc_w_init_fun_2 <- mod$sample( - data = stan_data, - seed = 123, - chains = 2, - refresh = 0, - init = function(chain_id) { - # silly but demonstrates optional use of chain_id - list(theta = 1 / (chain_id + 1)) - } -) -fit_mcmc_w_init_fun_2$init() - -# Specifying initial values as a list of lists -fit_mcmc_w_init_list <- mod$sample( - data = stan_data, - seed = 123, - chains = 2, - refresh = 0, - init = list( - list(theta = 0.75), # chain 1 - list(theta = 0.25) # chain 2 - ) -) -fit_optim_w_init_list <- mod$optimize( - data = stan_data, - seed = 123, - init = list( - list(theta = 0.75) - ) -) -fit_optim_w_init_list$init() -} - -} -\seealso{ -The CmdStanR website -(\href{https://mc-stan.org/cmdstanr/}{mc-stan.org/cmdstanr}) for online -documentation and tutorials. - -The Stan and CmdStan documentation: -\itemize{ -\item Stan documentation: \href{https://mc-stan.org/users/documentation/}{mc-stan.org/users/documentation} -\item CmdStan User’s Guide: \href{https://mc-stan.org/docs/cmdstan-guide/}{mc-stan.org/docs/cmdstan-guide} -} - -Other CmdStanModel methods: -\code{\link{model-method-check_syntax}}, -\code{\link{model-method-compile}}, -\code{\link{model-method-generate-quantities}}, -\code{\link{model-method-optimize}}, -\code{\link{model-method-sample}}, -\code{\link{model-method-variational}} -} -\concept{CmdStanModel methods} diff --git a/man/model-method-optimize.Rd b/man/model-method-optimize.Rd index 7cb687bd7..a98131cb9 100644 --- a/man/model-method-optimize.Rd +++ b/man/model-method-optimize.Rd @@ -255,7 +255,7 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, -\code{\link{model-method-mpi-sample}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-sample}}, \code{\link{model-method-variational}} } diff --git a/man/model-method-sample.Rd b/man/model-method-sample.Rd index 792b18174..c1080887e 100644 --- a/man/model-method-sample.Rd +++ b/man/model-method-sample.Rd @@ -345,8 +345,8 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, -\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-variational}} } \concept{CmdStanModel methods} diff --git a/man/model-method-sample_mpi.Rd b/man/model-method-sample_mpi.Rd new file mode 100644 index 000000000..fee26162c --- /dev/null +++ b/man/model-method-sample_mpi.Rd @@ -0,0 +1,98 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/model.R +\name{model-method-sample_mpi} +\alias{model-method-sample_mpi} +\alias{sample_mpi} +\title{Run Stan's MCMC algorithms with MPI} +\description{ +The \verb{$sample_mpi()} method of a \code{\link{CmdStanModel}} object is +identical to the \verb{$sample()} method but with support for +\href{https://mc-stan.org/math/mpi.html}{MPI}. The target audience for MPI are +those with large computer clusters. For other users, the +\code{\link[=model-method-sample]{$sample()}} method provides both parallelization of +chains and threading support for within-chain parallelization. +} +\details{ +In order to use MPI with Stan, an MPI implementation must be +installed. For Unix systems the most commonly used implementations are +MPICH and OpenMPI. The implementations provide an MPI C++ compiler wrapper +(for example mpicxx), which is required to compile the model. + +An example of compiling with MPI:\preformatted{mpi_options <- list(STAN_MPI=TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +mod <- cmdstan_model("model.stan", cpp_options = mpi_options) +} + +The C++ options that must be supplied to the +\link[=model-method-compile]{compile} call are: +\itemize{ +\item \code{STAN_MPI}: Enables the use of MPI with Stan if \code{TRUE}. +\item \code{CXX}: The name of the MPI C++ compiler wrapper. Typically \code{"mpicxx"}. +\item \code{TBB_CXX_TYPE}: The C++ compiler the MPI wrapper wraps. Typically \code{"gcc"} +on Linux and \code{"clang"} on macOS. +} + +In the call to the \verb{$sample_mpi()} method we can also provide the name of +the MPI launcher (\code{mpi_cmd}, defaulting to \code{"mpiexec"}) and any other +MPI launch arguments. In most cases, it is enough to only define the number +of processes with \code{mpi_args = list("n" = 4)}. +} +\section{Usage}{ +\preformatted{$sample_mpi( + ..., # same arguments as $sample() method + mpi_cmd = "mpiexec", + mpi_args = NULL +) +} +} + +\section{Arguments unique to the \code{sample_mpi} method}{ + +\itemize{ +\item \code{mpi_cmd}: (character vector) The MPI launcher used for launching MPI processes. +The default launcher is \code{"mpiexec"}. +\item \code{mpi_args}: (list) A list of arguments to use when launching MPI processes. +For example, \code{mpi_args = list("n" = 4)} launches the executable as +\verb{mpiexec -n 4 model_executable}, followed by CmdStan arguments +for the model executable. +} + +All other arguments are the same as for +\code{\link[=model-method-sample]{$sample()}}. +} + +\section{Value}{ + The \verb{$sample_mpi()} method returns a \code{\link{CmdStanMCMC}} object. +} + +\examples{ +\dontrun{ +# mpi_options <- list(STAN_MPI=TRUE, CXX="mpicxx", TBB_CXX_TYPE="gcc") +# mod <- cmdstan_model("model.stan", cpp_options = mpi_options) +# fit <- mod$sample_mpi(..., mpi_args = list("n" = 4)) +} + +} +\seealso{ +The CmdStanR website +(\href{https://mc-stan.org/cmdstanr/}{mc-stan.org/cmdstanr}) for online +documentation and tutorials. + +The Stan and CmdStan documentation: +\itemize{ +\item Stan documentation: \href{https://mc-stan.org/users/documentation/}{mc-stan.org/users/documentation} +\item CmdStan User’s Guide: \href{https://mc-stan.org/docs/cmdstan-guide/}{mc-stan.org/docs/cmdstan-guide} +} + +The Stan Math Library's MPI documentation +(\href{https://mc-stan.org/math/mpi.html}{mc-stan.org/math/mpi}) for more +details on MPI support in Stan. + +Other CmdStanModel methods: +\code{\link{model-method-check_syntax}}, +\code{\link{model-method-compile}}, +\code{\link{model-method-generate-quantities}}, +\code{\link{model-method-optimize}}, +\code{\link{model-method-sample}}, +\code{\link{model-method-variational}} +} +\concept{CmdStanModel methods} diff --git a/man/model-method-variational.Rd b/man/model-method-variational.Rd index de43e6658..9b7e61861 100644 --- a/man/model-method-variational.Rd +++ b/man/model-method-variational.Rd @@ -272,8 +272,8 @@ Other CmdStanModel methods: \code{\link{model-method-check_syntax}}, \code{\link{model-method-compile}}, \code{\link{model-method-generate-quantities}}, -\code{\link{model-method-mpi-sample}}, \code{\link{model-method-optimize}}, +\code{\link{model-method-sample_mpi}}, \code{\link{model-method-sample}} } \concept{CmdStanModel methods} From d46b8d73b7aaee1e674838a69998a94a2887fcfb Mon Sep 17 00:00:00 2001 From: jgabry Date: Tue, 1 Dec 2020 18:43:47 -0700 Subject: [PATCH 16/21] revert one of the doc edits --- R/model.R | 33 +++++++++++++++++++++++++++++---- man/model-method-sample_mpi.Rd | 33 +++++++++++++++++++++++++++++---- 2 files changed, 58 insertions(+), 8 deletions(-) diff --git a/R/model.R b/R/model.R index 237f0b500..00ffaa5f7 100644 --- a/R/model.R +++ b/R/model.R @@ -998,9 +998,35 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' @section Usage: #' ``` #' $sample_mpi( -#' ..., # same arguments as $sample() method +#' data = NULL, #' mpi_cmd = "mpiexec", -#' mpi_args = NULL +#' mpi_args = NULL, +#' seed = NULL, +#' refresh = NULL, +#' init = NULL, +#' save_latent_dynamics = FALSE, +#' output_dir = NULL, +#' chains = 4, +#' parallel_chains = getOption("mc.cores", 1), +#' chain_ids = seq_len(chains), +#' iter_warmup = NULL, +#' iter_sampling = NULL, +#' save_warmup = FALSE, +#' thin = NULL, +#' max_treedepth = NULL, +#' adapt_engaged = TRUE, +#' adapt_delta = NULL, +#' step_size = NULL, +#' metric = NULL, +#' metric_file = NULL, +#' inv_metric = NULL, +#' init_buffer = NULL, +#' term_buffer = NULL, +#' window = NULL, +#' fixed_param = FALSE, +#' sig_figs = NULL, +#' validate_csv = TRUE, +#' show_messages = TRUE #' ) #' ``` #' @@ -1012,8 +1038,7 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' `mpiexec -n 4 model_executable`, followed by CmdStan arguments #' for the model executable. #' -#' All other arguments are the same as for -#' [`$sample()`][model-method-sample]. +#' All other arguments are the same as for [`$sample()`][model-method-sample]. #' #' @section Value: The `$sample_mpi()` method returns a [`CmdStanMCMC`] object. #' diff --git a/man/model-method-sample_mpi.Rd b/man/model-method-sample_mpi.Rd index fee26162c..5d1abd65f 100644 --- a/man/model-method-sample_mpi.Rd +++ b/man/model-method-sample_mpi.Rd @@ -38,9 +38,35 @@ of processes with \code{mpi_args = list("n" = 4)}. } \section{Usage}{ \preformatted{$sample_mpi( - ..., # same arguments as $sample() method + data = NULL, mpi_cmd = "mpiexec", - mpi_args = NULL + mpi_args = NULL, + seed = NULL, + refresh = NULL, + init = NULL, + save_latent_dynamics = FALSE, + output_dir = NULL, + chains = 4, + parallel_chains = getOption("mc.cores", 1), + chain_ids = seq_len(chains), + iter_warmup = NULL, + iter_sampling = NULL, + save_warmup = FALSE, + thin = NULL, + max_treedepth = NULL, + adapt_engaged = TRUE, + adapt_delta = NULL, + step_size = NULL, + metric = NULL, + metric_file = NULL, + inv_metric = NULL, + init_buffer = NULL, + term_buffer = NULL, + window = NULL, + fixed_param = FALSE, + sig_figs = NULL, + validate_csv = TRUE, + show_messages = TRUE ) } } @@ -56,8 +82,7 @@ For example, \code{mpi_args = list("n" = 4)} launches the executable as for the model executable. } -All other arguments are the same as for -\code{\link[=model-method-sample]{$sample()}}. +All other arguments are the same as for \code{\link[=model-method-sample]{$sample()}}. } \section{Value}{ From 3ffd517129c04c245c031f44f185ab8ec6142ae5 Mon Sep 17 00:00:00 2001 From: jgabry Date: Tue, 1 Dec 2020 18:57:02 -0700 Subject: [PATCH 17/21] clarify that sample_mpi is missing a few arguments --- R/model.R | 4 +++- man/model-method-sample_mpi.Rd | 4 +++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/R/model.R b/R/model.R index 00ffaa5f7..cfa3d28a0 100644 --- a/R/model.R +++ b/R/model.R @@ -1038,7 +1038,9 @@ CmdStanModel$set("public", name = "sample", value = sample_method) #' `mpiexec -n 4 model_executable`, followed by CmdStan arguments #' for the model executable. #' -#' All other arguments are the same as for [`$sample()`][model-method-sample]. +#' All other arguments are the same as for [`$sample()`][model-method-sample] +#' except `$sample_mpi()` does not have arguments `threads_per_chain` or +#' `parallel_chains`. #' #' @section Value: The `$sample_mpi()` method returns a [`CmdStanMCMC`] object. #' diff --git a/man/model-method-sample_mpi.Rd b/man/model-method-sample_mpi.Rd index 5d1abd65f..b8b933d4c 100644 --- a/man/model-method-sample_mpi.Rd +++ b/man/model-method-sample_mpi.Rd @@ -82,7 +82,9 @@ For example, \code{mpi_args = list("n" = 4)} launches the executable as for the model executable. } -All other arguments are the same as for \code{\link[=model-method-sample]{$sample()}}. +All other arguments are the same as for \code{\link[=model-method-sample]{$sample()}} +except \verb{$sample_mpi()} does not have arguments \code{threads_per_chain} or +\code{parallel_chains}. } \section{Value}{ From 641d0c342dd26fb06f7bcdbab6e20ae622ce455a Mon Sep 17 00:00:00 2001 From: jgabry Date: Tue, 1 Dec 2020 18:57:09 -0700 Subject: [PATCH 18/21] rename test file --- tests/testthat/{test-mpi.R => test-model-sample_mpi.R} | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) rename tests/testthat/{test-mpi.R => test-model-sample_mpi.R} (97%) diff --git a/tests/testthat/test-mpi.R b/tests/testthat/test-model-sample_mpi.R similarity index 97% rename from tests/testthat/test-mpi.R rename to tests/testthat/test-model-sample_mpi.R index 688653108..47ab4c1f8 100644 --- a/tests/testthat/test-mpi.R +++ b/tests/testthat/test-model-sample_mpi.R @@ -1,4 +1,4 @@ -context("mpi") +context("model-sample_mpi") test_that("sample_mpi() works", { skip_on_cran() From 6db11dceea174418516087446bb3b13b1107b087 Mon Sep 17 00:00:00 2001 From: jgabry Date: Tue, 1 Dec 2020 18:58:25 -0700 Subject: [PATCH 19/21] don't need to define parallel_chains --- R/model.R | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/R/model.R b/R/model.R index cfa3d28a0..3d3691663 100644 --- a/R/model.R +++ b/R/model.R @@ -1086,14 +1086,12 @@ sample_mpi_method <- function(data = NULL, sig_figs = NULL, validate_csv = TRUE, show_messages = TRUE) { - parallel_chains <- 1 if (fixed_param) { chains <- 1 save_warmup <- FALSE } checkmate::assert_integerish(chains, lower = 1, len = 1) - checkmate::assert_integerish(parallel_chains, lower = 1, null.ok = TRUE) checkmate::assert_integerish(chain_ids, lower = 1, len = chains, unique = TRUE, null.ok = FALSE) sample_args <- SampleArgs$new( iter_warmup = iter_warmup, @@ -1128,7 +1126,7 @@ sample_mpi_method <- function(data = NULL, ) cmdstan_procs <- CmdStanMCMCProcs$new( num_procs = chains, - parallel_procs = parallel_chains, + parallel_procs = 1, show_stderr_messages = show_messages ) runset <- CmdStanRun$new(args = cmdstan_args, procs = cmdstan_procs) From cf22f8498a2553e3a8e6656d900266b232fab616 Mon Sep 17 00:00:00 2001 From: Rok Cesnovar Date: Thu, 3 Dec 2020 21:32:05 +0100 Subject: [PATCH 20/21] update NEWS.md after release --- NEWS.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/NEWS.md b/NEWS.md index 450853c02..9a55fe47a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,11 @@ +# Items for next tagged release + +### Bug fixes + +### New features + +* Added `$sample_mpi()` for MCMC sampling with MPI. (#350) + # cmdstanr 0.2.2 ### Bug fixes From 6e1c24b724d6c5b9a509dc9082ef5d716262a0a4 Mon Sep 17 00:00:00 2001 From: jgabry Date: Thu, 3 Dec 2020 14:17:29 -0700 Subject: [PATCH 21/21] remove duplicate news item --- NEWS.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 9a55fe47a..8c3e6a530 100644 --- a/NEWS.md +++ b/NEWS.md @@ -21,8 +21,6 @@ * Added threading support via `threads` argument for `$optimize()` and `$variational()` (was already available via `threads_per_chain` for `$sample()`). (#369) -* Added `$sample_mpi()` for MCMC sampling with MPI. (#350) - # cmdstanr 0.2.1 ### Bug fixes