[Pomp-commits] r894 - in pkg/pomp: . R inst tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Mar 17 23:02:29 CET 2014


Author: kingaa
Date: 2014-03-17 23:02:29 +0100 (Mon, 17 Mar 2014)
New Revision: 894

Added:
   pkg/pomp/R/generics.R
   pkg/pomp/tests/demos.R
Modified:
   pkg/pomp/DESCRIPTION
   pkg/pomp/R/aaa.R
   pkg/pomp/R/abc-methods.R
   pkg/pomp/R/abc.R
   pkg/pomp/R/bsmc.R
   pkg/pomp/R/compare-pmcmc.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/particles-mif.R
   pkg/pomp/R/pfilter.R
   pkg/pomp/R/pmcmc.R
   pkg/pomp/R/pomp-class.R
   pkg/pomp/R/pomp-methods.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/skeleton-pomp.R
   pkg/pomp/R/spect.R
   pkg/pomp/R/traj-match.R
   pkg/pomp/R/trajectory-pomp.R
   pkg/pomp/inst/NEWS
Log:
- fix bug in 'abc' to do with parameter transformation
- move all generic declarations to 'generics.R'
- add new test of demos


Modified: pkg/pomp/DESCRIPTION
===================================================================
--- pkg/pomp/DESCRIPTION	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/DESCRIPTION	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,7 +1,7 @@
 Package: pomp
 Type: Package
 Title: Statistical inference for partially observed Markov processes
-Version: 0.48-2
+Version: 0.48-3
 Date: 2014-03-17
 Authors at R: c(person(given=c("Aaron","A."),family="King",
 		role=c("aut","cre"),email="kingaa at umich.edu"),
@@ -23,8 +23,8 @@
 LazyData: true
 BuildVignettes: true
 MailingList: Subscribe to pomp-announce at r-forge.r-project.org for announcements by going to http://lists.r-forge.r-project.org/mailman/listinfo/pomp-announce.
-Collate: aaa.R authors.R version.R eulermultinom.R plugins.R 
-	 parmat.R logmeanexp.R slice-design.R 
+Collate: aaa.R authors.R generics.R version.R eulermultinom.R
+	 plugins.R parmat.R logmeanexp.R slice-design.R 
 	 profile-design.R sobol.R bsplines.R sannbox.R
 	 pomp-fun.R pomp-class.R pomp.R pomp-methods.R 
 	 rmeasure-pomp.R rprocess-pomp.R init-state-pomp.R 

Modified: pkg/pomp/R/aaa.R
===================================================================
--- pkg/pomp/R/aaa.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/aaa.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -5,22 +5,6 @@
 ##   packageStartupMessage("This is pomp version ",version,"\n")
 ## }
 
-setGeneric("print",function(x,...)standardGeneric("print"))
-setGeneric("plot",function(x,y,...)standardGeneric("plot"))
-setGeneric("summary",function(object,...)standardGeneric("summary"))
-setGeneric("simulate",function(object,nsim=1,seed=NULL,...)standardGeneric("simulate"))
-setGeneric("time",function(x,...)standardGeneric("time"))
-setGeneric("coef",function(object,...)standardGeneric("coef"))
-setGeneric("logLik",function(object,...)standardGeneric("logLik"))
-setGeneric("window",function(x,...)standardGeneric("window"))
-setGeneric("continue",function(object,...)standardGeneric("continue"))
-setGeneric("pred.mean",function(object,...)standardGeneric("pred.mean"))
-setGeneric("pred.var",function(object,...)standardGeneric("pred.var"))
-setGeneric("filter.mean",function(object,...)standardGeneric("filter.mean"))
-setGeneric("cond.logLik",function(object,...)standardGeneric("cond.logLik"))
-setGeneric("eff.sample.size",function(object,...)standardGeneric("eff.sample.size"))
-setGeneric("conv.rec",function(object,...)standardGeneric("conv.rec"))
-
 if (!exists("paste0",where="package:base")) {
   paste0 <- function(...) paste(...,sep="")
 }

Modified: pkg/pomp/R/abc-methods.R
===================================================================
--- pkg/pomp/R/abc-methods.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/abc-methods.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -19,7 +19,7 @@
             if (scatter) {
               pairs(conv.rec(x, pars))
             } else {
-              plot.ts(conv.rec(x,pars),main="Convergence record")
+              plot.ts(conv.rec(x,pars),...)
             }
           }
           )

