[Pomp-commits] r1094 - in pkg/pomp: . R inst man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Feb 26 10:42:51 CET 2015


Author: kingaa
Date: 2015-02-26 10:42:50 +0100 (Thu, 26 Feb 2015)
New Revision: 1094

Modified:
   pkg/pomp/DESCRIPTION
   pkg/pomp/NAMESPACE
   pkg/pomp/R/abc.R
   pkg/pomp/R/bsmc.R
   pkg/pomp/R/bsmc2.R
   pkg/pomp/R/builder.R
   pkg/pomp/R/dmeasure-pomp.R
   pkg/pomp/R/dprior-pomp.R
   pkg/pomp/R/dprocess-pomp.R
   pkg/pomp/R/init-state-pomp.R
   pkg/pomp/R/mif.R
   pkg/pomp/R/minim.R
   pkg/pomp/R/nlf.R
   pkg/pomp/R/pfilter.R
   pkg/pomp/R/pmcmc.R
   pkg/pomp/R/pomp-class.R
   pkg/pomp/R/pomp.R
   pkg/pomp/R/probe-match.R
   pkg/pomp/R/probe.R
   pkg/pomp/R/rmeasure-pomp.R
   pkg/pomp/R/rprior-pomp.R
   pkg/pomp/R/rprocess-pomp.R
   pkg/pomp/R/simulate-pomp.R
   pkg/pomp/R/skeleton-pomp.R
   pkg/pomp/R/spect-match.R
   pkg/pomp/R/spect.R
   pkg/pomp/R/traj-match.R
   pkg/pomp/R/trajectory-pomp.R
   pkg/pomp/inst/NEWS
   pkg/pomp/inst/NEWS.Rd
   pkg/pomp/man/builder.Rd
Log:
- 'pompLoad' and 'pompUnload' have been removed from the export list
- all top-level functions now call 'pompLoad' on call and 'pompUnload' before exit
- in 'pompBuilder', 'link' argument has been removed
- in 'pompCBuilder', 'link' and 'save' arguments have been removed.  A new argument, 'dir', specifying the directory to use for C codes has been added; the default is to use tempdir().
- in dynamically built codes, the number of load calls is now tracked. Unloading only occurs when the number reaches zero.
- the 'pomp' object 'solibfile' slot now contains a list (one element for each separate shared-object library)

Modified: pkg/pomp/DESCRIPTION
===================================================================
--- pkg/pomp/DESCRIPTION	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/DESCRIPTION	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,8 +1,8 @@
 Package: pomp
 Type: Package
 Title: Statistical Inference for Partially Observed Markov Processes
