Run parallel chains and update model

1332 views
Skip to first unread message

cro...@ualberta.ca

unread,
Jun 27, 2018, 8:09:01 PM6/27/18
to nimble-users
Hello all,
I am a quantitative ecologist - i.e. not a programmer or a statistician - and I use JAGS through R quite a bit to run hierarchical Bayesian models. I am trying to use nimble in the same way I use JAGS in an attempt to speed things up on models that take a long time in JAGS (like 3 weeks) and use a great deal of memory for the processing and output. 

My questions are:
1. Can I use parallel processing with nimble, i.e. send individual MCMC chains to separate cores (and if so, how? - I can't find anything on the internet about this)? I've tried with doParallel and can't get it to work. 

2. Is there any way to update the models after they have finished if the haven't converged yet? 

Thank you in advance for any help you can give or resources you can point me to. 

Andrew D. Crosby
Postdoctoral Fellow
Boreal Avian Modelling Project
Dept. of Biological Sciences
CW405 Biological Sciences Building
University of Alberta
Edmonton, AB T6G 2E9

Daniel Turek

unread,
Jun 27, 2018, 9:23:12 PM6/27/18
to cro...@ualberta.ca, nimble-users
I can give an easy answer to #2:

>> Is there any way to update the models after they have finished if the haven't converged yet? 

If you use the lowest-level entry point to NIMBLE's MCMC engine, the run() method of the compiled MCMC object, then at that level there's the ability to "continue" an on-going run using reset=FALSE.  Note the different syntax for extracting the posterior samples after using this method.


Rmodel <- nimbleModel(code, constants, data, inits)

conf <- configureMCMC(Rmodel)
Rmcmc <- buildMCMC(conf)
Cmodel <- compileNimble(Rmodel)
Cmcmc <- compileNimble(Rmcmc, project = Rmodel)

Cmcmc$run(10000)
samples <- as.matrix(Cmcmc$mvSamples)

## examine samples array, determine it hasn't converged yet...

## continue that same run of the MCMC for 50000 more iterations:
Cmcmc$run(50000, reset = FALSE)

samplesAll60000 <- as.matrix(Cmcmc$mvSamples)


Let me know if this answers your question.

Cheers,
Daniel





--
You received this message because you are subscribed to the Google Groups "nimble-users" group.
To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users+unsubscribe@googlegroups.com.
To post to this group, send email to nimble...@googlegroups.com.
To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/9375bca7-b53b-4536-a4ef-275b2062649f%40googlegroups.com.
For more options, visit https://groups.google.com/d/optout.

Perry de Valpine

unread,
Jun 28, 2018, 2:20:42 AM6/28/18
to Daniel Turek, cro...@ualberta.ca, nimble-users
Regarding parallelization, currently what you need to do is compile separate copies of the model and MCMC on each thread.  This is not ideal because that step can take some time.  We hope in the future to make it easier.

This is a brief answer but let me know if you need more details.

-Perry

To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users...@googlegroups.com.

To post to this group, send email to nimble...@googlegroups.com.
To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/9375bca7-b53b-4536-a4ef-275b2062649f%40googlegroups.com.
For more options, visit https://groups.google.com/d/optout.

--
You received this message because you are subscribed to the Google Groups "nimble-users" group.
To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users...@googlegroups.com.

To post to this group, send email to nimble...@googlegroups.com.

Andy Crosby

unread,
Jun 28, 2018, 12:12:35 PM6/28/18
to Perry de Valpine, Daniel Turek, nimble-users

Thank you both for the quick answers. So I guess it’s a tradeoff between compilation time and run time. I’ll keep working on it to see what I can do.

 

Best,

 

Andrew D. Crosby
Postdoctoral Fellow
Boreal Avian Modelling Project
Dept. of Biological Sciences
CW405 Biological Sciences Building
University of Alberta
Edmonton, AB T6G 2E9

 

Cat Sun

unread,
Mar 21, 2020, 3:34:18 AM3/21/20
to nimble-users
Hi,

I'm also interested in being able to send chains off to their own cores while also making sure that I can extend the chains if they end up not being long enough. I found code ( https://r-nimble.org/nimbleExamples/parallelizing_NIMBLE.html ) illustrating how to parallelize, and had some questions that I'm hoping someone can clarify:

1) What is the point of the 'seed' argument in the 'run_MCMC_allcode' function? It's not invoked in the parLapply call, but it seems necessary to avoid errors like " Error in checkForRemoteErrors(val) :  3 nodes produced errors; first error: unused argument (X[[i]])"