Modified: pkg/pomp/R/abc.R
===================================================================
--- pkg/pomp/R/abc.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/abc.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -14,9 +14,6 @@
            )
          )
 
-## ABC algorithm functions
-setGeneric('abc',function(object,...)standardGeneric("abc"))
-
 abc.internal <- function (object, Nabc,
                           start, pars,
                           rw.sd, probes,
@@ -100,7 +97,8 @@
   }
 
   theta <- start
-  log.prior <- dprior(object,params=theta,log=TRUE)
+  log.prior <- dprior(object,params=theta,log=TRUE,
+                      .getnativesymbolinfo=gnsi)
   ## we suppose that theta is a "match", which does the right thing for continue() and
   ## should have negligible effect unless doing many short calls to continue()
 
@@ -126,10 +124,8 @@
          )
   }
 
-  po <- as(object,"pomp")
-  
   ## apply probes to data
-  datval <- try(.Call(apply_probe_data,po,probes),silent=FALSE)
+  datval <- try(.Call(apply_probe_data,object,probes),silent=FALSE)
   if (inherits(datval,'try-error'))
     stop("abc error: error in ",sQuote("apply_probe_data"),call.=FALSE)
 
@@ -138,14 +134,25 @@
   for (n in seq_len(Nabc)) { # main loop
 
     theta.prop <- theta
+
+    if (transform)
+      theta.prop <- partrans(object,params=theta.prop,dir='inverse',
+                             .getnativesymbolinfo=gnsi)
+
     theta.prop[pars] <- rnorm(n=length(pars),mean=theta.prop[pars],sd=rw.sd)
 
+    if (transform)
+      theta.prop <- partrans(object,params=theta.prop,dir='forward',
+                             .getnativesymbolinfo=gnsi)
+
+    gnsi <- FALSE
+
     ## compute the probes for the proposed new parameter values
 
     simval <- try(
                   .Call(
                         apply_probe_sim,
-                        object=po,
+                        object=object,
                         nsim=1,
                         params=theta.prop,
                         seed=NULL,
@@ -177,7 +184,7 @@
 
   new(
       'abc',
-      po,
+      object,
       params=theta,
       pars=pars,
       transform=transform,
@@ -205,19 +212,23 @@
               start <- coef(object)
 
             if (missing(rw.sd))
-              stop("abc error: ",sQuote("rw.sd")," must be specified",call.=FALSE)
+              stop("abc error: ",sQuote("rw.sd")," must be specified",
+                   call.=FALSE)
 
             if (missing(pars))
               pars <- names(rw.sd)[rw.sd>0]
 
             if (missing(probes))
-              stop("abc error: ",sQuote("probes")," must be specified",call.=FALSE)
+              stop("abc error: ",sQuote("probes")," must be specified",
+                   call.=FALSE)
 
             if (missing(scale))
-              stop("abc error: ",sQuote("scale")," must be specified",call.=FALSE)
+              stop("abc error: ",sQuote("scale")," must be specified",
+                   call.=FALSE)
 
             if (missing(epsilon))
-              stop("abc error: abc match criterion, ",sQuote("epsilon"),", must be specified",call.=FALSE)
+              stop("abc error: abc match criterion, ",sQuote("epsilon"),
+                   ", must be specified",call.=FALSE)
 
             abc.internal(
                          object=object,
@@ -243,13 +254,13 @@
                     ...) {
 
             if (missing(probes)) probes <- object at probes
-
-            abc(
-                object=as(object,"pomp"),
-                probes=probes,
-                transform=transform,
-                ...
-                )
+            f <- selectMethod("abc","pomp")
+            f(
+              object=object,
+              probes=probes,
+              transform=transform,
+              ...
+              )
           }
           )
 
@@ -272,19 +283,21 @@
             if (missing(epsilon)) epsilon <- object at epsilon
             if (missing(transform)) transform <- object at transform
 
-            abc(
-                object=as(object,"pomp"),
-                Nabc=Nabc,
-                start=start,
-                pars=pars,
-                rw.sd=rw.sd,
-                probes=probes,
-                scale=scale,
-                epsilon=epsilon,
-                verbose=verbose,
-                transform=transform,
-                ...
-                )
+            f <- selectMethod("abc","pomp")
+
+            f(
+              object=object,
+              Nabc=Nabc,
+              start=start,
+              pars=pars,
+              rw.sd=rw.sd,
+              probes=probes,
+              scale=scale,
+              epsilon=epsilon,
+              verbose=verbose,
+              transform=transform,
+              ...
+              )
           }
           )
 
@@ -294,13 +307,14 @@
           function (object, Nabc = 1, ...) {
 
             ndone <- object at Nabc
+            f <- selectMethod("abc","abc")
             
-            obj <- abc(
-                       object=object,
-                       Nabc=Nabc,
-                       .ndone=ndone,
-                       ...
-                       )
+            obj <- f(
+                     object=object,
+                     Nabc=Nabc,
+                     .ndone=ndone,
+                     ...
+                     )
             
             obj at conv.rec <- rbind(
                                   object at conv.rec[,colnames(obj at conv.rec)],

Modified: pkg/pomp/R/bsmc.R
===================================================================
--- pkg/pomp/R/bsmc.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/bsmc.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -29,8 +29,6 @@
            )
          )
 
-setGeneric("bsmc",function(object,...)standardGeneric("bsmc"))
-
 bsmc.internal <- function (object, params, Np, est,
                            smooth = 0.1,
                            ntries = 1,

Modified: pkg/pomp/R/compare-pmcmc.R
===================================================================
--- pkg/pomp/R/compare-pmcmc.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/compare-pmcmc.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -99,5 +99,3 @@
   }
   invisible(NULL)
 }