-Version: 0.60-1
-Date: 2015-02-22
+Version: 0.61-1
+Date: 2015-02-24
 Authors at R: c(person(given=c("Aaron","A."),family="King",
 		role=c("aut","cre"),email="kingaa at umich.edu"),
 	  person(given=c("Edward","L."),family="Ionides",role=c("aut")),

Modified: pkg/pomp/NAMESPACE
===================================================================
--- pkg/pomp/NAMESPACE	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/NAMESPACE	2015-02-26 09:42:50 UTC (rev 1094)
@@ -56,7 +56,6 @@
 exportMethods(
               pomp,
               plot,show,print,coerce,summary,logLik,window,"$",
-              pompLoad,pompUnload,
               dprocess,rprocess,rmeasure,dmeasure,init.state,skeleton,
               dprior,rprior,
               data.array,obs,partrans,coef,"coef<-",

Modified: pkg/pomp/R/abc.R
===================================================================
--- pkg/pomp/R/abc.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/abc.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -36,6 +36,8 @@
   epsilon <- as.numeric(epsilon)
   epssq <- epsilon*epsilon
 
+  pompLoad(object)
+
   if (length(start)==0)
     stop(
          "abc error: ",sQuote("start")," must be specified if ",
@@ -140,6 +142,8 @@
   pars <- apply(conv.rec,2,function(x)diff(range(x))>0)
   pars <- names(pars[pars])
 
+  pompUnload(object)
+
   new(
       'abc',
       object,

Modified: pkg/pomp/R/bsmc.R
===================================================================
--- pkg/pomp/R/bsmc.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/bsmc.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -40,6 +40,8 @@
                            .getnativesymbolinfo = TRUE,
                            ...) {
 
+  pompLoad(object)
+
   gnsi.rproc <- gnsi.dmeas <- as.logical(.getnativesymbolinfo)
   ptsi.inv <- ptsi.for <- TRUE
   transform <- as.logical(transform)
@@ -335,6 +337,8 @@
   ## replace parameters with point estimate (posterior median)
   coef(object,transform=transform) <- apply(params,1,median)
 
+  pompUnload(object)
+
   new(
       "bsmcd.pomp",
       object,

Modified: pkg/pomp/R/bsmc2.R
===================================================================
--- pkg/pomp/R/bsmc2.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/bsmc2.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -15,6 +15,8 @@
                             max.fail, transform, .getnativesymbolinfo = TRUE,
                             ...) {
 
+  pompLoad(object)
+            
   gnsi.rproc <- gnsi.dmeas <- as.logical(.getnativesymbolinfo)
   ptsi.inv <- ptsi.for <- TRUE
   transform <- as.logical(transform)
@@ -216,6 +218,8 @@
   ## replace parameters with point estimate (posterior median)
   coef(object,transform=transform) <- apply(params,1,median)
 
+  pompUnload(object)
+
   new(
       "bsmcd.pomp",
       object,

Modified: pkg/pomp/R/builder.R
===================================================================
--- pkg/pomp/R/builder.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/builder.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -5,7 +5,7 @@
                          skelmap.delta.t = 1,
                          parameter.transform, parameter.inv.transform,
                          rprior, dprior,
-                         globals, ..., link = TRUE, save = FALSE) {
+                         globals, ..., save = FALSE) {
   
   if (!is.data.frame(data)) stop(sQuote("data")," must be a data-frame")
   obsnames <- names(data)
@@ -44,12 +44,10 @@
                rprior=rprior,
                dprior=dprior,
                globals=globals,
-               link=link,
-               save=save
-               ) -> bret
+               dir=if (save) getwd() else NULL
+               ) -> solib
 
-  name <- bret[1]
-  solib <- bret[2]
+  name <- solib[1]
 
   pomp(
        data=data,
@@ -75,24 +73,27 @@
        tcovar=tcovar,
        covar=covar,
        ...,
-       .solibfile=solib
+       .solibfile=list(solib)
        )
 }
 
-pompLoad.internal <- function (object, ...,
-                               verbose = getOption("verbose",FALSE)) {
+pompLoad.internal <- function (object, ..., verbose = getOption("verbose",FALSE)) {
   for (lib in object at solibfile) {
-    if (verbose) cat("loading",sQuote(lib),"\n")
-    dyn.load(lib)
+    if (!is.loaded("__pomp_load_stack_incr",PACKAGE=lib[1])) dyn.load(lib[2])
+    if (verbose) cat("loading",sQuote(lib[2]),"\n")
+    .C("__pomp_load_stack_incr",PACKAGE=lib[1])
   }
   invisible(NULL)
 }
-
-pompUnload.internal <- function (object, ...,
-                                 verbose = getOption("verbose",FALSE)) {
+ 
+pompUnload.internal <- function (object, ..., verbose = getOption("verbose",FALSE)) {
   for (lib in object at solibfile) {
-    if (verbose) cat("unloading",sQuote(lib),"\n")
-    dyn.unload(lib)
+    if (is.loaded("__pomp_load_stack_decr",PACKAGE=lib[1])) {
+      st <- .C("__pomp_load_stack_decr",st=integer(1),PACKAGE=lib[1])$st
+      stopifnot(st>=0)
+      if (st==0) dyn.unload(lib[2])
+      if (verbose) cat("unloading",sQuote(lib[2]),"\n")
+    }
   }
   invisible(NULL)
 }
@@ -120,6 +121,15 @@
 
 header <- list(
                file="/* pomp model file: {%name%} */\n\n#include <{%pompheader%}>\n#include <R_ext/Rdynload.h>\n\n",
+               stackhandling="
+static int __pomp_load_stack = 0;\n
+void __pomp_load_stack_incr (void) {
+  ++__pomp_load_stack;
+}\n
+void __pomp_load_stack_decr (int *val) {
+  *val = (--__pomp_load_stack);
+}
+",
                rmeasure="\nvoid {%name%}_rmeasure (double *__y, double *__x, double *__p, int *__obsindex, int *__stateindex, int *__parindex, int *__covindex, int __ncovars, double *__covars, double t)\n{\n",
                dmeasure= "\nvoid {%name%}_dmeasure (double *__lik, double *__y, double *__x, double *__p, int give_log, int *__obsindex, int *__stateindex, int *__parindex, int *__covindex, int __ncovars, double *__covars, double t)\n{\n",
                step.fn="\nvoid {%name%}_stepfn (double *__x, const double *__p, const int *__stateindex, const int *__parindex, const int *__covindex, int __covdim, const double *__covars, double t, double dt)\n{\n",
@@ -188,11 +198,12 @@
                           statenames, paramnames, covarnames, obsnames,
                           rmeasure, dmeasure, step.fn, skeleton,
                           parameter.transform, parameter.inv.transform,
-                          rprior, dprior, globals, save = FALSE, link = TRUE,
+                          rprior, dprior, globals, dir = NULL,
                           verbose = getOption("verbose",FALSE))
 {
 
   if (is.null(name)) name <- randomName()
+  if (is.null(dir)) dir <- tempdir()
 
   has.trans <- !(missing(parameter.transform))
 
@@ -204,7 +215,7 @@
   covarnames <- cleanForC(covarnames)
   obsnames <- cleanForC(obsnames)
 
-  stem <- if (save) name else file.path(tempdir(),name)
+  stem <- file.path(dir,name)
   if (.Platform$OS.type=="windows") {
     stem <- gsub("\\","/",stem,fixed=TRUE)
   }
@@ -222,6 +233,8 @@
   
   cat(file=out,render(header$file,name=name,pompheader=pompheader))
 
+  cat(file=out,header$stackhandling)
+
   for (f in utility.fns) {
     cat(file=out,f)
   }
@@ -325,8 +338,6 @@
     cat("model codes written to",sQuote(modelfile),
         "\nlink to shared-object library",sQuote(solib),"\n")
 
-  if (link) dyn.load(solib)
-
   invisible(c(name,solib))
 }
 

Modified: pkg/pomp/R/dmeasure-pomp.R
===================================================================
--- pkg/pomp/R/dmeasure-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/dmeasure-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,10 +1,14 @@
 ## evaluate the measurement model density function
 
 dmeasure.internal <- function (object, y, x, times, params, log = FALSE, .getnativesymbolinfo = TRUE, ...) {
-  .Call(do_dmeasure,object,y,x,times,params,log,.getnativesymbolinfo)
+  pompLoad(object)
+  rv <- .Call(do_dmeasure,object,y,x,times,params,log,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
 }
 
-setMethod("dmeasure","pomp",
+setMethod("dmeasure",
+          signature=signature("pomp"),
           function (object, y, x, times, params, log = FALSE, ...)
           dmeasure.internal(object=object,y=y,x=x,times=times,params=params,log=log,...)
           )

Modified: pkg/pomp/R/dprior-pomp.R
===================================================================
--- pkg/pomp/R/dprior-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/dprior-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -2,10 +2,14 @@
 
 dprior.internal <- function (object, params, log = FALSE,
                              .getnativesymbolinfo = TRUE, ...) {
-  .Call(do_dprior,object,params,log,.getnativesymbolinfo)
+  pompLoad(object)
+  rv <- .Call(do_dprior,object,params,log,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
 }
 
-setMethod("dprior","pomp",
+setMethod("dprior",
+          signature=signature("pomp"),
           function (object, params, log = FALSE, ...)
           dprior.internal(object=object,params=params,log=log,...)
           )

Modified: pkg/pomp/R/dprocess-pomp.R
===================================================================
--- pkg/pomp/R/dprocess-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/dprocess-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,9 +1,15 @@
 ## evaluate the process model density function
 
-dprocess.internal <- function (object, x, times, params, log = FALSE, .getnativesymbolinfo = TRUE, ...)
-  .Call(do_dprocess,object,x,times,params,log,.getnativesymbolinfo)
+dprocess.internal <- function (object, x, times, params, log = FALSE, .getnativesymbolinfo = TRUE, ...) {
+  pompLoad(object)
+  rv <- .Call(do_dprocess,object,x,times,params,log,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
+}
+  
 
-setMethod("dprocess","pomp",
-          function (object, x, times, params, log = FALSE, ...)
+setMethod("dprocess",
+          signature=signature("pomp"),
+          definition = function (object, x, times, params, log = FALSE, ...)
           dprocess.internal(object=object,x=x,times=times,params=params,log=log,...)
           )

Modified: pkg/pomp/R/init-state-pomp.R
===================================================================
--- pkg/pomp/R/init-state-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/init-state-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -3,13 +3,15 @@
 init.state.internal <- function (object, params, t0, ...) {
   if (missing(t0)) t0 <- object at t0
   if (missing(params)) params <- coef(object)
-  .Call(do_init_state,object,params,t0)
+  pompLoad(object)
+  rv <- .Call(do_init_state,object,params,t0)
+  pompUnload(object)
+  rv
 }
 
-setMethod(
-          'init.state',
-          'pomp',
-          function (object, params, t0, ...) {
+setMethod('init.state',
+          signature=signature('pomp'),
+          definition=function (object, params, t0, ...) {
             init.state.internal(object=object,params=params,t0=t0,...)
           }
           )

Modified: pkg/pomp/R/mif.R
===================================================================
--- pkg/pomp/R/mif.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/mif.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -118,6 +118,8 @@
                           .getnativesymbolinfo = TRUE,
                           ...) {
   
+  pompLoad(object)
+
   gnsi <- as.logical(.getnativesymbolinfo)
 
   transform <- as.logical(transform)
@@ -386,6 +388,8 @@
   ## back transform the parameter estimate if necessary
   if (transform) theta <- partrans(pfp,theta,dir="forward")
   
+  pompUnload(object)
+
   new(
       "mif",
       pfp,

Modified: pkg/pomp/R/minim.R
===================================================================
--- pkg/pomp/R/minim.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/minim.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,6 +1,8 @@
 minim.internal <- function(objfun, start, est, object, method, transform, verbose, ...)
 {
 
+  pompLoad(object)
+
   transform <- as.logical(transform)
   est <- as.character(est)
   
@@ -62,6 +64,8 @@
   if (transform)
     start <- partrans(object,start,dir='forward')
   
+  pompUnload(object)
+
   list(
        params=start,
        est=est,

Modified: pkg/pomp/R/nlf.R
===================================================================
--- pkg/pomp/R/nlf.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/nlf.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -59,6 +59,8 @@
                           eval.only, transform.data, ...)
 {
   
+  pompLoad(object)
+
   if (eval.only) est <- character(0)
   if (missing(start)) start <- coef(object)
   if (transform)
@@ -374,6 +376,8 @@
     opt$npts <- npts
   }
   
+  pompUnload(object)
+
   new(
       "nlfd.pomp",
       object,

Modified: pkg/pomp/R/pfilter.R
===================================================================
--- pkg/pomp/R/pfilter.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/pfilter.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -44,6 +44,8 @@
                               .transform,
                               .getnativesymbolinfo = TRUE) {
 
+  pompLoad(object)
+
   ptsi.inv <- ptsi.for <- gnsi.rproc <- gnsi.dmeas <- as.logical(.getnativesymbolinfo)
   mif2 <- as.logical(.mif2)
   transform <- as.logical(.transform)
@@ -334,6 +336,8 @@
                              msg2="%d filtering failures occurred in "),nfail),
             sQuote("pfilter"),call.=FALSE)
 
+  pompUnload(object)
+
   new(
       "pfilterd.pomp",
       object,

Modified: pkg/pomp/R/pmcmc.R
===================================================================
--- pkg/pomp/R/pmcmc.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/pmcmc.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -30,6 +30,8 @@
   gnsi <- as.logical(.getnativesymbolinfo)
   .ndone <- as.integer(.ndone)
 
+  pompLoad(object)
+
   if (missing(start))
     stop(sQuote("start")," must be specified",call.=FALSE)
   if (length(start)==0)
@@ -169,6 +171,8 @@
   pars <- apply(conv.rec,2,function(x)diff(range(x))>0)
   pars <- names(pars[pars])
 
+  pompUnload(object)
+
   new(
       "pmcmc",
       pfp,

Modified: pkg/pomp/R/pomp-class.R
===================================================================
--- pkg/pomp/R/pomp-class.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/pomp-class.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -34,7 +34,7 @@
            has.trans = 'logical',
            par.trans = 'pomp.fun',
            par.untrans = 'pomp.fun',
-           solibfile = 'character',
+           solibfile = 'list',
            userdata = 'list'
            ),
          prototype=prototype(
@@ -59,7 +59,7 @@
            has.trans=FALSE,
            par.trans=pomp.fun(),
            par.untrans=pomp.fun(),
-           solibfile=character(0),
+           solibfile=list(),
            userdata=list()
            ),
          validity=function (object) {

Modified: pkg/pomp/R/pomp.R
===================================================================
--- pkg/pomp/R/pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -17,7 +17,7 @@
   if (missing(times)) stop(sQuote("times")," is a required argument")
   if (missing(t0)) stop(sQuote("t0")," is a required argument")
   if (missing(params)) params <- numeric(0)
-  if (missing(.solibfile)) .solibfile <- character(0)
+  if (missing(.solibfile)) .solibfile <- list()
   
   if (missing(userdata)) userdata <- list()
   added.userdata <- list(...)
@@ -144,8 +144,6 @@
                                   paramnames=paramnames,
                                   covarnames=covarnames,
                                   globals=globals,
-                                  link=TRUE,
-                                  save=FALSE,
                                   verbose=verbose
                                   ),
                              snips
@@ -157,8 +155,8 @@
       stop("in ",sQuote("pomp"),": error in building shared-object library from Csnippets:\n",
            libname,call.=FALSE)
     } else {
-      .solibfile <- c(.solibfile,libname[2L])
-      libname <- libname[1L]
+      .solibfile <- c(.solibfile,list(libname))
+      libname <- libname[1]
     }
   } else {
     libname <- ''
@@ -703,6 +701,7 @@
                              parameter.inv.transform=par.untrans,
                              params=params,
                              globals=globals,
+                             .solibfile=data at solibfile,
                              userdata=data at userdata,
                              ...
                              )

Modified: pkg/pomp/R/probe-match.R
===================================================================
--- pkg/pomp/R/probe-match.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/probe-match.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -65,6 +65,8 @@
     
   function (par) {
     
+    pompLoad(object)
+
     params[par.est.idx] <- par
     
     if (transform)
@@ -82,6 +84,7 @@
                     )
     
     ll <- .Call(synth_loglik,simval,datval)
+    pompUnload(object)
     if (is.finite(ll)||is.na(fail.value)) -ll else fail.value
   }
 }
@@ -136,6 +139,8 @@
                    transform = FALSE,
                    ...) {
 
+            pompLoad(object)
+            
             if (missing(start)) start <- coef(object)
             if (missing(probes)) stop(sQuote("probes")," must be supplied")
             if (missing(nsim)) stop(sQuote("nsim")," must be supplied")
@@ -167,6 +172,8 @@
 
             coef(object) <- m$params
             
+            pompUnload(object)
+            
             new(
                 "probe.matched.pomp",
                 probe(

Modified: pkg/pomp/R/probe.R
===================================================================
--- pkg/pomp/R/probe.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/probe.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -14,6 +14,8 @@
 
 probe.internal <- function (object, probes, params, nsim = 1, seed = NULL, ...) {
 
+  pompLoad(object)
+
   if (!is.list(probes)) probes <- list(probes)
   if (!all(sapply(probes,is.function)))
     stop(sQuote("probes")," must be a function or a list of functions")
@@ -56,6 +58,8 @@
 
   coef(object) <- params
 
+  pompUnload(object)
+
   new(
       "probed.pomp",
       object,

Modified: pkg/pomp/R/rmeasure-pomp.R
===================================================================
--- pkg/pomp/R/rmeasure-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/rmeasure-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -2,10 +2,14 @@
 
 rmeasure.internal <- function (object, x, times, params,
                                .getnativesymbolinfo = TRUE, ...) {
-  .Call(do_rmeasure,object,x,times,params,.getnativesymbolinfo)
+  pompLoad(object)
+  rv <- .Call(do_rmeasure,object,x,times,params,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
 }
 
-setMethod("rmeasure","pomp",
-          function (object, x, times, params, ...)
+setMethod("rmeasure",
+          signature=signature("pomp"),
+          definition=function (object, x, times, params, ...)
           rmeasure.internal(object=object,x=x,times=times,params=params,...)
           )

Modified: pkg/pomp/R/rprior-pomp.R
===================================================================
--- pkg/pomp/R/rprior-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/rprior-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,10 +1,14 @@
 ## simulate from the prior
 
 rprior.internal <- function (object, params, .getnativesymbolinfo = TRUE, ...) {
-  .Call(do_rprior,object,params,.getnativesymbolinfo)
+  pompLoad(object)
+  rv <- .Call(do_rprior,object,params,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
 }
 
-setMethod("rprior","pomp",
-          function (object, params, ...)
+setMethod("rprior",
+          signature=signature("pomp"),
+          definition=function (object, params, ...)
           rprior.internal(object=object,params=params,...)
           )

Modified: pkg/pomp/R/rprocess-pomp.R
===================================================================
--- pkg/pomp/R/rprocess-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/rprocess-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,7 +1,12 @@
 ## simulate the process model
 
-rprocess.internal <- function (object, xstart, times, params, offset = 0, .getnativesymbolinfo = TRUE, ...)
-  .Call(do_rprocess,object,xstart,times,params,offset,.getnativesymbolinfo)
+rprocess.internal <- function (object, xstart, times, params, offset = 0, .getnativesymbolinfo = TRUE, ...) {
+  pompLoad(object)
+  rv <- .Call(do_rprocess,object,xstart,times,params,offset,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
+}  
+  
 
 setMethod(
           "rprocess",

Modified: pkg/pomp/R/simulate-pomp.R
===================================================================
--- pkg/pomp/R/simulate-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/simulate-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -5,6 +5,7 @@
                                times, t0, as.data.frame = FALSE,
                                include.data = FALSE,
                                .getnativesymbolinfo = TRUE, ...) {
+  pompLoad(object)
 
   if (missing(times))
     times <- time(object,t0=FALSE)
@@ -122,6 +123,8 @@
 
   }
 
+  pompUnload(object)
+
   retval
 }
 

Modified: pkg/pomp/R/skeleton-pomp.R
===================================================================
--- pkg/pomp/R/skeleton-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/skeleton-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,10 +1,14 @@
 ## evaluate the deterministic skeleton
 
 skeleton.internal <- function (object, x, t, params, .getnativesymbolinfo = TRUE, ...) {
-  .Call(do_skeleton,object,x,t,params,.getnativesymbolinfo)
+  pompLoad(object)
+  rv <- .Call(do_skeleton,object,x,t,params,.getnativesymbolinfo)
+  pompUnload(object)
+  rv
 }
 
-setMethod("skeleton","pomp",
-          function (object, x, t, params, ...)
+setMethod("skeleton",
+          signature=signature("pomp"),
+          definition=function (object, x, t, params, ...)
           skeleton.internal(object=object,x=x,t=t,params=params,...)
           )

Modified: pkg/pomp/R/spect-match.R
===================================================================
--- pkg/pomp/R/spect-match.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/spect-match.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -20,6 +20,8 @@
   if (missing(est)) est <- integer(0)
   if (missing(params)) params <- coef(object)
   
+  pompLoad(object)
+
   params[est] <- par
   
   ## vector of frequencies and estimated power spectum of data
@@ -55,6 +57,7 @@
     mismatch <- sum(discrep) 
   }
 
+  pompUnload(object)
   mismatch
 }
 
@@ -67,6 +70,8 @@
                         verbose = getOption("verbose"),
                         eval.only = FALSE, fail.value = NA, ...) {
 
+  pompLoad(object)
+
   obj.fn <- spect.mismatch
 
   if (!is(object,"pomp"))
@@ -213,6 +218,8 @@
     msg <- opt$message
   }
 
+  pompUnload(object)
+
   new(
       "spect.matched.pomp",
       spect(

Modified: pkg/pomp/R/spect.R
===================================================================
--- pkg/pomp/R/spect.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/spect.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -144,6 +144,8 @@
                     detrend = c("none","mean","linear","quadratic"),
                     ...) {
 
+            pompLoad(object)
+            
             if (missing(params)) params <- coef(object)
 
             if (missing(vars))
@@ -199,6 +201,8 @@
 
             coef(object) <- params
 
+            pompUnload(object)
+            
             new(
                 "spect.pomp",
                 object,

Modified: pkg/pomp/R/traj-match.R
===================================================================
--- pkg/pomp/R/traj-match.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/traj-match.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -48,6 +48,7 @@
     stop("parameter(s): ",sQuote(est[is.na(par.est.idx)])," not found in ",sQuote("params"))
 
   function (par) {
+    pompLoad(object)
     params[par.est.idx] <- par
     if (transform)
       tparams <- partrans(object,params,dir="forward")
@@ -63,6 +64,7 @@
                   params=if (transform) tparams else params,
                   log=TRUE
                   )
+    pompUnload(object)
     -sum(d)
   }
 }

Modified: pkg/pomp/R/trajectory-pomp.R
===================================================================
--- pkg/pomp/R/trajectory-pomp.R	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/R/trajectory-pomp.R	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,5 +1,7 @@
 trajectory.internal <- function (object, params, times, t0, as.data.frame = FALSE, .getnativesymbolinfo = TRUE, ...) {
 
+  pompLoad(object)
+  
   if (missing(times))
     times <- time(object,t0=FALSE)
   else
@@ -111,6 +113,8 @@
     x$traj <- factor(x$traj)
   }
 
+  pompUnload(object)
+
   x
 }
 

Modified: pkg/pomp/inst/NEWS
===================================================================
--- pkg/pomp/inst/NEWS	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/inst/NEWS	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,5 +1,13 @@
 _N_e_w_s _f_o_r _p_a_c_k_a_g_e '_p_o_m_p'
 
+_C_h_a_n_g_e_s _i_n '_p_o_m_p' _v_e_r_s_i_o_n _0._6_1-_1:
+
+        • When using ‘Csnippet’s or ‘pompBuilder’, it is no longer
+          necessary to manually load and unload the dynamically
+          loadable library.  This is now handled automatically.
+          Accordingly, the ‘link’ argument of ‘pompBuilder’ and the
+          ‘pompLoad’ and ‘pompUnload’ functions have been removed.
+
 _C_h_a_n_g_e_s _i_n '_p_o_m_p' _v_e_r_s_i_o_n _0._6_0-_1:
 
         • ‘pmcmc’ and ‘abc’ can now use arbitrary symmetric proposal

Modified: pkg/pomp/inst/NEWS.Rd
===================================================================
--- pkg/pomp/inst/NEWS.Rd	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/inst/NEWS.Rd	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,5 +1,12 @@
 \name{NEWS}
 \title{News for package `pomp'}
+\section{Changes in \pkg{pomp} version 0.61-1}{
+  \itemize{
+    \item When using \code{Csnippet}s or \code{pompBuilder}, it is no longer necessary to manually load and unload the dynamically loadable library.
+    This is now handled automatically.
+    Accordingly, the \code{link} argument of \code{pompBuilder} and the \code{pompLoad} and \code{pompUnload} functions have been removed.
+  }
+}
 \section{Changes in \pkg{pomp} version 0.60-1}{
   \itemize{
     \item \code{pmcmc} and \code{abc} can now use arbitrary symmetric proposal distributions via the \code{proposal} argument.

Modified: pkg/pomp/man/builder.Rd
===================================================================
--- pkg/pomp/man/builder.Rd	2015-02-25 12:18:35 UTC (rev 1093)
+++ pkg/pomp/man/builder.Rd	2015-02-26 09:42:50 UTC (rev 1094)
@@ -1,6 +1,6 @@
 \name{pompBuilder}
 \alias{pompBuilder}
-\title{Write, compile, link, and build a pomp object using native codes}
+\title{Write, compile, and build a pomp object using native codes}
 \description{
   \code{pompBuilder} is a facility for producing compiled \code{pomp} objects.
 }
@@ -11,8 +11,7 @@
             skeleton, skeleton.type = c("map","vectorfield"),
             skelmap.delta.t = 1,
             parameter.transform, parameter.inv.transform,
-            rprior, dprior,
-            globals, \dots, link = TRUE, save = FALSE)
+            rprior, dprior, globals, \dots, save = FALSE)
 }
 \arguments{
   \item{data, times, t0}{
@@ -58,9 +57,6 @@
   \item{\dots}{
     additional arguments are passed to \code{\link{pomp}}
   }
-  \item{link}{
-    logical; if TRUE, the resulting code will be linked after compilation.
-  }
   \item{save}{
     logical; if TRUE, the resulting C code will be saved in the current working directory.
     The shared-object library will also be created in this directory.
@@ -70,16 +66,13 @@
 \value{
   The constructed \code{pomp} object.
   A side-effect is the writing and compilation of a C code into a dynamics shared object.
-  These files will reside in the current working directory (see \code{\link{getwd}}).
-  If \code{pompBuilder} has been called with \code{link=FALSE}, this dynamic shared object must be linked (see \code{\link{dyn.load}}) before the \code{pomp} object can be used.
 
   \strong{Parallel computing caution:}
   note that, since a side-effect of running \code{pompBuilder} is the writing and compilation of a file, caution must be used when running parallel computations.
   Simultaneous execution of \code{pompBuilder} on nodes sharing a common disk will cause all nodes to attempt to write the same file at the same time;
   the results will be undefined.
-  If multiple nodes are to work on the same \code{pomp} object built by \code{pompBuilder}, first run \code{pompBuilder} once (perhaps with \code{link=FALSE}) to write the C file and compile it into a dynamic shared object file.
+  If multiple nodes are to work on the same \code{pomp} object built by \code{pompBuilder}, first run \code{pompBuilder} once (with \code{save = TRUE}) to write the C file and compile it into a dynamic shared object file.
   The \code{pomp} object returned by \code{pompBuilder} can then be shared with all worker nodes.
-  Note, however, that all worker nodes must dynamically load (using \code{\link{dyn.load}}) the dynamic shared object file before anything can be done with the \code{pomp} object.
 }
 \details{
   \code{pompBuilder} with \code{save=TRUE} assumes that files can be written to the current working directory and that dynamic shared objects can be compiled and linked, i.e., that \code{R CMD SHLIB} will work.



More information about the pomp-commits mailing list