2) I cant seem to get the function to correctly return the compiled MCMC object, when I use the run() method in anticipation of wanting to extend the chains. I get empty slots. Is this to do with the active binding? See code and output below.

3) Does it even make sense to try to do this? If i have to bring the chains from the different cores back together to assess convergence and effective sample sizes, is it possible to get back to the cores and where they left off? Or do I somehow need to send the compiled model MCMC object back to each core with another custom function  and parLapply()... This latter option does not seem likely, as the code in the link for parallelization suggests that the model and MCMC building and compiling need to happen on the cores. 

My models dont take long to compile, especially relative to the chain lengths that are likely to be necessary. I just dont want to risk running the chains for not long enough, and then having to start from scratch again to run for longer.

any thoughts would be greatly appreciated - thanks!


-Cat


################
#### the code 
################

library(parallel)
this_cluster <- makeCluster(3)
set.seed(10120)
# Simulate some data
myData <- rgamma(1000, shape = 0.4, rate = 0.8)

# Create a function with all the needed code
run_MCMC_allcode <- function( seed,data) { # removing the seed argument here causes issues with the parLapply call that comes after
  library(nimble)
  
  myCode <- nimbleCode({
    a ~ dunif(0, 100)
    b ~ dnorm(0, 100)
    
    for (i in 1:length_y) {
      y[i] ~ dgamma(shape = a, rate = b)
    }
  })
  
  myModel <- nimbleModel(code = myCode,
                         data = list(y = data),
                         constants = list(length_y = 1000),
                         inits = list(a = 0.5, b = 0.5))
 

 # Instead of this, since runMCMC does not allow for chain extension... 
  # CmyModel <- compileNimble(myModel)
  # myMCMC <- buildMCMC(CmyModel)
  # CmyMCMC <- compileNimble(myMCMC)
  # results <- runMCMC(CmyMCMC, niter = 10) # but there is no issue when removing setSeed = seed 
  # return(results)
  # 
  # 

#and instead have this:
  conf <- configureMCMC(myModel)
  conf$addMonitors(c("a","b"))
  Rmcmc <- buildMCMC(conf)
  Cmodel <- compileNimble(myModel,showCompilerOutput = TRUE)
  Cmcmc <- compileNimble(Rmcmc, project = myModel,showCompilerOutput = TRUE)
  Cmcmc$run(20)
  return(Cmcmc)
}

chain_output <- parLapply(cl = this_cluster, X = 1:3, 
                          fun = run_MCMC_allcode, 
                          data = myData)

stopCluster(this_cluster)

####### the output

> chain_output[[1]]$mvSamples
CmodelValues object with variables: a, b.

> as.matrix(chain_output[[1]]$mvSamples)
Error in .Call(NULL, <pointer: (nil)>) : 
  first argument must be a string (of length 1) or native symbol reference


















--

To unsubscribe from this group and stop receiving emails from it, send an email to nimble...@googlegroups.com.

--
You received this message because you are subscribed to the Google Groups "nimble-users" group.

To unsubscribe from this group and stop receiving emails from it, send an email to nimble...@googlegroups.com.

Adrian Monroe

unread,
Mar 21, 2020, 11:53:00 AM3/21/20
to Cat Sun, nimble-users
Hi Cat,

To answer your third question, see below for some code to check on your model, and then keep sampling more iterations until convergence. If anyone sees areas for improvement I would be grateful!

Best,
Adrian

library(parallel)
library(coda)
set.seed(22)
nc <- 3 # number of chains
cl<-makeCluster(nc,timeout=5184000)
inits <- function() {list(a = rnorm(1), b = rnorm(1))}
nimbledata <- list(y = data)
nimbleconstants <- list(length_y = 1000)
params <- c("a", "b")
clusterExport(cl, c("myCode", "inits", "nimbledata", "nimbleconstants", "params"))
for (j in seq_along(cl)) {
  set.seed(j)
  init <- inits()
  clusterExport(cl[j], "init")
}
out <- clusterEvalQ(cl, {
  library(nimble)
  library(coda)
  model <- nimbleModel(code = myCode, name = "myCode",
                           constants = nimbleconstants, data = nimbledata,
                           inits = init)
  Cmodel <- compileNimble(model)
  modelConf <- configureMCMC(model)
  modelConf$addMonitors(params)
  modelMCMC <- buildMCMC(modelConf)
  CmodelMCMC <- compileNimble(modelMCMC, project = myCode)
  out1 <- runMCMC(CmodelMCMC, niter = 10000)
  return(as.mcmc(out1))
})

