[Distr-commits] r965 - in branches/distr-2.6/pkg/distrMod: R inst man
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Tue Aug 19 02:27:04 CEST 2014
Author: ruckdeschel
Date: 2014-08-19 02:27:04 +0200 (Tue, 19 Aug 2014)
New Revision: 965
Modified:
branches/distr-2.6/pkg/distrMod/R/0distrModUtils.R
branches/distr-2.6/pkg/distrMod/R/AllPlot.R
branches/distr-2.6/pkg/distrMod/inst/NEWS
branches/distr-2.6/pkg/distrMod/man/L2ParamFamily-class.Rd
Log:
[distrMod] arguments panel.first, panel.last for plot-methods can now be lists (see rev964 for distr)
Modified: branches/distr-2.6/pkg/distrMod/R/0distrModUtils.R
===================================================================
--- branches/distr-2.6/pkg/distrMod/R/0distrModUtils.R 2014-08-19 00:11:33 UTC (rev 964)
+++ branches/distr-2.6/pkg/distrMod/R/0distrModUtils.R 2014-08-19 00:27:04 UTC (rev 965)
@@ -709,6 +709,23 @@
return(outC)
}
+.panel.mingle <- function(dots, element){
+ pF <- dots[[element]]
+ if(is.list(pF)) return(pF)
+ pFr <- if(typeof(pF)=="symbol") eval(pF) else{
+ pFc <- as.call(pF)
+ if(as.list(pFc)[[1]] == "list"){
+ lis <- vector("list",length(as.list(pFc))-1)
+ for(i in 1:length(lis)){
+ lis[[i]] <- pFc[[i+1]]
+ }
+ lis
+ }else pF
+ }
+ return(pFr)
+}
+
+
#---------------------------------------------------
### from packages stats:
#---------------------------------------------------
Modified: branches/distr-2.6/pkg/distrMod/R/AllPlot.R
===================================================================
--- branches/distr-2.6/pkg/distrMod/R/AllPlot.R 2014-08-19 00:11:33 UTC (rev 964)
+++ branches/distr-2.6/pkg/distrMod/R/AllPlot.R 2014-08-19 00:27:04 UTC (rev 965)
@@ -33,12 +33,25 @@
else if(is.numeric(to.draw.arg))
to.draw <- to.draw.arg
}
+ l.draw <- length(to.draw)
+
+ pF <- expression({})
+ if(!is.null(dots[["panel.first"]])){
+ pF <- .panel.mingle(dots,"panel.first")
+ }
+ pF <- .fillList(pF, l.draw)
+ pL <- expression({})
+ if(!is.null(dots[["panel.last"]])){
+ pl <- .panel.mingle(dots,"panel.last")
+ }
+ pL <- .fillList(pL, length(to.draw))
+ plotCount <- 1
+
l2dpl <- to.draw[to.draw > 3]
dims0 <- length(l2dpl)
nrows <- trunc(sqrt(dims0))
ncols <- ceiling(dims0/nrows)
-
if(!is.logical(inner)){
if(!is.list(inner))
inner <- as.list(inner)
@@ -205,7 +218,10 @@
col.inner = col.inner, cex.inner = cex.innerD),
dots, mfColRow = mfColRow)
lis0$to.draw.arg <- todrw
- do.call(plot, args = lis0)
+ lis0[["panel.first"]] <- pF[plotCount+(0:2)]
+ lis0[["panel.last"]] <- pL[plotCount+(0:2)]
+ do.call(plot, args = lis0)
+ plotCount <- plotCount + 1
}
o.warn <- options("warn")
options(warn = -1)
@@ -229,11 +245,14 @@
for(i in 1:dims0){
indi <- l2dpl[i]-3
if(!is.null(ylim)) dots$ylim <- ylim[,d.0+d.1+i]
+ dots$panel.first <- pF[[plotCount]]
+ dots$panel.last <- pL[[plotCount]]
do.call(plot, args=c(list(x=x.vec, y=sapply(x.vec, L2deriv at Map[[indi]]),
type = plty, lty = lty,
xlab = "x",
ylab = expression(paste(L[2], " derivative"))),
dots))
+ plotCount <- plotCount + 1
if(is(e1, "DiscreteDistribution")){
x.vec1 <- seq(from = min(x.vec), to = max(x.vec), length = 1000)
do.call(lines, args=c(list(x.vec1, sapply(x.vec1, L2deriv at Map[[indi]]),
Modified: branches/distr-2.6/pkg/distrMod/inst/NEWS
===================================================================
--- branches/distr-2.6/pkg/distrMod/inst/NEWS 2014-08-19 00:11:33 UTC (rev 964)
+++ branches/distr-2.6/pkg/distrMod/inst/NEWS 2014-08-19 00:27:04 UTC (rev 965)
@@ -13,6 +13,7 @@
user-visible CHANGES:
+ introduced dropZeroDensity argument to ML estimators
++ arguments panel.first, panel.last for plot-methods can now be lists
GENERAL ENHANCEMENTS:
Modified: branches/distr-2.6/pkg/distrMod/man/L2ParamFamily-class.Rd
===================================================================
--- branches/distr-2.6/pkg/distrMod/man/L2ParamFamily-class.Rd 2014-08-19 00:11:33 UTC (rev 964)
+++ branches/distr-2.6/pkg/distrMod/man/L2ParamFamily-class.Rd 2014-08-19 00:27:04 UTC (rev 965)
@@ -203,6 +203,13 @@
in panels "d.c" and "d.d", and the last
two elements are the values for \code{ylim} resp. \code{xlim} in panels
"p", "p.c", "p.d" and "q", "q.c", "q.d".
+
+In addition, argument \code{\dots} may contain arguments \code{panel.first},
+\code{panel.last}, i.e., hook expressions to be evaluated at the very beginning
+and at the very end of each panel (within the then valid coordinates).
+To be able to use these hooks for each panel individually, they may also be
+lists of expressions (of the same length as the number of panels and
+run through in the same order as the panels).
}
More information about the Distr-commits
mailing list