[Rsiena-commits] r336 - in pkg: RSiena RSiena/R RSiena/data RSiena/man RSiena/src RSiena/src/model/effects RSienaTest RSienaTest/R RSienaTest/data RSienaTest/doc RSienaTest/man RSienaTest/src RSienaTest/src/data RSienaTest/src/model RSienaTest/src/model/effects RSienaTest/src/model/settings RSienaTest/src/model/variables RSienaTest/src/network/layers

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Oct 30 12:22:37 CET 2018


Author: tomsnijders
Date: 2018-10-30 12:22:36 +0100 (Tue, 30 Oct 2018)
New Revision: 336

Added:
   pkg/RSiena/src/model/effects/AverageGroupEffect.cpp
   pkg/RSiena/src/model/effects/AverageGroupEffect.h
   pkg/RSiena/src/model/effects/SameCovariateTransitiveReciprocatedTripletsEffect.cpp
   pkg/RSiena/src/model/effects/SameCovariateTransitiveReciprocatedTripletsEffect.h
   pkg/RSienaTest/src/model/effects/AverageGroupEffect.cpp
   pkg/RSienaTest/src/model/effects/AverageGroupEffect.h
   pkg/RSienaTest/src/model/effects/SameCovariateTransitiveReciprocatedTripletsEffect.cpp
   pkg/RSienaTest/src/model/effects/SameCovariateTransitiveReciprocatedTripletsEffect.h
   pkg/RSienaTest/src/network/layers/PrimaryLayer.cpp
   pkg/RSienaTest/src/network/layers/PrimaryLayer.h
Modified:
   pkg/RSiena/ChangeLog
   pkg/RSiena/DESCRIPTION
   pkg/RSiena/R/checkImpossibleChanges.r
   pkg/RSiena/R/effectsMethods.r
   pkg/RSiena/R/maxlikec.r
   pkg/RSiena/R/print01Report.r
   pkg/RSiena/R/siena08.r
   pkg/RSiena/R/sienaDataCreate.r
   pkg/RSiena/R/sienaGOF.r
   pkg/RSiena/R/sienaTimeTest.r
   pkg/RSiena/R/sienaeffects.r
   pkg/RSiena/R/sienaprint.r
   pkg/RSiena/R/sienatable.r
   pkg/RSiena/cran-comments.md
   pkg/RSiena/data/allEffects.csv
   pkg/RSiena/man/RSiena-package.Rd
   pkg/RSiena/man/getEffects.Rd
   pkg/RSiena/man/includeInteraction.Rd
   pkg/RSiena/man/print.sienaMeta.Rd
   pkg/RSiena/man/setEffect.Rd
   pkg/RSiena/man/siena07.Rd
   pkg/RSiena/man/siena08.Rd
   pkg/RSiena/man/sienaDependent.Rd
   pkg/RSiena/man/sienaGOF-auxiliary.Rd
   pkg/RSiena/man/sienaGOF.Rd
   pkg/RSiena/man/sienaGroupCreate.Rd
   pkg/RSiena/src/model/effects/AllEffects.h
   pkg/RSiena/src/model/effects/BehaviorEffect.cpp
   pkg/RSiena/src/model/effects/BehaviorEffect.h
   pkg/RSiena/src/model/effects/EffectFactory.cpp
   pkg/RSiena/src/sources.list
   pkg/RSienaTest/ChangeLog
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/R/checkImpossibleChanges.r
   pkg/RSienaTest/R/effects.r
   pkg/RSienaTest/R/effectsMethods.r
   pkg/RSienaTest/R/initializeFRAN.r
   pkg/RSienaTest/R/iwlsm.R
   pkg/RSienaTest/R/maxlikec.r
   pkg/RSienaTest/R/print01Report.r
   pkg/RSienaTest/R/siena08.r
   pkg/RSienaTest/R/sienaBayes.r
   pkg/RSienaTest/R/sienaDataCreate.r
   pkg/RSienaTest/R/sienaGOF.r
   pkg/RSienaTest/R/sienaTimeTest.r
   pkg/RSienaTest/R/sienaeffects.r
   pkg/RSienaTest/R/sienaprint.r
   pkg/RSienaTest/R/sienatable.r
   pkg/RSienaTest/data/allEffects.csv
   pkg/RSienaTest/doc/RSiena.bib
   pkg/RSienaTest/doc/RSienaDeveloper.tex
   pkg/RSienaTest/doc/RSiena_Manual.pdf
   pkg/RSienaTest/doc/RSiena_Manual.tex
   pkg/RSienaTest/man/RSiena-package.Rd
   pkg/RSienaTest/man/getEffects.Rd
   pkg/RSienaTest/man/includeEffects.Rd
   pkg/RSienaTest/man/includeInteraction.Rd
   pkg/RSienaTest/man/print.sienaMeta.Rd
   pkg/RSienaTest/man/setEffect.Rd
   pkg/RSienaTest/man/siena07.Rd
   pkg/RSienaTest/man/siena08.Rd
   pkg/RSienaTest/man/sienaBayes.Rd
   pkg/RSienaTest/man/sienaDependent.Rd
   pkg/RSienaTest/man/sienaGroupCreate.Rd
   pkg/RSienaTest/src/data/Data.cpp
   pkg/RSienaTest/src/data/Data.h
   pkg/RSienaTest/src/model/State.cpp
   pkg/RSienaTest/src/model/StatisticCalculator.cpp
   pkg/RSienaTest/src/model/StatisticCalculator.h
   pkg/RSienaTest/src/model/effects/AllEffects.h
   pkg/RSienaTest/src/model/effects/BehaviorEffect.cpp
   pkg/RSienaTest/src/model/effects/BehaviorEffect.h
   pkg/RSienaTest/src/model/effects/EffectFactory.cpp
   pkg/RSienaTest/src/model/settings/PrimarySetting.cpp
   pkg/RSienaTest/src/model/settings/PrimarySetting.h
   pkg/RSienaTest/src/model/settings/Setting.h
   pkg/RSienaTest/src/model/variables/DependentVariable.h
   pkg/RSienaTest/src/model/variables/NetworkVariable.cpp
   pkg/RSienaTest/src/model/variables/NetworkVariable.h
   pkg/RSienaTest/src/siena07internals.cpp
   pkg/RSienaTest/src/siena07models.cpp
   pkg/RSienaTest/src/siena07models.h
   pkg/RSienaTest/src/siena07utilities.cpp
   pkg/RSienaTest/src/siena07utilities.h
   pkg/RSienaTest/src/sources.list
