[Pomp-commits] r1210 - in pkg/pompExamples: . R inst/examples tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed Jun 17 14:56:45 CEST 2015


Author: kingaa
Date: 2015-06-17 14:56:44 +0200 (Wed, 17 Jun 2015)
New Revision: 1210

Modified:
   pkg/pompExamples/DESCRIPTION
   pkg/pompExamples/R/pertussis.R
   pkg/pompExamples/inst/examples/bbp.R
   pkg/pompExamples/inst/examples/bsflu.R
   pkg/pompExamples/inst/examples/bsflu3.R
   pkg/pompExamples/inst/examples/budmoth.R
   pkg/pompExamples/inst/examples/parus.R
   pkg/pompExamples/tests/bbp.Rout.save
   pkg/pompExamples/tests/budmoth.Rout.save
   pkg/pompExamples/tests/ebola.Rout.save
   pkg/pompExamples/tests/parus.Rout.save
   pkg/pompExamples/tests/pertussis.R
   pkg/pompExamples/tests/pertussis.Rout.save
Log:
- bring pompExamples up to date

Modified: pkg/pompExamples/DESCRIPTION
===================================================================
--- pkg/pompExamples/DESCRIPTION	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/DESCRIPTION	2015-06-17 12:56:44 UTC (rev 1210)
@@ -16,7 +16,7 @@
 	  person(given=c("Helen"),family="Wearing",role=c("ctb")))
 URL: http://pomp.r-forge.r-project.org
 Description: More 'pomp' examples.
-Depends: R(>= 3.0.0), stats, graphics, pomp(>= 0.58-6)
+Depends: R(>= 3.0.0), stats, graphics, pomp(>= 0.65-1)
 Suggests: plyr, reshape2, ggplot2, knitr, markdown
 LinkingTo: pomp
 Additional_repositories: http://r-forge.r-rproject.org