out.mcmc <- as.mcmc(out)
traceplot(out.mcmc[, "b"]

## If has not converged, continue sampling
start <- Sys.time()
out2 <- clusterEvalQ(cl, {
  out1 <- runMCMC(CmodelMCMC, niter = 20000)
  return(as.mcmc(out1))
})

out.mcmc.update1 <- as.mcmc(out2)

out.mcmc.bind <- mcmc.list()
for (i in seq_len(nc)) {
out.mcmc.bind[[i]] <- mcmc(rbind(out.mcmc[[i]], out.mcmc.update1[[i]]))
}
traceplot(out.mcmc.bind[, "b"]

To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users...@googlegroups.com.
To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/4fa0c5c5-9fc3-492c-b21f-50f6c5f3185a%40googlegroups.com.

Cat Sun

unread,
Mar 21, 2020, 3:50:01 PM3/21/20
to nimble-users
Hi Adrian - yes, that worked fantastically, thank you! 

Interested to hear if anybody has clarity on questions 1 and 2, just for curiosity's sake.

Cheers,
To unsubscribe from this group and stop receiving emails from it, send an email to nimble...@googlegroups.com.
To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/4fa0c5c5-9fc3-492c-b21f-50f6c5f3185a%40googlegroups.com.

Chris Paciorek

unread,
Mar 24, 2020, 2:46:57 PM3/24/20
to Cat Sun, nimble-users
Hi Cat,

1) In the `parLapply` call, the values of `X` are the values used for
the `seed` function. So it is used.

2) Passing around NIMBLE's compiled objects is not something that will
work in general at the moment because of how the C++ objects are set
up and interfaced to R.
We are working (long-term) on improving NIMBLE's ability to save and
reload models and nimbleFunctions, which should ultimately address
this.

3) Adrian's solution looks quite nice. Thanks!

Chris
> To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users...@googlegroups.com.
> To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/dfdf70b6-3291-48d5-904a-ab41ecbbdec0%40googlegroups.com.

Adrian Monroe

unread,
Mar 28, 2020, 2:14:01 PM3/28/20
to oliver...@gmail.com, nimble-users
Hi Ollie,