Log:
Version 1.2-13. Various changes. 

Modified: pkg/RSiena/ChangeLog
===================================================================
--- pkg/RSiena/ChangeLog	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/ChangeLog	2018-10-30 11:22:36 UTC (rev 336)
@@ -1,3 +1,50 @@
+2018-10-29 R-Forge Revision 336, packages version 1.2-13.
+Changes in RSiena and RSienaTest:
+   * Correct error in print01Report that occurred for changing dyadic covariates
+     given as lists of sparse matrices.
+   * Correct error in sienaGroupCreate for centered actor covariates.
+   * Drop dependence on utils (the packages did not depend on it).
+   * Also get simulated dependent behavior variables for
+     siena07(,,, returnDeps=TRUE, ...) for ML estimation.
+   * siena.table corrected for data sets with several dependent variables.
+   * For siena08: new parameters which and useBound in plot.sienaMeta;
+     new parameter reportEstimates in siena08, allowing to reduce
+     the output produced.
+   * updateSpecification: also update randomEffects column.
+   * Change help page for sienaDependent.
+   * Some changes in sienaprint.r depending on sienaBayes, to keep the two
+     packages the same when possible.
+Changes in RSienaTest:
+   * sienaBayes: new parameters proposalFromPrev, which allows
+     taking proposal distributions from prevBayes object;
+     incidentalBasicRates resuscitated;
+     allow fixed rate parameters, with priorRatesFromData=-1;
+     changed initial values of scale factors for proposal distributions;
+     new parameters target and usePrevOnly;
+     in case prevBayes is used, parameters nrunMHBatches, nSampVarying, nSampConst,
+     and nSampRates in the function call of sienaBayes supersede those
+     in the prevBayes object;
+     correct bug for three-effect interactions (projectEffects)
+     copy parameters modelType, behModelType, MaxDegree, Offset, initML,
+     from parameter algo to the algorithms created within sienaBayes;
+     more extensive checking of smallest eigenvalue of covariance matrix
+     (function correctMatrix);
+     For priorRatesFromData = 1 or 2, the resulting matrix for priorKappa != 1 
+     was incorrect; this was corrected.
+     reported timing changed to elapsed system time;
+     some reordering of parameters.
+     This also required some corresponding changes in sienaprint.r.
+
+2018-05-13 CRAN for RSiena, version 1.2-12.
+
+2018-05-07 R-Forge Revision 336, packages version 1.2-12.
+Changes in RSiena and RSienaTest:
+    * Change default parameter of reciAct to 1 (implies changes only in 
+       output, not computationally).
+    * Internal effect parameter carried through in sienaTimeFix.
+Changes in RSiena:
+    * Shorter examples for sienaGOF and sienaGOF-auxiliary help pages.       
+
 2018-05-06 R-Forge Revision 335, packages version 1.2-11.
 Changes in RSiena and RSienaTest:
    * New effects gwdspFF and gwdspFB.
@@ -17,7 +64,8 @@
      general options; changed minus to – ;
      added column for asterisks to have better alignment for estimates.
    * Stop cluster also if (!z$OK || !z$Phase3Interrupt) (robmon.r).
-   * Extension of help page for siena07 by mentioning functions for testing.
+   * Extension of help page for siena07 by mentioning functions for accessing
+     simulated networks for ML.
 Changes in RSienaTest:
    * extract.sienaBayes: error corrected that occurred if called with 
      extracted="all" but there are no varying, or no non-varying parameters.

Modified: pkg/RSiena/DESCRIPTION
===================================================================
--- pkg/RSiena/DESCRIPTION	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/DESCRIPTION	2018-10-30 11:22:36 UTC (rev 336)
@@ -1,10 +1,11 @@
+Encoding: UTF-8
 Package: RSiena
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.2-11
-Date: 2018-05-06
+Version: 1.2-13
+Date: 2018-10-29
 Author: Ruth Ripley, Krists Boitmanis, Tom A.B. Snijders, Felix Schoenenberger
-Depends: R (>= 2.15.0), utils
+Depends: R (>= 2.15.0)
 Imports: Matrix, tcltk, lattice, parallel, MASS, methods
 Suggests: xtable, network, tools, codetools
 SystemRequirements: GNU make, tcl/tk 8.5, Tktable
@@ -12,7 +13,8 @@
 Description: The main purpose of this package is to perform simulation-based 
    estimation of stochastic actor-oriented models for longitudinal network 
    data collected as panel data. Dependent variables can be single or 
-   multivariate networks, which can be directed, non-directed, or two-mode. 
+   multivariate networks, which can be directed, non-directed, or two-mode;
+   and associated actor variables. 
    There are also functions for testing parameters and checking goodness of fit.
    An overview of these models is given in Tom A.B. Snijders (2017), Stochastic 
    Actor-Oriented Models for Network Dynamics, Annual Review of Statistics and 