-
-

Modified: pkg/pomp/R/dmeasure-pomp.R
===================================================================
--- pkg/pomp/R/dmeasure-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/dmeasure-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,5 +1,4 @@
 ## evaluate the measurement model density function
-setGeneric("dmeasure",function(object,...)standardGeneric("dmeasure"))
 
 dmeasure.internal <- function (object, y, x, times, params, log = FALSE, .getnativesymbolinfo = TRUE, ...) {
   .Call(do_dmeasure,object,y,x,times,params,log,.getnativesymbolinfo)

Modified: pkg/pomp/R/dprior-pomp.R
===================================================================
--- pkg/pomp/R/dprior-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/dprior-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,5 +1,4 @@
 ## evaluate the prior probability density
-setGeneric("dprior",function(object,...)standardGeneric("dprior"))
 
 dprior.internal <- function (object, params, log = FALSE,
                              .getnativesymbolinfo = TRUE, ...) {

Modified: pkg/pomp/R/dprocess-pomp.R
===================================================================
--- pkg/pomp/R/dprocess-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/dprocess-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,5 +1,4 @@
 ## evaluate the process model density function
-setGeneric("dprocess",function(object,...)standardGeneric("dprocess"))
 
 dprocess.internal <- function (object, x, times, params, log = FALSE, .getnativesymbolinfo = TRUE, ...)
   .Call(do_dprocess,object,x,times,params,log,.getnativesymbolinfo)

Added: pkg/pomp/R/generics.R
===================================================================
--- pkg/pomp/R/generics.R	                        (rev 0)
+++ pkg/pomp/R/generics.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -0,0 +1,79 @@
+## basic constructor
+setGeneric("pomp",function(data,...)standardGeneric("pomp"))
+
+setGeneric("print",function(x,...)standardGeneric("print"))
+setGeneric("plot",function(x,y,...)standardGeneric("plot"))
+setGeneric("summary",function(object,...)standardGeneric("summary"))
+setGeneric("window",function(x,...)standardGeneric("window"))
+
+## constituent components of a 'pomp' object
+setGeneric("dmeasure",function(object,...)standardGeneric("dmeasure"))
+setGeneric("rmeasure",function(object,...)standardGeneric("rmeasure"))
+setGeneric("dprocess",function(object,...)standardGeneric("dprocess"))
+setGeneric("rprocess",function(object,...)standardGeneric("rprocess"))
+setGeneric("dprior",function(object,...)standardGeneric("dprior"))
+setGeneric("rprior",function(object,...)standardGeneric("rprior"))
+setGeneric("init.state",function(object,...)standardGeneric("init.state"))
+setGeneric("skeleton",function(object,...)standardGeneric("skeleton"))
+
+## functions to extract or call the components of a "pomp" object
+setGeneric("obs",function(object,...)standardGeneric("obs"))
+setGeneric("data.array",function(object,...)standardGeneric("data.array"))
+setGeneric("time",function(x,...)standardGeneric("time"))
+setGeneric("time<-",function(object,...,value)standardGeneric("time<-"))  
+setGeneric("coef",function(object,...)standardGeneric("coef"))
+setGeneric("coef<-",function(object,...,value)standardGeneric("coef<-"))
+setGeneric("states",function(object,...)standardGeneric("states"))
+setGeneric("timezero",function(object,...)standardGeneric("timezero"))
+setGeneric("timezero<-",function(object,...,value)standardGeneric("timezero<-"))
+setGeneric("partrans",function(object,params,dir=c("forward","inverse"),...)standardGeneric("partrans"))
+setGeneric("logLik",function(object,...)standardGeneric("logLik"))
+
+## prediction mean
+setGeneric("pred.mean",function(object,...)standardGeneric("pred.mean"))
+## prediction variance
+setGeneric("pred.var",function(object,...)standardGeneric("pred.var"))
+## filter mean
+setGeneric("filter.mean",function(object,...)standardGeneric("filter.mean"))
+## conditional log likelihood
+setGeneric("cond.logLik",function(object,...)standardGeneric("cond.logLik"))
+## effective sample size
+setGeneric("eff.sample.size",function(object,...)standardGeneric("eff.sample.size"))
+## convergence record
+setGeneric("conv.rec",function(object,...)standardGeneric("conv.rec"))
+
+## stochastic simulation
+setGeneric("simulate",function(object,nsim=1,seed=NULL,...)standardGeneric("simulate"))
+
+## deterministic trajectory computation
+setGeneric("trajectory",function(object,...)standardGeneric("trajectory"))
+## trajectory matching
+setGeneric("traj.match",function(object,...)standardGeneric("traj.match"))
+
+## ABC algorithm functions
+setGeneric('abc',function(object,...)standardGeneric("abc"))
+
+## Bayesian SMC (Liu & West)
+setGeneric("bsmc",function(object,...)standardGeneric("bsmc"))
+
+## basic SMC (particle filter)
+setGeneric("pfilter",function(object,...)standardGeneric("pfilter"))
+
+## particle Markov chain Monte Carlo (PMCMC)
+setGeneric('pmcmc',function(object,...)standardGeneric("pmcmc"))
+
+## iterated filtering
+setGeneric('mif',function(object,...)standardGeneric("mif"))
+## generate new particles
+setGeneric('particles',function(object,...)standardGeneric("particles"))
+
+## synthetic likelihood
+setGeneric("probe",function(object,probes,...)standardGeneric("probe"))
+## probe matching
+setGeneric("probe.match",function(object,...)standardGeneric("probe.match"))
+
+## power spectrum
+setGeneric("spect",function(object,...)standardGeneric("spect"))
+
+## continue an iteration
+setGeneric("continue",function(object,...)standardGeneric("continue"))

Modified: pkg/pomp/R/init-state-pomp.R
===================================================================
--- pkg/pomp/R/init-state-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/init-state-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,12 +1,11 @@
 ## initialize the state variables of the process model
+
 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)
 }
 