You bring up a good point, and I am sharing this with the rest of the nimble group to clarify. It seems indeed according to chapter 7 of the nimble help (https://r-nimble.org/html_manual/cha-mcmc.html#sec:runMCMC) that runMCMC does NOT continue an MCMC run where it left off previously. I must have missed that, and I have modified the code for sampling and updating in parallel is below. Note the update returns all iterations from the start, not just the additional samples. Interestingly, when I used runMCMC to update, it didn't look to me like it was completely starting over, but instead was sampling from distributions it had reached previously (which is probably why I assumed it picked up from the previous run). If any of the nimble developers have some insights on this, and why reset = FALSE is not the default, I would be interested.

Best,
Adrian

out1 <- clusterEvalQ(cl, {
  library(nimble)
  library(coda)
  model <- nimbleModel(code = myCode, name = "model",

                           constants = nimbleconstants, data = nimbledata,
                           inits = init)
  Cmodel <- compileNimble(model)
  modelConf <- configureMCMC(model)
  modelConf$addMonitors(params)
  modelMCMC <- buildMCMC(modelConf)
  CmodelMCMC <- compileNimble(modelMCMC, project = model)
  CmodelMCMC$run(10000, reset = FALSE)
  return(as.mcmc(as.matrix(CmodelMCMC$mvSamples)))
})

out.mcmc <- as.mcmc(out1)
traceplot(out.mcmc[, "b"]

## If has not converged, continue sampling
start <- Sys.time()
out2 <- clusterEvalQ(cl, {
  CmodelMCMC$run(20000, reset = FALSE)
  return(as.mcmc(as.matrix(CmodelMCMC$mvSamples)))
})

out.mcmc.update1 <- as.mcmc(out2) 
 

On Sat, Mar 28, 2020 at 6:07 AM orwearn <oliver...@gmail.com> wrote:
Hi Adrian

I'm implementing your code solution - thanks for posting it! I had a quick question, though. The Nimble help page (in Section 7.4says 

However, using runMCMC does not support several lower-level options, such as...continuing an existing MCMC run (picking up where it left off)

So what is happening in your code where you continue sampling? Is it starting from the beginning again, and therefore includes burn-in that might need removing?

Thanks for any help with this, I'm just getting started with nimble
Ollie

orwearn

unread,
Mar 29, 2020, 8:55:50 AM3/29/20
to nimble-users
Hi Adrian (and all), 

Thanks for updating your code example. I have a follow-up query on it:

Am I right in thinking that R cannot be closed between the initial run and the update in your code, because it depends on the same cluster ('cl') being open? 

Is there a way of saving, exiting and then updating with more iterations at a later time (as possible in runjags etc.)? (I am running NIMBLE on Google Cloud, wherein it's difficult for me to keep R open for 3+ weeks...). 

Many thanks for any pointers from anyone, I'm only just starting to transition over from JAGS
Ollie

PS If there's a way to add a progress bar (e.g. just for node 1), that would also be a dream...! But not to worry if that isn't possible.

Adrian Monroe

unread,
Apr 1, 2020, 12:56:24 PM4/1/20
to orwearn, nimble-users
Hi Ollie,

Your connection to the clusters will be lost if you shut down R. That said, unless I am missing something, I don't see why you couldn't use clusterEvalQ() to return the necessary nimble objects from each cluster (such as in a list), save these nimble objects, then export the nimble objects back to individual clusters in another R session (looping clusterExport() through each cluster) and continue updating with more iterations. I am curious to see if that works, so please let me know how it goes.

I don't know about a progress bar, and the run times for each chain can be different so I don't know what one would really tell you. 

Best,
Adrian

To unsubscribe from this group and stop receiving emails from it, send an email to nimble-users...@googlegroups.com.
To view this discussion on the web visit https://groups.google.com/d/msgid/nimble-users/fd4c56ae-fa02-4702-818d-f76ac52467d4%40googlegroups.com.

Daniel Turek

unread,
Apr 2, 2020, 3:39:15 PM4/2/20
to Adrian Monroe, orwearn, nimble-users
To add just a few things:

1) I'm not sure if there's any way to have the progress bar printed from one cluster node.  I agree, that would be nice.

2) Even if you return the compiled object(s) from one cluster (looping over clusterExport(), as was suggested), these compiled objects still could not be saved (to be reloaded subsequently into a new R session) due to the current nature of NIMBLE's compilation and the resulting objects.  As I believe was mentioned, addressing this is a long-term goal for NIMBLE.

3) Towards that end - being able to start a new R session, and resume executing an MCMC chain precisely where it left off - I wrote a vignette about "Saving Model and MCMC State", which demonstrates how to save the model and MCMC state after executing an MCMC algorithm.  This is only demonstrated for a single chain, but could be generalized for the multi-chain case.  See the vignette here:

Hope this helps!
Daniel




Daniel Eacker

unread,
Jan 18, 2022, 2:36:39 PM1/18/22
to nimble-users
Hi,

A bit late to add this, but I just wanted to add that I don't think this is correct for setting the seed in parallel processing using the parallel package:

1) In the `parLapply` call, the values of `X` are the values used for
the `seed` function. So it is used.

I've tried this and it produces different results across MCMC simulations.

What I've found that works for repeatable results using parallel processing is to add this just after making the cluster:

e.g.,

this_cluster <- makeCluster(2)

clusterSetRNGStream(cl = this_cluster, 500) # note that 500 could be any integer.

So, I don't think the X in parLapply actually does anything to produce repeatable results, whereas using this builtin function of the parallel package provides reproducible results.

Cheers,

Dan

Chris Paciorek

unread,
Jan 20, 2022, 4:57:06 PM1/20/22
to Daniel Eacker, nimble-users
hi Dan,

Thanks for commenting here.

I've checked the example and I do get reproducible results using the code provided. I'm wondering if you modified it such that you are creating random initial values? If so, you'd need to use set.seed before you generate the initial values within the run_MCMC_allcode function.