Modified: pkg/RSiena/R/checkImpossibleChanges.r
===================================================================
--- pkg/RSiena/R/checkImpossibleChanges.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/checkImpossibleChanges.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -6,7 +6,7 @@
 ## * File: checkImpossibleChanges.r
 ## *
 ## * Description: This file contains the function checkImpossibleChanges
-## * which checks for changes from structural values to
+## * which checks for impossible changes from structural values to
 ## * different observed values.
 ## * Used for maximum likelihood and Bayesian estimation.
 ## *

Modified: pkg/RSiena/R/effectsMethods.r
===================================================================
--- pkg/RSiena/R/effectsMethods.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/effectsMethods.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -129,9 +129,9 @@
 	}
 	if (includeRandoms)
 	{
-		nreff <- sum(x$randomEffects & x$include)
-		nrate <- sum(x$basicRate & x$include & (x$group==2))
-		if (nrate > 0) # else there is only one group, and counting should be different.
+		nreff <- sum(x$randomEffects & x$include & (!x$fix))
+		nrate <- sum(x$basicRate & x$include & (x$group==2) & (!x$fix))
+		if (sum(x$group != 1) > 0) # else there is only one group, and counting should be different.
 		{
 			cat('Dimensions of priorMu and priorSigma for sienaBayes should be',
 				nreff, '+', nrate, '=', nreff+nrate,'.\n')
@@ -297,5 +297,6 @@
 	effects.to$fix[use] <- prevEffects$fix[correspondence][use]
 	effects.to$test[use] <- prevEffects$test[correspondence][use]
 	effects.to$parameter[use] <- prevEffects$parameter[correspondence][use]
+	effects.to$randomEffects[use] <- prevEffects$randomEffects[correspondence][use]
 	effects.to
 }

Modified: pkg/RSiena/R/maxlikec.r
===================================================================
--- pkg/RSiena/R/maxlikec.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/maxlikec.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -111,7 +111,7 @@
 			ans[[11]] <- sapply(anss, "[[", 11)
 			if (z$returnDeps)
 			{
-				fff <- lapply(anss, function(x) x[[12]][[1]])
+				fff <- lapply(anss, function(x) x[[12]])
 				sims <- split(fff, callGrid[, 1 ]) ## split by group
 			}
 			else

Modified: pkg/RSiena/R/print01Report.r
===================================================================
--- pkg/RSiena/R/print01Report.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/print01Report.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -748,7 +748,7 @@
 					any.noncent <- any.noncent+1
 				}
 				Report(c(format(covars[i], width=28), cent, '\n'), outf) # name