-setGeneric("init.state",function(object,...)standardGeneric("init.state"))
-
 setMethod(
           'init.state',
           'pomp',

Modified: pkg/pomp/R/mif.R
===================================================================
--- pkg/pomp/R/mif.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/mif.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -386,8 +386,6 @@
       )
 }
 
-setGeneric('mif',function(object,...)standardGeneric("mif"))
-
 setMethod(
           "mif",
           signature=signature(object="pomp"),

Modified: pkg/pomp/R/particles-mif.R
===================================================================
--- pkg/pomp/R/particles-mif.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/particles-mif.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -30,8 +30,6 @@
   x
 }
 
-setGeneric('particles',function(object,...)standardGeneric("particles"))
-
 setMethod("particles",signature=signature(object="mif"),
           function (object, Np = 1, center = coef(object), sd = 0, ...) {
             particles.internal(object=object,Np=Np,center=center,sd=sd,...)

Modified: pkg/pomp/R/pfilter.R
===================================================================
--- pkg/pomp/R/pfilter.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/pfilter.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -341,9 +341,6 @@
       )
 }
 
-## generic particle filter
-setGeneric("pfilter",function(object,...)standardGeneric("pfilter"))
-
 setMethod(
           "pfilter",
           signature=signature(object="pomp"),

Modified: pkg/pomp/R/pmcmc.R
===================================================================
--- pkg/pomp/R/pmcmc.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/pmcmc.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -12,9 +12,6 @@
                         )
          )
 