One other note is that the approach in that example relies on simply setting different seeds for the different chains. While this is probably safe, it is possible that the random numbers generated for one chain could partially overlap the random numbers generated for another chain. Even if this happened, I don't think it would cause substantive dependence between the chains. But your approach of using clusterSetRNGStream has the nice feature of ensuring the sequences of random numbers for each of the worker processes won't overlap.

-chris

Quresh Latif

unread,
Aug 15, 2022, 1:23:43 PM8/15/22
to nimble-users
Hello all. I realize this is an older post, but thought I'd share that I was able to successfully build on Adrian's code. The code below implements parallel processing, checks Rhats for specified parameters, and if they are too low, it keeps resuming until Rhats meet the desired threshold. The calculation of Rhats leverages the 'mcmcOutput' package. Perhaps others may find this useful.

    #~~~~~~~~~Parallel processing code (won't work in Windows)~~~~~~~~~#
    library(parallel)
    library(coda)
    set.seed(3)
    cl<-makeCluster(nc, timeout = 5184000)
    clusterExport(cl, c("model", "inits", "data", "constants", "parameters", "ni"))

    for (j in seq_along(cl)) {
      set.seed(j)
      init <- inits()
      clusterExport(cl[j], "init")
    }
    out1 <- clusterEvalQ(cl, {
      library(nimble)
      library(coda)
      model <- nimbleModel(code = model, name = "model",
                           
                           constants = constants, data = data,

                           inits = init)
      Cmodel <- compileNimble(model)
      modelConf <- configureMCMC(model)
      modelConf$addMonitors(parameters)

      modelMCMC <- buildMCMC(modelConf)
      CmodelMCMC <- compileNimble(modelMCMC, project = model)
      CmodelMCMC$run(ni, reset = FALSE)
      return(as.mcmc(as.matrix(CmodelMCMC$mvSamples)))
    })
   
    ## Check convergence ##
    out2 <- out1
    out2[[1]] <- out2[[1]][seq(nb+2, ni+1, by = nt),]
    out2[[2]] <- out2[[2]][seq(nb+2, ni+1, by = nt),]
    out.mcmc <- coda::as.mcmc.list(lapply(out2, coda::as.mcmc))
    #traceplot(out.mcmc[, "b"])
    library(mcmcOutput)
    #if(nc > 1) mod.raw <- coda::as.mcmc.list(lapply(out$samples, coda::mcmc))
    mod <- mcmcOutput(out.mcmc)
    sumTab <- summary(mod, MCEpc = F, Rhat = T, n.eff = T, f = T, overlap0 = T, verbose = F)
    sumTab <- sumTab %>%
      as_tibble() %>%
      mutate(Parameter = row.names(sumTab)) %>%
      select(Parameter, mean:f)
    #MCMCvis::MCMCtrace(out.mcmc, params = "DELTA1[114, 2]", pdf = F, ISB = F)
    ind.Rht <- which(!str_detect(sumTab$Parameter, "test.n") &
                       !str_detect(sumTab$Parameter, "M.save") &
                       !str_detect(sumTab$Parameter, "pXtheta") &
                       !str_detect(sumTab$Parameter, "Ind") &
                       !str_detect(sumTab$Parameter, "ind"))
    mxRht <- sumTab %>% slice(ind.Rht) %>% pull(Rhat) %>% max(na.rm = T)
    #sumTab %>% slice(ind.Rht) %>% arrange(desc(Rhat)) %>% View()

   
    ## If has not converged, continue sampling
    n.reruns <- 0
    while(round(mxRht, digits = 1) > 1.1) {
      out2 <- clusterEvalQ(cl, {
        CmodelMCMC$run(ni, reset = FALSE)
        return(as.mcmc(as.matrix(CmodelMCMC$mvSamples)))
      })
     
      n.reruns <- n.reruns + 1
      print(str_c("Reruns = ", n.reruns))
      if(n.reruns == 1) {
        nb2 <- nb + nb
        ni2 <- ni + ni
      } else {
        nb2 <- nb2 + nb
        ni2 <- ni2 + ni
      }
      out2[[1]] <- out2[[1]][seq(nb2+2, ni2+1, by = nt),]
      out2[[2]] <- out2[[2]][seq(nb2+2, ni2+1, by = nt),]
      out.mcmc.update <- coda::as.mcmc.list(lapply(out2, coda::as.mcmc))
     
      mod <- mcmcOutput(out.mcmc.update)
      sumTab <- summary(mod, MCEpc = F, Rhat = T, n.eff = T, f = T, overlap0 = T, verbose = F)
      sumTab <- sumTab %>%
        as_tibble() %>%
        mutate(Parameter = row.names(sumTab)) %>%
        select(Parameter, mean:f)
      #MCMCvis::MCMCtrace(out.mcmc, params = "DELTA1[114, 2]", pdf = F, ISB = F)
      mxRht <- sumTab %>% slice(ind.Rht) %>% pull(Rhat) %>% max(na.rm = T)
      gc(verbose = F)
    }
    #~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~#