-				for (j in 1:(dim(x$dyvCovars[[i]])[3]))
+				for (j in 1:(atts$vardims[3]))
 				{
 					Report(c("	period", format(j + periodFromStart,
 											   width=3),

Modified: pkg/RSiena/R/siena08.r
===================================================================
--- pkg/RSiena/R/siena08.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/siena08.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -213,7 +213,7 @@
 ## methods
 
 ##@print.sienaMeta Methods
-print.sienaMeta <- function(x, file=FALSE, ...)
+print.sienaMeta <- function(x, file=FALSE, reportEstimates=FALSE, ...)
 {
     exitfn <- function()
     {
@@ -257,6 +257,8 @@
        Report(c("\n", dashes, "\nParameter ", i, ": ",
                 as.character(x$effects[1]), "\n", dashes, "\n"),
               sep="", outf)
+	   if (reportEstimates)
+	   {
        tmp <- paste("Data set ", 1:nrow(x), ", ", format(x$projname),
                     " :  Estimate ",
                     format(round(x$theta, 4), width=12),
@@ -264,6 +266,7 @@
                     format(round(x$se, 4), nsmall=4,
                            width=12), ")", x$excl, "\n", sep="")
        Report(c(tmp, "\n"), sep="", outf)
+	   }
        Report(c(" ", y$n1, " datasets used.\n\n"), sep="", outf)
        if (y$n1 > 0)
        {
@@ -403,11 +406,19 @@
 }
 
 ##@plot.sienaMeta Methods
-plot.sienaMeta <- function(x, ..., layout = c(2,2))
+plot.sienaMeta <- function(x, ..., which = 1:length(x$theta), useBound=TRUE, layout = c(2,2))
 {
     ## library(lattice)
-    tmp <- xyplot(theta ~ se|effects,
-                  data=x$thetadf[is.na(x$thetadf$scoretests),],
+	if (useBound)
+	{
+		usedLines <- is.na(x$thetadf$scoretests) & (x$thetadf$se < x$bound)
+	}
+	else
+	{
+		usedLines <- is.na(x$thetadf$scoretests)
+	}
+    tmp <- xyplot(theta ~ se|effects[which],
+                  data=x$thetadf[usedLines,],
                   ylab="estimates",
                   xlab="standard errors", layout=layout,
                   panel=function(x, y)

Modified: pkg/RSiena/R/sienaDataCreate.r
===================================================================
--- pkg/RSiena/R/sienaDataCreate.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienaDataCreate.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -1288,10 +1288,17 @@
 		for (i in 1:length(group))
 		{
 			j <- match(atts$vCovars[covar], names(group[[i]]$vCovars))
+			j1 <- match(atts$vCovars[covar], names(group[[1]]$vCovars))
 			if (is.na(j))
 			{
 				stop("inconsistent actor covariate names")
 			}
+			if (attr(group[[i]]$vCovars[[j]],"centered") != attr(group[[1]]$vCovars[[j]],"centered"))
+			{
+				stop(paste("Inconsistent centering for covariate", names(group[[i]]$vCovars)[j]))
+			}
+			if (attr(group[[i]]$vCovars[[j]],"centered"))
+			{
 			vartotal <- vartotal + attr(group[[i]]$vCovars[[j]], "vartotal")
 			nonMissingCount <- nonMissingCount +
 				attr(group[[i]]$vCovars[[j]], "nonMissingCount")
@@ -1299,8 +1306,8 @@
 				attr(group[[i]]$vCovars[[j]], "vartotal") /
 					attr(group[[i]]$vCovars[[j]], "nonMissingCount")
 		}
+		}
 		varmean <- vartotal / nonMissingCount
-#browser() # Hier kijken hoe je moet centreren in de groep.
 		j <- match(atts$vCovars[covar], names(group[[1]]$vCovars))
 		if (attr(group[[1]]$vCovars[[j]],"centered"))
 		{
@@ -1779,6 +1786,8 @@
 			nVCovar <- length(vars)
 			for (j in seq(along=const))
 			{
+				oneCentered <- FALSE
+				oneNonCentered <- FALSE
 				dim3 <- objlist[[i]]$observations - 1
 				newcovar <-
 					varDyadCovar(array(const[[j]], dim=c(dim(const[[j]]),

Modified: pkg/RSiena/R/sienaGOF.r
===================================================================
--- pkg/RSiena/R/sienaGOF.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienaGOF.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -1176,7 +1176,7 @@
 ##@TriadCensus sienaGOF Calculates mixed triad census
 # Contributed by Christoph Stadtfeld.
 # 
-# Implementation of the Batagelj–Mrvar (Social Networks, 2001) algorithm
+# Implementation of the Batagelj-Mrvar (Social Networks, 2001) algorithm
 # based on the summary in the thesis of Sindhuja
 #
 TriadCensus <- function (i, obsData, sims, period, groupName, varName, levls = 1:16) {  

Modified: pkg/RSiena/R/sienaTimeTest.r
===================================================================
--- pkg/RSiena/R/sienaTimeTest.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienaTimeTest.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -36,7 +36,7 @@
 	{
 		if (!sienaFit$sf2.byIterations)
 		{
-			stop("sienaTimeTest needs sf2 by iterations")
+			stop("sienaTimeTest needs sf2 by iterations (use lessMem=FALSE)")
 		}
 	}
 	waveNumbers <- attr(sienaFit$f, "periodNos")
@@ -1168,6 +1168,7 @@
 								interaction1= c(effect$interaction1,
 									dname),
 								interaction2=effect$interaction2,
+								parameter=effect$parameter,
 								name=depvar, verbose=FALSE)
 					} else {
 						newEffects <-
@@ -1178,6 +1179,7 @@
 								interaction1= c(effect$interaction1,
 									dname),
 								interaction2=effect$interaction2,
+								parameter=effect$parameter,
 								name=depvar, verbose=FALSE)
 					}
 					## find the row altered

Modified: pkg/RSiena/R/sienaeffects.r
===================================================================
--- pkg/RSiena/R/sienaeffects.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienaeffects.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -83,7 +83,7 @@
 includeInteraction <- function(myeff, ...,
 				include=TRUE, name=myeff$name[1],
 				type="eval", interaction1=rep("", 3), interaction2=rep("", 3),
-				fix=FALSE, test=FALSE, parameter=0, random=FALSE,
+				fix=FALSE, test=FALSE, parameter=NULL, random=FALSE,
 				character=FALSE, verbose=TRUE)
 {
 	if (character)

Modified: pkg/RSiena/R/sienaprint.r
===================================================================
--- pkg/RSiena/R/sienaprint.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienaprint.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -724,6 +724,12 @@
 				z$ThinParameters[nfirst:ntott,
 				group, !z$generalParametersInGroup, drop=FALSE], 3, var, na.rm=TRUE)
 	}
+
+	if (is.null(z$priorRatesFromData))
+	{
+		z$priorRatesFromData <- 2
+	}
+# 2 is here the default; this is to achieve compatibility with earlier versions
 	if (groupOnly != 0)
 	{
 		thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
@@ -732,6 +738,16 @@
 	}
 	else
 	{
+		if ((z$priorRatesFromData <0) | z$incidentalBasicRates)
+		{
+		thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
+				z$ThinPosteriorMu[(nfirst):dim(z$ThinPosteriorMu)[1],
+					, drop=FALSE], na.rm=TRUE)
+		postVarMean[z$varyingObjectiveParameters] <- sapply(1:(dim(z$ThinPosteriorSigma)[2]),
+			function(i){mean(z$ThinPosteriorSigma[nfirst:dim(z$ThinPosteriorSigma)[1],i,i], na.rm=TRUE)})
+		}
+		else
+		{
 	thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
 				z$ThinPosteriorMu[(nfirst):dim(z$ThinPosteriorMu)[1],
 				z$objectiveInVarying, drop=FALSE], na.rm=TRUE)
@@ -739,16 +755,11 @@
 		function(i){mean(z$ThinPosteriorSigma[nfirst:dim(z$ThinPosteriorSigma)[1],i,i], na.rm=TRUE)}
 														)[z$objectiveInVarying]
 	}
-	if (any(z$set2))
-	{
+	}
 		thetaMean[z$set2] <-
 			colMeans(z$ThinPosteriorEta[nfirst:dim(z$ThinPosteriorEta)[1],, drop=FALSE],
 						na.rm=TRUE)
-	}
-	if (any(z$fix))
-	{
-		thetaMean[z$fix] <- z$thetaMat[1,z$fix]
-	}
+	thetaMean[z$fix & (!z$basicRate)] <- z$thetaMat[1,z$fix & (!z$basicRate)]
 	list(thetaMean, postVarMean)
 }
 
@@ -776,16 +787,20 @@
 	}
 	else
 	{
+		if ((z$priorRatesFromData <0) | z$incidentalBasicRates)
+		{
 		sdTheta[(z$set1)&(!z$basicRate)] <- apply(
+				z$ThinPosteriorMu[nfirst:ntot, , drop=FALSE], 2, sd)
+		}
+		else
+		{
+		sdTheta[(z$set1)&(!z$basicRate)] <- apply(
 				z$ThinPosteriorMu[nfirst:ntot,
 				z$objectiveInVarying, drop=FALSE], 2, sd)
 	}
-	if (any(z$set2))
-	{
+	}
 		sdTheta[z$set2] <-
-			apply(z$ThinPosteriorEta[nfirst:ntot,, drop=FALSE],
-			   2, sd)
-	}
+			apply(z$ThinPosteriorEta[nfirst:ntot,, drop=FALSE], 2, sd)
 	sdTheta
 }
 
@@ -811,6 +826,18 @@
 	}
 	else
 	{
+		if ((z$priorRatesFromData <0) | z$incidentalBasicRates)
+		{
+			credVals[(z$set1)&(!z$basicRate), 1:3] <-
+				t(apply(z$ThinPosteriorMu[nfirst:ntott,
+					, drop=FALSE], 2, cvp, test0 = tested))
+			credVals[z$varyingObjectiveParameters, 4:5] <-
+				t(sapply(1:(dim(z$ThinPosteriorSigma)[2]),
+		function(i){cvp(z$ThinPosteriorSigma[nfirst:dim(z$ThinPosteriorSigma)[1],i,i],
+									10)[1:2]} ))
+		}
+		else
+		{
 		credVals[(z$set1)&(!z$basicRate), 1:3] <-
 			t(apply(z$ThinPosteriorMu[nfirst:ntott,
 				z$objectiveInVarying, drop=FALSE], 2, cvp, test0 = tested))
@@ -820,6 +847,7 @@
 									10)[1:2]}
 		)[,z$objectiveInVarying])
 	}