-## PMCMC algorithm functions
-setGeneric('pmcmc',function(object,...)standardGeneric("pmcmc"))
-
 pmcmc.internal <- function (object, Nmcmc,
                             start, pars,
                             rw.sd, Np,

Modified: pkg/pomp/R/pomp-class.R
===================================================================
--- pkg/pomp/R/pomp-class.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/pomp-class.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,6 +1,3 @@
-## as of version 0.37-1 'pomp' is a generic function
-setGeneric("pomp",function(data,...)standardGeneric("pomp"))
-
 ## this is the initial-condition setting function that is used by default
 ## it simply finds all parameters in the vector 'params' that have a name ending in '.0'
 ## and returns a vector with their values with names stripped of '.0'

Modified: pkg/pomp/R/pomp-methods.R
===================================================================
--- pkg/pomp/R/pomp-methods.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/pomp-methods.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,15 +1,5 @@
 ## this file contains some basic methods definitions
 
-## functions to extract or call the components of a "pomp" object
-setGeneric("data.array",function(object,...)standardGeneric("data.array"))
-setGeneric("obs",function(object,...)standardGeneric("obs"))
-setGeneric("time<-",function(object,...,value)standardGeneric("time<-"))  
-setGeneric("coef<-",function(object,...,value)standardGeneric("coef<-"))
-setGeneric("states",function(object,...)standardGeneric("states"))
-setGeneric("timezero",function(object,...)standardGeneric("timezero"))
-setGeneric("timezero<-",function(object,...,value)standardGeneric("timezero<-"))
-setGeneric("partrans",function(object,params,dir=c("forward","inverse"),...)standardGeneric("partrans"))
-
 ## 'coerce' method: allows for coercion of a "pomp" object to a data-frame
 setAs(
       from="pomp",

Modified: pkg/pomp/R/probe-match.R
===================================================================
--- pkg/pomp/R/probe-match.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/probe-match.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -169,8 +169,6 @@
       )
 }
 
-setGeneric("probe.match",function(object,...)standardGeneric("probe.match"))
-
 setMethod(
           "probe.match",
           signature=signature(object="pomp"),

Modified: pkg/pomp/R/probe.R
===================================================================
--- pkg/pomp/R/probe.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/probe.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -63,8 +63,6 @@
       )
 }
 