Quresh Latif

unread,
Aug 23, 2022, 12:17:16 PM8/23/22
to nimble-users
One trade-off I am discovering with the above code is that because it uses the base function 'CModelMCMC$run' to allow resumption of sampling after checking convergence, I can't thin the samples as I go. I can thin after recovering the samples to save hard drive space, but the primary sampler does not allow thinning (or burn-in), which means that I end up running out of RAM before I reach convergence. For the time being, it seems like this code is useful at the initial stage of exploring a model, but once I have a sense of how long I'm going to need to run the sampler to get to convergence, I am probably going to have to switch to using the higher level 'nimbleMCMC' function, so that I can implement burn-in and thinning for better memory management.

It might be nice for future versions of NIMBLE if either thinning/burn-in could be included in the base function (...$run) or if an option for resuming sampling could be incorporated into higher level functions that also allow thinning and burn-in.

Daniel Turek

unread,
Aug 23, 2022, 12:24:59 PM8/23/22
to Quresh Latif, nimble-users
Quresh, just set the thinning interval in the MCMC configuration object (using conf$setThin(INTERVAL), I believe), doing that before you build and compile the MCMC.  Then, even using mcmc$run(ITERATIONS) will respect the thinning interval, and only record those samples internally.

Quresh Latif

unread,
Aug 23, 2022, 12:38:00 PM8/23/22
to nimble-users
Ah, perfect! Thanks for pointing that out. I also see that you can set thinning when actually configuring the MCMC using the 'thin' argument (e.g., configureMCMC(Rmodel, thin = 10)). I don't see an argument for setting burn-in, but maybe I'm missing it? In any case, the option for setting thinning in the primary sampler is going to help a lot. Thank you!

Daniel Turek

unread,
Aug 23, 2022, 12:44:41 PM8/23/22
to Quresh Latif, nimble-users
Great, glad it helps.

Quresh Latif

unread,
Aug 23, 2022, 12:56:31 PM8/23/22
to nimble-users
Is it possible or are there plans to allow the user to pull the saved samples out of CModelMCMC and just keep the last sample along with mcmc parameters at that step (e.g., jump probabilities, etc.)? The idea would be to save the samples to the hard drive and keep on sampling without relying on RAM to store sampled iterations. This is what the `saveJAGS` package allows for JAGS, but JAGS is clearly a lot slower, so I'm wondering if there's any way to do this with NIMBLE.

Daniel Turek

unread,
Aug 23, 2022, 2:27:17 PM8/23/22
to Quresh Latif, nimble-users
Quresh, I think we have this functionality pretty well built-in, although I'm not sure how well documented this is... if it's documented at all.

Try:

## build and compile model and MCMC
mcmc$run(iterations)
samples <- as.matrix(mcmc$mvSamples)
## save samples to disk
mcmc$run(more_iterations, reset = FALSE, resetMV = TRUE)   ## resets the internal mvSamples object, but leaves everything else the same
more_samples <- as.matrix(mcmc$mvSamples)




Quresh Latif

unread,
Aug 23, 2022, 2:37:09 PM8/23/22
to nimble-users
Oh wow! Another game changer. I searched for 'resetMV' in the NIMBLE user manual and came up with nothing, so it's not documented in there. I'm not sure how to access the help file (or if there is one) for the ...$run function. In any case, I'll write some code that saves the samples to disk and post it here. Thanks so much!

Daniel Turek

unread,
Aug 23, 2022, 3:07:24 PM8/23/22
to Quresh Latif, nimble-users
You're welcome!  It makes me happy to hear "another game changer".