+	}
 	for (group in 1:z$nGroup)
 	{
 		credVals[z$ratePositions[[group]], 1:2] <-
@@ -995,7 +1023,7 @@
 	mydf[nrates + (1:xp), 'text' ] <- theEffects$effectName
 	mydf[nrates + (1:xp), 'value' ] <- theta
 
-	if (fromBayes)
+	if (fromBayes) # then nrates=0
 	{
 		mydf[nrates + (1:xp), 'se' ] <- sdTheta.last(x, groupOnly, nfirst=nfirst)
 		mydf[nrates + (1:xp), 'random' ] <- NA
@@ -1184,6 +1212,13 @@
 			mymat[(x$fix|x$basicRate|x$set2), 'cSdFrom']   <- "       "
 			mymat[(x$fix|x$basicRate|x$set2), 'cSdTo']     <- "       "
 		}
+		if (x$incidentalBasicRates)
+		{
+			mymat[x$basicRate, 'se']     <- "       "
+#			mymat[x$basicRate, 'postSd'] <- "       "
+			mymat[x$basicRate, 'cFrom']  <- "       "
+			mymat[x$basicRate, 'cTo']    <- "       "
+		}
 		mymat[, 'type'] <- format(mymat[, 'type'])
 		mymat[, 'text'] <- format(mymat[, 'text'])
 		mymat[mydf$row < 1, 'row'] <-
@@ -1405,7 +1440,7 @@
 		{
 			cat(sprintf("%8.4f", x$priorSigma[i,]),"\n        ")
 		}
-		cat("\nDf       ",sprintf("%1d", x$priorDf),"\n")
+		cat("\nPrior Df ",sprintf("%1d", x$priorDf),"\n")
 		if (length(x$f$groupNames) >= 2)
 		{
 			cat("\nKappa  ",sprintf("%8.4f", x$priorKappa),"\n")
@@ -1470,7 +1505,7 @@
 			lines.thisgroup <- union(lines.thisgroup,
 							2 + which(x$varyingObjectiveParameters))
 			lines.thisgroup <- union(lines.thisgroup,
-							2 + which(x$fix))
+							2 + which(x$fix & (!x$basicRate)))
 			lines.thisgroup <- sort(union(lines.thisgroup, 2 + which(x$set2)))
 			for (i in lines.thisgroup)
 			{

Modified: pkg/RSiena/R/sienatable.r
===================================================================
--- pkg/RSiena/R/sienatable.r	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/R/sienatable.r	2018-10-30 11:22:36 UTC (rev 336)
@@ -305,8 +305,9 @@
 					<TD>   (s.e.)</TD>",start.tstat,"</TR>")))
 					midTable <- tableSection(c("",""))
 					indentTable <- tableSection("")
-		ruleTable <- tableSection("</TABLE>")
-		footnoteStart <- "<TABLE border=1  rules=none frame = below>"
+		ruleTable <- tableSection("<TR> <TD colspan='9'><HR/></TD> </TR>")
+
+		footnoteStart <- c("</TABLE>","<TABLE border=1  rules=none frame = below>")
 					footnote <- c(paste(" <TR> <TD colspan=9 align=left>
 							all convergence t ratios < ",
 							max.t,".</TD> </TR> <TR> </TR>",

Modified: pkg/RSiena/cran-comments.md
===================================================================
--- pkg/RSiena/cran-comments.md	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/cran-comments.md	2018-10-30 11:22:36 UTC (rev 336)
@@ -1,18 +1,11 @@
-# RSiena new version 1.2-3 (2017-9-08)
+# RSiena new version 1.2-12 (2018-05-12)
 
-## Issue for previous version (1.1-232) on gcc-UBSAN (runtime error) solved.
+## Passed checks on Windows, Mac, and Linux
+* No ERRORs, WARNINGs, or NOTEs on Windows and Mac. 
+* For Linux there were no ERRORs or WARNINGs;
+  there was a NOTE about the installed package size,
+  which is due to the use of a lot of compiled C++ code.
 
-## Warning for previous version (1.1-232) on windows-devel
-(cleanup: Non-Windows OSes require LF line endings) solved.
+## R CMD check --run-donttest on Windows OK.
 
-##Test environments
-* local Windows 7, R 3.4.1: OK
-* local Windows 7, R-devel (2017-8-24) through devtools: OK
-* local Windows 7, R-patched (2017-8-25) through devtools: OK
-* R-Hub Debian Linux, R-devel, GCC: OK
-* R-Hub macOS 10.9 Mavericks, R-oldrel (experimental): OK
-* R-Hub macOS 10.11 El Capitan, R-release (experimental): OK
-* R-Hub Ubuntu Linux 16.04 LTS, R-devel, GCC: OK
-
-## R CMD check results
-* All results were OK, no ERRORs, WARNINGs, or NOTEs.
\ No newline at end of file
+## Reverse dependency checked: btergm.
\ No newline at end of file

Modified: pkg/RSiena/data/allEffects.csv
===================================================================
--- pkg/RSiena/data/allEffects.csv	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/data/allEffects.csv	2018-10-30 11:22:36 UTC (rev 336)
@@ -320,7 +320,7 @@
 nonSymmetricObjective,indegree - activity (sqrt),Sum of outdegrees x sqrt(indegree),inActSqrt,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego,TRUE
 nonSymmetricObjective,outdegree - activity,Sum of squared outdegrees,outAct,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,TRUE
 nonSymmetricObjective,outdegree - activity (sqrt),Sum of outdegrees^(1.5),outActSqrt,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,TRUE
-nonSymmetricObjective,rec.degree^(1/#) - activity,Sum rec.degr^(1/#) x outdegr,reciAct,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,TRUE
+nonSymmetricObjective,rec.degree^(1/#) - activity,Sum rec.degr^(1/#) x outdegr,reciAct,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,TRUE
 nonSymmetricObjective,indegree - activity,Sum of crossproducts indegree x outdegree,inAct,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego,TRUE
 nonSymmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,TRUE
 nonSymmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc2,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,,TRUE

Modified: pkg/RSiena/man/RSiena-package.Rd
===================================================================
--- pkg/RSiena/man/RSiena-package.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/RSiena-package.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -44,8 +44,8 @@
   \tabular{ll}{
     Package: \tab RSiena\cr
     Type: \tab Package\cr
-    Version: \tab 1.2-11\cr
-    Date: \tab 2018-05-06\cr
+    Version: \tab 1.2-13\cr
+    Date: \tab 2018-10-29\cr
     Depends: \tab R (>= 3.0.0)\cr
     Imports: \tab Matrix\cr
     Suggests: \tab tcltk, network, codetools, lattice, MASS, parallel,

Modified: pkg/RSiena/man/getEffects.Rd
===================================================================
--- pkg/RSiena/man/getEffects.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/getEffects.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -82,7 +82,8 @@
 \references{See \url{http://www.stats.ox.ac.uk/~snijders/siena/}}
 \author{Ruth Ripley}
 \seealso{\code{\link{sienaDataCreate}}, \code{\link{sienaDataCreate}},
-        \code{\link{includeEffects}}, \code{\link{setEffect}}}
+        \code{\link{includeEffects}}, \code{\link{setEffect}},
+        \code{\link{print.sienaEffects}}}
 \examples{
 mynet1 <- sienaDependent(array(c(s501, s502, s503), dim=c(50, 50, 3)))
 mybeh <- sienaDependent(s50a, type="behavior")

Modified: pkg/RSiena/man/includeInteraction.Rd
===================================================================
--- pkg/RSiena/man/includeInteraction.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/includeInteraction.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -9,7 +9,7 @@
 \usage{
 includeInteraction(myeff, ..., include = TRUE, name = myeff$name[1],
     type = "eval", interaction1 = rep("", 3), interaction2 = rep("", 3),
-    fix = FALSE, test = FALSE, parameter = 0, random = FALSE,
+    fix = FALSE, test = FALSE, parameter = NULL, random = FALSE,
     character = FALSE, verbose = TRUE)
 }
 \arguments{
@@ -42,7 +42,7 @@
   \item{test}{
     Boolean. Are the effects to be tested or not (requires \code{fix}).}
   \item{parameter}{
-    Value of internal effect parameter of this interaction effect. Default 0.
+    Value of internal effect parameter of this interaction effect.
 	If NULL, no change is made.}
   \item{random}{For specifying that the interaction effect will vary randomly;
     not relevant for \code{RSiena} at this moment.

Modified: pkg/RSiena/man/print.sienaMeta.Rd
===================================================================
--- pkg/RSiena/man/print.sienaMeta.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/print.sienaMeta.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -6,30 +6,34 @@
 \alias{print.summary.sienaMeta}
 \title{Methods for processing sienaMeta objects}
 \usage{
-\method{print}{sienaMeta}(x, file=FALSE, ...)
+\method{print}{sienaMeta}(x, file=FALSE, reportEstimates=FALSE, ...)
 
 \method{summary}{sienaMeta}(object, file=FALSE, extra=TRUE, ...)
 
 \method{print}{summary.sienaMeta}(x, file=FALSE, extra=TRUE, ...)
 
-\method{plot}{sienaMeta}(x,  ..., layout=c(2,2))
+\method{plot}{sienaMeta}(x, ..., which = 1:length(x$theta),
+                         useBound=TRUE, layout = c(2,2))
 }
 \description{
   \code{print}, \code{summary}, and \code{plot} methods for
    \code{sienaMeta} objects.
 }
 \arguments{
-  \item{object}{An object of class \code{sienaMeta}}
+  \item{object}{An object of class \code{sienaMeta}.}
   \item{x}{An object of class \code{sienaMeta}, or
-    \code{summary.sienaMeta} as appropriate}
+    \code{summary.sienaMeta} as appropriate.}
   \item{file}{Boolean: if TRUE, sends output to file named
     \code{x$projname.out}. If FALSE, output is to the terminal.}
-  \item{extra}{Boolean: if TRUE, prints more information}
-  \item{layout}{the vector giving number of rows and columns
+  \item{reportEstimates}{Boolean: whether to report all estimates and standard errors.}
+  \item{extra}{Boolean: if TRUE, prints more information.}
+  \item{which}{Set of effects contained in the plot (given by sequence numbers).}
+  \item{useBound}{Boolean: whether to restict plotted symbols to the bound
+    used in the call of \code{sienaMeta}.}
+  \item{layout}{Vector giving number of rows and columns
     in the arrangement of the several panels in a
-    rectangular array, possibly spanning multiple pages}
-  \item{\dots}{For extra arguments (none used at present)
-  }
+    rectangular array, possibly spanning multiple pages.}
+  \item{\dots}{For extra arguments (none used at present).}
 }
 \value{
  The function \code{print.sienaMeta} prints details of the merged
@@ -83,18 +87,20 @@
 effects.3 <- getEffects(dataset.3)
 effects.4 <- getEffects(dataset.4)
 effects.1 <- includeEffects(effects.1, transTrip)
-effects.1 <- setEffect(effects.1, cycle3, fix=TRUE, test=TRUE)
+effects.1 <- setEffect(effects.1, transRecTrip, fix=TRUE, test=TRUE)
 effects.3 <- includeEffects(effects.3, transTrip)
-effects.3 <- setEffect(effects.3, cycle3, fix=TRUE, test=TRUE)
+effects.3 <- setEffect(effects.3, transRecTrip, fix=TRUE, test=TRUE)
 effects.4 <- includeEffects(effects.4, transTrip)
-effects.4 <- setEffect(effects.4, cycle3, fix=TRUE, test=TRUE)
+effects.4 <- setEffect(effects.4, transRecTrip, fix=TRUE, test=TRUE)
 ans.1 <- siena07(OneAlgorithm, data=dataset.1, effects=effects.1, batch=TRUE)
 ans.3 <- siena07(OneAlgorithm, data=dataset.3, effects=effects.3, batch=TRUE)
 ans.4 <- siena07(OneAlgorithm, data=dataset.4, effects=effects.4, batch=TRUE)
 ans.1
 ans.3
 ans.4
-(meta <- siena08(ans.1, ans.3, ans.4))
+meta <- siena08(ans.1, ans.3, ans.4)
+print(meta, reportEstimates=FALSE)
+print(meta)
 summary(meta)
 # For specifically presenting the Fisher combinations:
 # First determine the number of estimated effects:
@@ -109,5 +115,9 @@
 plo <- plot(meta, layout = c(3,1))
 plo
 plo[3]
+# Show effects of bound (bounding at 0.4 is not reasonable, just for example)
+meta <- siena08(ans.1, ans.3, ans.4, bound=0.4)
+plot(meta, which=c(2,3), layout=c(2,1))
+plot(meta, which=c(2,3), layout=c(2,1), useBound=FALSE)
 }}
 \keyword{ methods }

Modified: pkg/RSiena/man/setEffect.Rd
===================================================================
--- pkg/RSiena/man/setEffect.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/setEffect.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -95,7 +95,8 @@
 \author{Ruth Ripley }
 \seealso{
   \code{\link{getEffects}}, \code{\link{includeEffects}},
-  \code{\link{includeInteraction}}.
+  \code{\link{includeInteraction}},
+  \code{\link{print.sienaEffects}}.
 }
 
 \examples{

Modified: pkg/RSiena/man/siena07.Rd
===================================================================
--- pkg/RSiena/man/siena07.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/siena07.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -178,7 +178,8 @@
 }
 \author{Ruth Ripley, Tom Snijders}
 
-\seealso{\code{\link{sienaAlgorithmCreate}},
+\seealso{\code{\link{siena}}, \code{\link{sienaAlgorithmCreate}},
+  \code{\link{sienaEffects}},
   \code{\link{Wald.RSiena}}, \code{\link{Multipar.RSiena}},
   \code{\link{score.Test}}.
 
@@ -200,7 +201,7 @@
 
 # or if a previous "on track" result ans was obtained --------------------------
 \dontrun{
-ans1 <- siena07(myalgorithm, data=mydata, effects=myeff, prevAns=ans, batch=TRUE)
+ans1 <- siena07(myalgorithm, data=mydata, effects=myeff, prevAns=ans)
          }
 
 # Running in multiple processors -----------------------------------------------
@@ -258,7 +259,7 @@
 alg <- sienaAlgorithmCreate(maxlike=TRUE, nsub=3, n3=100, seed=1234)
 effs <- getEffects(sdat)
 \dontrun{
-(ans <- siena07(alg, data=sdat, effects=effs, returnDeps=TRUE, batch=TRUE))
+(ans <- siena07(alg, data=sdat, effects=effs, returnDeps=TRUE))
 # See manual Section 9.1 for information about the following functions
 edges.to.adj <- function(x,n){
 # create empty adjacency matrix
@@ -275,7 +276,7 @@
 ego <- rep.int(1:n,n)
 alter <- rep(1:n, each=n)
 ones <- sapply(1:n^2, function(i)
-    {mean(sapply(ans$sims, function(x){the.edge(x[[1]][[2]],n,ego[i],alter[i])}))})
+    {mean(sapply(ans$sims, function(x){the.edge(x[[1]][[2]][[1]],n,ego[i],alter[i])}))})
 cbind(ego,alter,ones)
 matrix(ones,n,n)
     }

Modified: pkg/RSiena/man/siena08.Rd
===================================================================
--- pkg/RSiena/man/siena08.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/siena08.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -130,11 +130,11 @@
 effects.3 <- getEffects(dataset.3)
 effects.4 <- getEffects(dataset.4)
 effects.1 <- includeEffects(effects.1, transTrip)
-effects.1 <- setEffect(effects.1, cycle3, fix=TRUE, test=TRUE)
+effects.1 <- setEffect(effects.1, transRecTrip, fix=TRUE, test=TRUE)
 effects.3 <- includeEffects(effects.3, transTrip)
-effects.3 <- setEffect(effects.3, cycle3, fix=TRUE, test=TRUE)
+effects.3 <- setEffect(effects.3, transRecTrip, fix=TRUE, test=TRUE)
 effects.4 <- includeEffects(effects.4, transTrip)
-effects.4 <- setEffect(effects.4, cycle3, fix=TRUE, test=TRUE)
+effects.4 <- setEffect(effects.4, transRecTrip, fix=TRUE, test=TRUE)
 ans.1 <- siena07(OneAlgorithm, data=dataset.1, effects=effects.1, batch=TRUE)
 ans.3 <- siena07(OneAlgorithm, data=dataset.3, effects=effects.3, batch=TRUE)
 ans.4 <- siena07(OneAlgorithm, data=dataset.4, effects=effects.4, batch=TRUE)
@@ -142,6 +142,7 @@
 ans.3
 ans.4
 (meta <- siena08(ans.1, ans.3, ans.4))
+plot(meta, which=2:3, layout = c(2,1))
 # For specifically presenting the Fisher combinations:
 # First determine the components of meta with estimated effects:
 which.est <- sapply(meta, function(x){ifelse(is.list(x),!is.null(x$cjplus),FALSE)})

Modified: pkg/RSiena/man/sienaDependent.Rd
===================================================================
--- pkg/RSiena/man/sienaDependent.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/sienaDependent.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -69,19 +69,31 @@
 ## note that the following example works although the node sets do not yet exist!
 mynet3 <- sienaDependent(array(c(s501, s502, s503), dim=c(50, 50, 3)),
        type="bipartite", nodeSet=c("senders", "receivers"))
-## sparse matrix input - create some RSiena edgelists first
+## sparse matrix input
+## To show this, we first go back from the adjacency matrices to edgelists.
+## The manual shows one way to do this.
+## Another way is to use the sparse matrix representation which internally
+## indeed is an edge list:
 library(Matrix)
 tmps501 <- as(Matrix(s501), "dgTMatrix")
 tmps502 <- as(Matrix(s502), "dgTMatrix")
 tmps503 <- as(Matrix(s503), "dgTMatrix")
+## If you are interested in the internal structure of these sparse matrices,
+## you can request
+str(tmps501)
+## Slot @i is the row, @j is the column, and @x the value;
+## here the values all are 1.
+## The edge lists now are created as matrices in the following way,
+## where the columns are sender, receiver, tie value, and wave:
 mymat1 <- cbind(tmps501 at i + 1, tmps501 at j + 1, 1, 1)
 mymat2 <- cbind(tmps502 at i + 1, tmps502 at j + 1, 1, 2)
 mymat3 <- cbind(tmps503 at i + 1, tmps503 at j + 1, 1, 3)
 mymat <- rbind(mymat1, mymat2, mymat3)
-library(Matrix)
-## mymat includes all 3 waves
-mymatlist <- by(mymat, mymat[, 4], function(x)
-    spMatrix(50, 50, x[, 1], x[, 2], x[, 3]))
+## mymat is an edge list and includes all 3 waves.
+## The edge lists do not contain information about the number of nodes,
+## so that has to be supplied additionally; here it is 50:
+mymatlist <- by( mymat, mymat[, 4], function(x)
+    spMatrix(50, 50, x[, 1], x[, 2], x[, 3]) )
 mynet4 <- sienaDependent(mymatlist)
 ## or alternatively
 mymat1 <- mymat[mymat[, 4] == 1, ]

Modified: pkg/RSiena/man/sienaGOF-auxiliary.Rd
===================================================================
--- pkg/RSiena/man/sienaGOF-auxiliary.Rd	2018-05-06 13:27:16 UTC (rev 335)
+++ pkg/RSiena/man/sienaGOF-auxiliary.Rd	2018-10-30 11:22:36 UTC (rev 336)
@@ -175,13 +175,13 @@
 \examples{
 ### For use out of the box:
 
-mynet1 <- sienaDependent(array(c(s501, s502, s503), dim=c(50, 50, 3)))
-mybeh <- sienaDependent(s50a, type="behavior")
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/rsiena -r 336


More information about the Rsiena-commits mailing list