-setGeneric("probe",function(object,probes,...)standardGeneric("probe"))
-
 setMethod("probe",signature(object="pomp"),
           function (object, probes, params, nsim = 1, seed = NULL, ...) {
             probe.internal(object=object,probes=probes,params=params,

Modified: pkg/pomp/R/rmeasure-pomp.R
===================================================================
--- pkg/pomp/R/rmeasure-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/rmeasure-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,7 +1,5 @@
 ## simulate the measurement model
 
-setGeneric("rmeasure",function(object,...)standardGeneric("rmeasure"))
-
 rmeasure.internal <- function (object, x, times, params,
                                .getnativesymbolinfo = TRUE, ...) {
   .Call(do_rmeasure,object,x,times,params,.getnativesymbolinfo)

Modified: pkg/pomp/R/rprior-pomp.R
===================================================================
--- pkg/pomp/R/rprior-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/rprior-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,7 +1,5 @@
 ## simulate from the prior
 
-setGeneric("rprior",function(object,...)standardGeneric("rprior"))
-
 rprior.internal <- function (object, params, .getnativesymbolinfo = TRUE, ...) {
   .Call(do_rprior,object,params,.getnativesymbolinfo)
 }

Modified: pkg/pomp/R/rprocess-pomp.R
===================================================================
--- pkg/pomp/R/rprocess-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/rprocess-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,7 +1,5 @@
 ## simulate the process model
 
-setGeneric("rprocess",function(object,...)standardGeneric("rprocess"))
-
 rprocess.internal <- function (object, xstart, times, params, offset = 0, .getnativesymbolinfo = TRUE, ...)
   .Call(do_rprocess,object,xstart,times,params,offset,.getnativesymbolinfo)
 

Modified: pkg/pomp/R/skeleton-pomp.R
===================================================================
--- pkg/pomp/R/skeleton-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/skeleton-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,5 +1,4 @@
 ## evaluate the deterministic skeleton
-setGeneric("skeleton",function(object,...)standardGeneric("skeleton"))
 
 skeleton.internal <- function (object, x, t, params, .getnativesymbolinfo = TRUE, ...) {
   .Call(do_skeleton,object,x,t,params,.getnativesymbolinfo)

Modified: pkg/pomp/R/spect.R
===================================================================
--- pkg/pomp/R/spect.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/spect.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -136,8 +136,6 @@
   simspec
 }
 
-setGeneric("spect",function(object,...)standardGeneric("spect"))
-
 setMethod(
           "spect",
           signature(object="pomp"),

Modified: pkg/pomp/R/traj-match.R
===================================================================
--- pkg/pomp/R/traj-match.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/traj-match.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -151,8 +151,6 @@
 traj.match <- function (object, ...)
   stop("function ",sQuote("traj.match")," is undefined for objects of class ",sQuote(class(object)))
 
-setGeneric("traj.match")
-
 setMethod(
           "traj.match",
           signature=signature(object="pomp"),

Modified: pkg/pomp/R/trajectory-pomp.R
===================================================================
--- pkg/pomp/R/trajectory-pomp.R	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/R/trajectory-pomp.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,5 +1,3 @@
-setGeneric("trajectory",function(object,...)standardGeneric("trajectory"))
-
 trajectory.internal <- function (object, params, times, t0, as.data.frame = FALSE, .getnativesymbolinfo = TRUE, ...) {
 
   if (missing(times))

Modified: pkg/pomp/inst/NEWS
===================================================================
--- pkg/pomp/inst/NEWS	2014-03-17 16:10:44 UTC (rev 893)
+++ pkg/pomp/inst/NEWS	2014-03-17 22:02:29 UTC (rev 894)
@@ -1,4 +1,7 @@
 NEWS
+0.48-3
+     o	Correct a bug in 'abc' to do with parameter transformation.
+
 0.48-1
      o	Create new 'dprior' and 'rprior' slots for 'pomp' objects.
      	These will be used by the Bayesian methods (currently 'abc', 'bsmc', and 'pmcmc').

Added: pkg/pomp/tests/demos.R
===================================================================
--- pkg/pomp/tests/demos.R	                        (rev 0)
+++ pkg/pomp/tests/demos.R	2014-03-17 22:02:29 UTC (rev 894)
@@ -0,0 +1,18 @@
+if (Sys.getenv("POMP_FULL_TESTS")=="yes") {
+
+  library(pomp)
+
+  pdf.options(useDingbats=FALSE)
+  pdf(file="demos.pdf")
+
+  set.seed(47575684)
+
+  demos <- list.files(path=system.file("demo",package="pomp"),pattern=".\\.R$",full.names=TRUE)
+
+  for (d in demos) {
+    source(d,local=TRUE,echo=TRUE)
+  }
+
+  dev.off()
+
+}



More information about the pomp-commits mailing list