Modified: pkg/pompExamples/R/pertussis.R
===================================================================
--- pkg/pompExamples/R/pertussis.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/R/pertussis.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -15,117 +15,119 @@
     invisible(datasets)
   } else {
     which <- as.character(substitute(which))
-    simulate(
-             pomp(
-                  data=data.frame(time=seq(from=0,to=20,by=1/52),reports=NA),
-                  times="time",
-                  t0=-1/52,
-                  params=switch(
-                    which,
-                    SEIR.small=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=450, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0, alpha.ratio=1,
-                      report.prob=0.3, boost.prob=0, polar.prob=0, foi.mod=0,
-                      popsize=5e+5, noise.sigma=0, tau=0.01,
-                      S.0=0.0574148031949802, E.0=0.0004081763321755, I.0=0.00067028956509212,
-                      R1.0=0.941506730907752, R2.0=0),
-                    SEIR.big=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=450, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0, alpha.ratio=1,
-                      report.prob=0.3, boost.prob=0, polar.prob=0, foi.mod=0,
-                      popsize=5e+6, noise.sigma=0, tau=0.01,
-                      S.0=0.0515635231482973, E.0=0.000437143470487014, I.0=0.000734641109212043,
-                      R1.0=0.947264692272004, R2.0=0),
-                    SEIRS.small=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.1, boost.prob=0, polar.prob=0, foi.mod=0,
-                      popsize=5e+5, noise.sigma=0, tau=0.01,
-                      S.0=0.157360395940609, E.0=0.000837874318852172, I.0=0.00124181372794081,
-                      R1.0=0.45913512973054, R2.0=0.381424786282058),
-                    SEIRS.big=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.1, boost.prob=0, polar.prob=0, foi.mod=0,
-                      popsize=5e+6, noise.sigma=0, tau=0.01,
-                      S.0=0.157398354546347, E.0=0.00132093662562661, I.0=0.0022558671035406,
-                      R1.0=0.457185201591761, R2.0=0.381839640132725),
-                    SEIRR.small=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.11, boost.prob=0.75, polar.prob=0, foi.mod=0.5,
-                      popsize=5e+5, noise.sigma=0, tau=0.01,
-                      S.0=0.128943112158304, E.0=0.00068688724266688, I.0=0.00114414648269803,
-                      R1.0=0.638074319602244, R2.0=0.231151534514087),
-                    SEIRR.big=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.11, boost.prob=0.75, polar.prob=0, foi.mod=0.5,
-                      popsize=5e+6, noise.sigma=0, tau=0.01,
-                      S.0=0.127128689912424, E.0=0.00126497004491763, I.0=0.00216092385991776,
-                      R1.0=0.639879739889535, R2.0=0.229565676293206),
-                    full.small=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.1, boost.prob=0.75, polar.prob=0.1, foi.mod=0.5,
-                      popsize=5e+5, noise.sigma=0.01, tau=0.01,
-                      S.0=0.132553922599906, E.0=0.0010539075727066, I.0=0.00166100642162314,
-                      R1.0=0.641737544956371, R2.0=0.222993618449393),
-                    full.big=c(
-                      birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
-                      imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
-                      report.prob=0.1, boost.prob=0.75, polar.prob=0.1, foi.mod=0.5,
-                      popsize=5e+6, noise.sigma=0.01, tau=0.01,
-                      S.0=0.130980596244438, E.0=0.00115096693013597, I.0=0.0018994251960431,
-                      R1.0=0.643957103848235, R2.0=0.222011907781148),
-                    stop("unrecognized dataset ",sQuote(which),call.=FALSE)
-                    ),
-                  rprocess = euler.sim(
-                    step.fun="pertussis_sveirr_EM",
-                    delta.t=1/52/7,          # Euler stepsize
-                    PACKAGE="pompExamples"
-                    ),
-                  skeleton.type="vectorfield",
-                  skeleton="pertussis_sveirr_skel",
-                  PACKAGE="pompExamples",
-                  paramnames=c(
-                    "birthrate","deathrate","mean.beta","ampl.beta",
-                    "imports","sigma","gamma","alpha","alpha.ratio",
-                    "report.prob","boost.prob","polar.prob",
-                    "foi.mod","noise.sigma","popsize","tau",
-                    "S.0","E.0","I.0","R1.0","R2.0"
-                    ),
-                  statenames=c("S","E","I","R1","R2","cases","W","err","simpop"),
-                  zeronames=c("cases","err"),
-                  ivps=c("S.0","E.0","I.0","R1.0","R2.0"),
-                  comp.names=c("S","E","I","R1","R2"),
-                  rmeasure = "negbin_rmeasure",
-                  dmeasure = "negbin_dmeasure",
-                  parameter.inv.transform="pertussis_par_untrans",
-                  parameter.transform="pertussis_par_trans",
-                  varnames=c("S","E","I","R1","R2","cases","W","err","simpop"),
-                  initializer = function (params, t0, varnames, comp.names, ivps, ...) {
-                    states <- numeric(length(varnames))
-                    names(states) <- varnames
-                    ## translate fractions into initial conditions
-                    frac <- params[ivps]
-                    states[comp.names] <- round(params['popsize']*frac/sum(frac))
-                    states["simpop"] <- params["popsize"]
-                    states
-                  }
-                  ),
-             seed=switch(
-               which,
-               SEIR.small=1831650124L,
-               SEIR.big=908022490L,
-               SEIRS.small=1111340406L,
-               SEIRS.big=1751228386L,
-               SEIRR.small=350421545L,
-               SEIRR.big=748454784L,
-               full.small=581894515L,
-               full.big=301057392L,
-               stop("unrecognized dataset ",sQuote(which),call.=FALSE)
-               )
-             )
+    suppressMessages(
+                     simulate(
+                              pomp(
+                                   data=data.frame(time=seq(from=0,to=20,by=1/52),reports=NA),
+                                   times="time",
+                                   t0=-1/52,
+                                   params=switch(
+                                     which,
+                                     SEIR.small=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=450, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0, alpha.ratio=1,
+                                       report.prob=0.3, boost.prob=0, polar.prob=0, foi.mod=0,
+                                       popsize=5e+5, noise.sigma=0, tau=0.01,
+                                       S.0=0.0574148031949802, E.0=0.0004081763321755, I.0=0.00067028956509212,
+                                       R1.0=0.941506730907752, R2.0=0),
+                                     SEIR.big=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=450, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0, alpha.ratio=1,
+                                       report.prob=0.3, boost.prob=0, polar.prob=0, foi.mod=0,
+                                       popsize=5e+6, noise.sigma=0, tau=0.01,
+                                       S.0=0.0515635231482973, E.0=0.000437143470487014, I.0=0.000734641109212043,
+                                       R1.0=0.947264692272004, R2.0=0),
+                                     SEIRS.small=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.1, boost.prob=0, polar.prob=0, foi.mod=0,
+                                       popsize=5e+5, noise.sigma=0, tau=0.01,
+                                       S.0=0.157360395940609, E.0=0.000837874318852172, I.0=0.00124181372794081,
+                                       R1.0=0.45913512973054, R2.0=0.381424786282058),
+                                     SEIRS.big=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.1, boost.prob=0, polar.prob=0, foi.mod=0,
+                                       popsize=5e+6, noise.sigma=0, tau=0.01,
+                                       S.0=0.157398354546347, E.0=0.00132093662562661, I.0=0.0022558671035406,
+                                       R1.0=0.457185201591761, R2.0=0.381839640132725),
+                                     SEIRR.small=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.11, boost.prob=0.75, polar.prob=0, foi.mod=0.5,
+                                       popsize=5e+5, noise.sigma=0, tau=0.01,
+                                       S.0=0.128943112158304, E.0=0.00068688724266688, I.0=0.00114414648269803,
+                                       R1.0=0.638074319602244, R2.0=0.231151534514087),
+                                     SEIRR.big=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.11, boost.prob=0.75, polar.prob=0, foi.mod=0.5,
+                                       popsize=5e+6, noise.sigma=0, tau=0.01,
+                                       S.0=0.127128689912424, E.0=0.00126497004491763, I.0=0.00216092385991776,
+                                       R1.0=0.639879739889535, R2.0=0.229565676293206),
+                                     full.small=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.1, boost.prob=0.75, polar.prob=0.1, foi.mod=0.5,
+                                       popsize=5e+5, noise.sigma=0.01, tau=0.01,
+                                       S.0=0.132553922599906, E.0=0.0010539075727066, I.0=0.00166100642162314,
+                                       R1.0=0.641737544956371, R2.0=0.222993618449393),
+                                     full.big=c(
+                                       birthrate=0.02, deathrate=0.02, mean.beta=150, ampl.beta=0.15,
+                                       imports=10, sigma=46, gamma=26, alpha=0.1, alpha.ratio=1,
+                                       report.prob=0.1, boost.prob=0.75, polar.prob=0.1, foi.mod=0.5,
+                                       popsize=5e+6, noise.sigma=0.01, tau=0.01,
+                                       S.0=0.130980596244438, E.0=0.00115096693013597, I.0=0.0018994251960431,
+                                       R1.0=0.643957103848235, R2.0=0.222011907781148),
+                                     stop("unrecognized dataset ",sQuote(which),call.=FALSE)
+                                     ),
+                                   rprocess = euler.sim(
+                                     step.fun="pertussis_sveirr_EM",
+                                     delta.t=1/52/7,          # Euler stepsize
+                                     PACKAGE="pompExamples"
+                                     ),
+                                   skeleton.type="vectorfield",
+                                   skeleton="pertussis_sveirr_skel",
+                                   PACKAGE="pompExamples",
+                                   paramnames=c(
+                                     "birthrate","deathrate","mean.beta","ampl.beta",
+                                     "imports","sigma","gamma","alpha","alpha.ratio",
+                                     "report.prob","boost.prob","polar.prob",
+                                     "foi.mod","noise.sigma","popsize","tau",
+                                     "S.0","E.0","I.0","R1.0","R2.0"
+                                     ),
+                                   statenames=c("S","E","I","R1","R2","cases","W","err","simpop"),
+                                   zeronames=c("cases","err"),
+                                   ivps=c("S.0","E.0","I.0","R1.0","R2.0"),
+                                   comp.names=c("S","E","I","R1","R2"),
+                                   rmeasure = "negbin_rmeasure",
+                                   dmeasure = "negbin_dmeasure",
+                                   toEstimationScale="pertussis_par_untrans",
+                                   fromEstimationScale="pertussis_par_trans",
+                                   varnames=c("S","E","I","R1","R2","cases","W","err","simpop"),
+                                   initializer = function (params, t0, varnames, comp.names, ivps, ...) {
+                                     states <- numeric(length(varnames))
+                                     names(states) <- varnames
+                                     ## translate fractions into initial conditions
+                                     frac <- params[ivps]
+                                     states[comp.names] <- round(params['popsize']*frac/sum(frac))
+                                     states["simpop"] <- params["popsize"]
+                                     states
+                                   }
+                                   ),
+                              seed=switch(
+                                which,
+                                SEIR.small=1831650124L,
+                                SEIR.big=908022490L,
+                                SEIRS.small=1111340406L,
+                                SEIRS.big=1751228386L,
+                                SEIRR.small=350421545L,
+                                SEIRR.big=748454784L,
+                                full.small=581894515L,
+                                full.big=301057392L,
+                                stop("unrecognized dataset ",sQuote(which),call.=FALSE)
+                                )
+                              )
+                     )
   }
 }