It looks like it's only documented using help(buildMCMC) --- at least it's documented somewhere, I suppose.

Take a look for yourself, but I'll copy that documentation here:

     ‘resetMV’: Boolean specifying whether to begin recording posterior
     sample chains anew. This argument is only considered when using
     ‘reset = FALSE’.  Specifying ‘reset = FALSE, resetMV = TRUE’
     allows the MCMC algorithm to continue running from where it left
     off, but without appending the new posterior samples to the
     already existing samples, i.e. all previously obtained samples
     will be erased. This option can help reduce memory usage during
     burn-in (default = FALSE).





Quresh Latif

unread,
Aug 23, 2022, 3:11:58 PM8/23/22
to nimble-users

I do see the documentation there. Thanks for pointing it out! Working on upgrading my code now….

 

Quresh S. Latif 
Research Scientist
Bird Conservancy of the Rockies

Phone: (970) 482-1707 ext. 15

www.birdconservancy.org

 

From: Daniel Turek <db...@williams.edu>
Sent: Tuesday, August 23, 2022 1:07 PM
To: Quresh Latif <quresh...@birdconservancy.org>
Cc: nimble-users <nimble...@googlegroups.com>
Subject: Re: Run parallel chains and update model

 

You're welcome!  It makes me happy to hear "another game changer".

 

On Wed, Apr 1, 2020 at 12:56 PM Adrian Monroe <apm...@gmail.com> wrote:

Hi Ollie,

 

Your connection to the clusters will be lost if you shut down R. That said, unless I am missing something, I don't see why you couldn't use clusterEvalQ() to return the necessary nimble objects from each cluster (such as in a list), save these nimble objects, then export the nimble objects back to individual clusters in another R session (looping clusterExport() through each cluster) and continue updating with more iterations. I am curious to see if that works, so please let me know how it goes.

 

I don't know about a progress bar, and the run times for each chain can be different so I don't know what one would really tell you. 

 

Best,

Adrian

 

On Sun, Mar 29, 2020 at 6:55 AM orwearn <oliver...@gmail.com> wrote:

Hi Adrian (and all), 

 

Thanks for updating your code example. I have a follow-up query on it:

 

Am I right in thinking that R cannot be closed between the initial run and the update in your code, because it depends on the same cluster ('cl') being open? 

 

Is there a way of saving, exiting and then updating with more iterations at a later time (as possible in runjags etc.)? (I am running NIMBLE on Google Cloud, wherein it's difficult for me to keep R open for 3+ weeks...). 

 

Many thanks for any pointers from anyone, I'm only just starting to transition over from JAGS

Ollie

 

PS If there's a way to add a progress bar (e.g. just for node 1), that would also be a dream...! But not to worry if that isn't possible.

On Sunday, March 29, 2020 at 1:14:01 AM UTC+7, Adrian Monroe wrote:

Hi Ollie,

 

You bring up a good point, and I am sharing this with the rest of the nimble group to clarify. It seems indeed according to chapter 7 of the nimble help (https://link.edgepilot.com/s/2d4acb37/e08YctqZB0a2BWthtIRhPg?u=https://r-nimble.org/html_manual/cha-mcmc.html%23sec:runMCMC) that runMCMC does NOT continue an MCMC run where it left off previously. I must have missed that, and I have modified the code for sampling and updating in parallel is below. Note the update returns all iterations from the start, not just the additional samples. Interestingly, when I used runMCMC to update, it didn't look to me like it was completely starting over, but instead was sampling from distributions it had reached previously (which is probably why I assumed it picked up from the previous run). If any of the nimble developers have some insights on this, and why reset = FALSE is not the default, I would be interested.

Hi,

 

I'm also interested in being able to send chains off to their own cores while also making sure that I can extend the chains if they end up not being long enough. I found code ( https://link.edgepilot.com/s/5efceaac/RtQw4wQLCESzDc-vZHMF5Q?u=https://r-nimble.org/nimbleExamples/parallelizing_NIMBLE.html ) illustrating how to parallelize, and had some questions that I'm hoping someone can clarify:

--
You received this message because you are subscribed to the Google Groups "nimble-users" group.
To unsubscribe from this group and stop receiving emails from it, send an email to nimble...@googlegroups.com.
To post to this group, send email to nimble...@googlegroups.com.

To view this discussion on the web visit