Modified: pkg/pompExamples/inst/examples/bbp.R
===================================================================
--- pkg/pompExamples/inst/examples/bbp.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/inst/examples/bbp.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -87,12 +87,12 @@
 ###     dmeasure=Csnippet("lik=dnbinom_mu(deaths,theta,ratio*exp(y),give_log);"),
      logvar=c("beta","delta","ratio","sigma","theta","mu"),
      logitvar=c("y0"),
-     parameter.inv.transform=function (params, logvar, logitvar, ...) {
+     toEstimationScale=function (params, logvar, logitvar, ...) {
        params[logvar] <- log(params[logvar])
        params[logitvar] <- qlogis(params[logitvar])
        params
      },
-     parameter.transform=function (params, logvar, logitvar, ...) {
+     fromEstimationScale=function (params, logvar, logitvar, ...) {
        params[logvar] <- exp(params[logvar])
        params[logitvar] <- plogis(params[logitvar])
        params

Modified: pkg/pompExamples/inst/examples/bsflu.R
===================================================================
--- pkg/pompExamples/inst/examples/bsflu.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/inst/examples/bsflu.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -89,8 +89,8 @@
      skeleton.type="map",
      rmeasure=Csnippet(rmeas),
      dmeasure=Csnippet(dmeas),
-     parameter.transform=Csnippet(partrans),
-     parameter.inv.transform=Csnippet(paruntrans),
+     fromEstimationScale=Csnippet(partrans),
+     toEstimationScale=Csnippet(paruntrans),
      obsnames = c("confined","convalescent"),
      statenames=c("S","I","R","C"),
      paramnames=c(

Modified: pkg/pompExamples/inst/examples/bsflu3.R
===================================================================
--- pkg/pompExamples/inst/examples/bsflu3.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/inst/examples/bsflu3.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -97,8 +97,8 @@
      skeleton.type="map",
      rmeasure=Csnippet(rmeas),
      dmeasure=Csnippet(dmeas),
-     parameter.transform=Csnippet(partrans),
-     parameter.inv.transform=Csnippet(paruntrans),
+     fromEstimationScale=Csnippet(partrans),
+     toEstimationScale=Csnippet(paruntrans),
      obsnames = c("confined","convalescent"),
      statenames=c("S","I","R1","R2","R3","C"),
      paramnames=c(

Modified: pkg/pompExamples/inst/examples/budmoth.R
===================================================================
--- pkg/pompExamples/inst/examples/budmoth.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/inst/examples/budmoth.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -77,13 +77,13 @@
                   "g","delta","a","w","sig.a","beta1","sigQobs",
                   "sigNobs", "sigSobs","N.0"
                   ),
-                parameter.transform=function (params, logitvar,
+                fromEstimationScale=function (params, logitvar,
                   logvar, ...) {
                   params[logitvar] <- plogis(params[logitvar])
                   params[logvar] <- exp(params[logvar])
                   params
                 },
-                parameter.inv.transform=function (params, logitvar,
+                toEstimationScale=function (params, logitvar,
                   logvar, ...) {
                   params[logitvar] <- qlogis(params[logitvar])
                   params[logvar] <- log(params[logvar])

Modified: pkg/pompExamples/inst/examples/parus.R
===================================================================
--- pkg/pompExamples/inst/examples/parus.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/inst/examples/parus.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -91,10 +91,10 @@
        paramnames=c("r","K","sigma","theta"),
        statenames=c("N"),
        obsnames=c("pop"),
-       parameter.transform=function(params,...){
+       fromEstimationScale=function(params,...){
          exp(params)
        },
-       parameter.inv.transform=function(params,...){
+       toEstimationScale=function(params,...){
          log(params)
        },
        PACKAGE="pompExamples"

Modified: pkg/pompExamples/tests/bbp.Rout.save
===================================================================
--- pkg/pompExamples/tests/bbp.Rout.save	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/bbp.Rout.save	2015-06-17 12:56:44 UTC (rev 1210)
@@ -1,6 +1,6 @@
 
-R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet"
-Copyright (C) 2014 The R Foundation for Statistical Computing
+R version 3.1.3 (2015-03-09) -- "Smooth Sidewalk"
+Copyright (C) 2015 The R Foundation for Statistical Computing
 Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
@@ -17,12 +17,11 @@
 
 > library(pompExamples)
 Loading required package: pomp
-Loading required package: subplex
-Loading required package: nloptr
 > 
 > set.seed(47575684L)
 > 
 > pompExample(bbp)
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'logvar','logitvar'
 newly created object(s):
  bbp 
 > pf <- pfilter(simulate(bbp),Np=100,max.fail=Inf)
@@ -30,4 +29,4 @@
 > 
 > proc.time()
    user  system elapsed 
-  0.575   0.045   0.608 
+  0.633   0.026   0.636 

Modified: pkg/pompExamples/tests/budmoth.Rout.save
===================================================================
--- pkg/pompExamples/tests/budmoth.Rout.save	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/budmoth.Rout.save	2015-06-17 12:56:44 UTC (rev 1210)
@@ -1,6 +1,6 @@
 
-R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet"
-Copyright (C) 2014 The R Foundation for Statistical Computing
+R version 3.1.3 (2015-03-09) -- "Smooth Sidewalk"
+Copyright (C) 2015 The R Foundation for Statistical Computing
 Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
@@ -17,12 +17,14 @@
 
 > library(pompExamples)
 Loading required package: pomp
-Loading required package: subplex
-Loading required package: nloptr
 > 
 > all <- c("food","para1","para2","tri")
 > 
 > bm <- pompExample(budmoth,envir=NULL)
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'logitvar','logvar'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'logitvar','logvar'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'logitvar','logvar'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'logitvar','logvar'
 > 
 > names(bm)
 [1] "food"  "para1" "para2" "tri"  
@@ -127,4 +129,4 @@
 > 
 > proc.time()
    user  system elapsed 
-  0.626   0.053   0.668 
+  0.653   0.042   0.680 

Modified: pkg/pompExamples/tests/ebola.Rout.save
===================================================================
--- pkg/pompExamples/tests/ebola.Rout.save	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/ebola.Rout.save	2015-06-17 12:56:44 UTC (rev 1210)
@@ -1,6 +1,6 @@
 
-R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet"
-Copyright (C) 2014 The R Foundation for Statistical Computing
+R version 3.1.3 (2015-03-09) -- "Smooth Sidewalk"
+Copyright (C) 2015 The R Foundation for Statistical Computing
 Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
@@ -17,8 +17,6 @@
 
 > library(pompExamples)
 Loading required package: pomp
-Loading required package: subplex
-Loading required package: nloptr
 > 
 > set.seed(47575684L)
 > 
@@ -28,16 +26,19 @@
 newly created object(s):
  ebolaModel 
 > ebolaModel(country="Guinea") -> po
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'nstageE'
 > pf <- pfilter(simulate(po),Np=100)
 > tj <- trajectory(po)
 > 
 > ebolaModel(country="SierraLeone",na.rm=TRUE,type='cum') -> po
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'nstageE'
 > pf <- pfilter(simulate(po),Np=100)
 > tj <- trajectory(po)
 > dd <- simulate(po,as.data.frame=TRUE,obs=TRUE)
 > dd$week <- dd$time
 > po <- ebolaModel(data=subset(dd,select=c(week,cases,deaths)))
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'nstageE'
 > 
 > proc.time()
    user  system elapsed 
-  1.837   0.246   2.034 
+  1.824   0.321   2.121 

Modified: pkg/pompExamples/tests/parus.Rout.save
===================================================================
--- pkg/pompExamples/tests/parus.Rout.save	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/parus.Rout.save	2015-06-17 12:56:44 UTC (rev 1210)
@@ -1,6 +1,6 @@
 
-R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet"
-Copyright (C) 2014 The R Foundation for Statistical Computing
+R version 3.1.3 (2015-03-09) -- "Smooth Sidewalk"
+Copyright (C) 2015 The R Foundation for Statistical Computing
 Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
@@ -17,8 +17,6 @@
 
 > library(pompExamples)
 Loading required package: pomp
-Loading required package: subplex
-Loading required package: nloptr
 > 
 > set.seed(47575684L)
 > 
@@ -45,4 +43,4 @@
 > 
 > proc.time()
    user  system elapsed 
-  0.575   0.033   0.596 
+  0.576   0.024   0.580 

Modified: pkg/pompExamples/tests/pertussis.R
===================================================================
--- pkg/pompExamples/tests/pertussis.R	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/pertussis.R	2015-06-17 12:56:44 UTC (rev 1210)
@@ -21,7 +21,7 @@
 pttest <- function (po, digits = 15) {
   identical(
             signif(coef(po),digits=digits),
-            signif(partrans(po,partrans(po,coef(po),dir='inv'),dir='for'),digits=digits)
+            signif(partrans(po,partrans(po,coef(po),dir='to'),dir='from'),digits=digits)
             )
 }
 
@@ -30,7 +30,7 @@
 pttest <- function (po, digits = 15) {
   identical(
             signif(coef(po,trans=T),digits=digits),
-            signif(partrans(po,partrans(po,coef(po,trans=T),dir='f'),dir='inv'),digits=digits)
+            signif(partrans(po,partrans(po,coef(po,trans=T),dir='from'),dir='to'),digits=digits)
             )
 }
 

Modified: pkg/pompExamples/tests/pertussis.Rout.save
===================================================================
--- pkg/pompExamples/tests/pertussis.Rout.save	2015-06-17 12:56:41 UTC (rev 1209)
+++ pkg/pompExamples/tests/pertussis.Rout.save	2015-06-17 12:56:44 UTC (rev 1210)
@@ -1,6 +1,6 @@
 
-R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet"
-Copyright (C) 2014 The R Foundation for Statistical Computing
+R version 3.1.3 (2015-03-09) -- "Smooth Sidewalk"
+Copyright (C) 2015 The R Foundation for Statistical Computing
 Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
@@ -17,12 +17,18 @@
 
 > library(pompExamples)
 Loading required package: pomp
-Loading required package: subplex
-Loading required package: nloptr
 > 
 > all <- c("SEIR.small","SEIR.big","SEIRS.small","SEIRS.big","SEIRR.small","SEIRR.big","full.small","full.big")
 > 
 > sapply(all,function(n)eval(bquote(pertussis.sim(.(n))))) -> pt
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
 > 
 > names(pt)
 [1] "SEIR.small"  "SEIR.big"    "SEIRS.small" "SEIRS.big"   "SEIRR.small"
@@ -111,6 +117,7 @@
 
 > 
 > x <- simulate(pertussis.sim(full.big),seed=395885L,as.data.frame=TRUE)
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
 > tail(x)
          time reports      S    E    I      R1      R2 cases          W err
 1036 19.90385     432 662434 5677 9458 3201351 1118149  4831 -0.4801610   7
@@ -128,6 +135,7 @@
 1041 4997213   1
 > 
 > y <- trajectory(pertussis.sim(SEIRS.small),as.data.frame=TRUE)
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
 > tail(y)
             S        E         I       R1       R2    cases W err simpop
 1036 81409.73 558.4599  942.3100 227353.0 189736.5 487.2963 0   0  5e+05
@@ -145,13 +153,14 @@
 1041 20.00000    1
 > 
 > pf <- pfilter(pertussis.sim(full.small),seed=3445886L,Np=1000)
+In 'pomp': the following unrecognized argument(s) will be stored for use by user-defined functions: 'ivps','comp.names','varnames'
 > logLik(pf)
 [1] -3829.33
 > 
 > pttest <- function (po, digits = 15) {
 +   identical(
 +             signif(coef(po),digits=digits),
-+             signif(partrans(po,partrans(po,coef(po),dir='inv'),dir='for'),digits=digits)
++             signif(partrans(po,partrans(po,coef(po),dir='to'),dir='from'),digits=digits)
 +             )
 + }
 > 
@@ -160,7 +169,7 @@
 > pttest <- function (po, digits = 15) {
 +   identical(
 +             signif(coef(po,trans=T),digits=digits),
-+             signif(partrans(po,partrans(po,coef(po,trans=T),dir='f'),dir='inv'),digits=digits)
++             signif(partrans(po,partrans(po,coef(po,trans=T),dir='from'),dir='to'),digits=digits)
 +             )
 + }
 > 
@@ -168,4 +177,4 @@
 > 
 > proc.time()
    user  system elapsed 
- 23.862   0.074  23.943 
+ 23.602   0.053  23.659 



More information about the pomp-commits mailing list