[Rsiena-commits] r338 - in pkg/RSienaTest: . R data doc man src/model/effects src/model/ml tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Jan 15 17:54:21 CET 2019


Author: tomsnijders
Date: 2019-01-15 17:54:20 +0100 (Tue, 15 Jan 2019)
New Revision: 338

Modified:
   pkg/RSienaTest/ChangeLog
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/NAMESPACE
   pkg/RSienaTest/R/bayesTest.r
   pkg/RSienaTest/R/sienaBayes.r
   pkg/RSienaTest/R/sienaprint.r
   pkg/RSienaTest/R/sienatable.r
   pkg/RSienaTest/data/allEffects.csv
   pkg/RSienaTest/doc/RSiena.bib
   pkg/RSienaTest/doc/RSiena_Manual.pdf
   pkg/RSienaTest/doc/RSiena_Manual.tex
   pkg/RSienaTest/man/RSiena-package.Rd
   pkg/RSienaTest/man/print.sienaBayesFit.Rd
   pkg/RSienaTest/man/sienaAlgorithmCreate.Rd
   pkg/RSienaTest/man/sienaBayes.Rd
   pkg/RSienaTest/man/sienaFit.Rd
   pkg/RSienaTest/src/model/effects/EffectFactory.cpp
   pkg/RSienaTest/src/model/effects/SameCovariateActivityEffect.cpp
   pkg/RSienaTest/src/model/effects/SameCovariateActivityEffect.h
   pkg/RSienaTest/src/model/ml/MLSimulation.cpp
   pkg/RSienaTest/tests/parallel.Rout.save
Log:
Only RSienaTest, for AdSUM

Modified: pkg/RSienaTest/ChangeLog
===================================================================
--- pkg/RSienaTest/ChangeLog	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/ChangeLog	2019-01-15 16:54:20 UTC (rev 338)
@@ -1,3 +1,17 @@
+2019-01-02 R-Forge Revision 338, packages version 1.2-15.
+Changes in RSiena and RSienaTest:
+   * New effects sameXReciAct and diffXReciAct.
+   * Increased length of MLSimulation::preburnin.
+   * Changes in sienaFitThetaTable, averageTheta.last, sdTheta.last in sienaprint.r
+     to enable change in extract.posteriorMeans (see below).
+   * siena.table adapted for sienaBayes results.
+Changes in RSienaTest:
+   * New functions shortBayesResults and plotPostMeansMDS.
+   * extract.posteriorMeans works also for an object saved as PartialBayesResult
+     (which has NA results for as yet unfinished runs) 
+     (this was achieved by changes in sienaprint.r, see above).
+   * Examples added to help page for print.sienaBayesFit (in dontrun...).
+
 2018-12-05 R-Forge Revision 337, packages version 1.2-14.
 Changes in RSiena and RSienaTest:
    * Check for length of parameter mult for ML estimation (initializeFRAN), 
@@ -12,7 +26,9 @@
      prior mean is used for initial parameter values;
      prewarming phase introduced before improveMH;
      in case prevBayes is used, also parameter nImproveMH in the function 
-     call of sienaBayes supersedes this parameter in the prevBayes object.
+     call of sienaBayes supersedes this parameter in the prevBayes object;
+     checks for dimensions of prior mean and covariance matrix
+     put earlier in the initialization phase.
 
 2018-10-29 R-Forge Revision 336, packages version 1.2-13.
 Changes in RSiena and RSienaTest:

Modified: pkg/RSienaTest/DESCRIPTION
===================================================================
--- pkg/RSienaTest/DESCRIPTION	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/DESCRIPTION	2019-01-15 16:54:20 UTC (rev 338)
@@ -2,8 +2,8 @@
 Package: RSienaTest
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.2-14
-Date: 2018-12-05
+Version: 1.2-15
+Date: 2019-01-02
 Author: Ruth Ripley, Krists Boitmanis, Tom A.B. Snijders, Felix Schoenenberger
 Depends: R (>= 2.15.0)
 Imports: Matrix, tcltk, lattice, parallel, MASS, RUnit, methods

Modified: pkg/RSienaTest/NAMESPACE
===================================================================
--- pkg/RSienaTest/NAMESPACE	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/NAMESPACE	2019-01-15 16:54:20 UTC (rev 338)
@@ -18,7 +18,8 @@
 
 export(
 	sienaBayes, glueBayes, simpleBayesTest, multipleBayesTest,
-	extract.sienaBayes, extract.posteriorMeans, algorithms, profileLikelihoods,
+	extract.sienaBayes, extract.posteriorMeans, plotPostMeansMDS, 
+   shortBayesResults, algorithms, profileLikelihoods,
 	sienaRIDynamics
 )
 

Modified: pkg/RSienaTest/R/bayesTest.r
===================================================================
--- pkg/RSienaTest/R/bayesTest.r	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/R/bayesTest.r	2019-01-15 16:54:20 UTC (rev 338)
@@ -228,8 +228,9 @@
 	x
 }
 
-plot.multipleBayesTest <- function(x, xlim=NULL, ylim=NULL,
-	main=NULL, ...){
+
+##@plot.multipleBayesTest methods
+plot.multipleBayesTest <- function(x, xlim=NULL, ylim=NULL,	main=NULL, ...){
 	if (!inherits(x, 'multipleBayesTest'))
 	{
 		stop("not a legitimate multipleBayesTest object")
@@ -430,7 +431,7 @@
 		stop('z must be a sienaBayesFit object')
 	}
 
-	ntot <- dim(z$ThinPosteriorMu)[1]
+	ntot <- max(which(!is.na(z$ThinPosteriorMu[,1])))
 	nit <- ntot - nfirst + 1
 	nind <- sum(z$varyingParametersInGroup)
 	res <- matrix(NA, z$nGroup, 2*nind)
@@ -456,4 +457,45 @@
 		dimnames(res) <- list(1:dim(res)[1], fName)
 	}
 	res
+}
+
+
+##@plotPostMeansMDS MDS plot of posterior means for sienaBayesFit object
+plotPostMeansMDS <- function(x, pmonly=0, nfirst=NULL, ...){
+# This function makes an MDS plot of the posterior means in z;
+# for the method: see MASS (book) p. 308.
+# if pmonly=0 posterior means and standard deviations,
+# if pmonly=1 only the posterior means,
+# if pmonly=2 only the posterior standard deviations.
+	if (!inherits(x, "sienaBayesFit"))
+	{
+		stop('x must be a sienaBayesFit object')
+	}
+	if (is.null(nfirst))
+	{
+		nfirst <- x$nwarm+1
+	}
+#	requireNamespace(MASS)
+	is.even <- function(k){k %% 2 == 0}
+	is.odd <- function(k){k %% 2 != 0}
+	cat('extracting posterior means ...\n')
+	pm <- extract.posteriorMeans(x, nfirst=nfirst)
+	if (pmonly <= 0)
+	{ 
+		vars <- (1:dim(pm)[2])
+	}
+	else if (pmonly == 1)
+	{ 
+		vars <- is.odd(1:dim(pm)[2])
+	}
+	else
+	{ 
+		vars <- is.even(1:dim(pm)[2])
+	}
+	cat('calculating MDS solution ...\n')
+	corpm <- cor(t(pm[,vars]))
+	mds <- isoMDS(1-corpm)
+	eqscplot(mds$points, type='n', ...)
+	text(mds$points, labels=as.character(1:dim(mds$points)[1]), ...)
+	invisible(mds$points)
 }
\ No newline at end of file

Modified: pkg/RSienaTest/R/sienaBayes.r
===================================================================
--- pkg/RSienaTest/R/sienaBayes.r	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/R/sienaBayes.r	2019-01-15 16:54:20 UTC (rev 338)
@@ -2860,11 +2860,10 @@
 }
 
 ##@protectedInverse inverse of p.s.d matrix
-protectedInverse <- function(x)
+protectedInverse <- function(x){
+	if (inherits(try(xinv <- chol2inv(chol(x)),
+		silent=TRUE), "try-error"))
 	{
-		if (inherits(try(xinv <- chol2inv(chol(x)),
-			silent=TRUE), "try-error"))
-		{
 	# Now make this x positive definite, if it is not.
 	# See above for a more extensive treatment of the same.
 	# Adapted from function make.positive.definite in package corpcor
@@ -2872,24 +2871,21 @@
 	# but changed to make the matrix positive definite (psd)
 	# instead of nonnegative definite.
 	# The idea is to left-truncate all eigenvalues to delta0.
-	# The construction with tol, not used now,
-	# is to ensure positive definiteness given numerical inaccuracy.
-			es <- eigen(x)
-			esv <- es$values
-			delta0 <- 1e-6
-			cat("protectedInverse: Eigenvalues Sigma = ", sort(esv), "\n")
-			if (min(esv) < delta0)
-			{
-				delta <- delta0
-				tau <- pmax(delta, esv)
-		#		cat("Smallest eigenvalue of Sigma now is ",
-		#					min(esv),"; make posdef.\n")
-				xinv <- es$vectors %*%
-							diag(1/tau, dim(x)[1]) %*% t(es$vectors)
-			}
+		es <- eigen(x)
+		esv <- es$values
+		delta0 <- 1e-6
+		cat("protectedInverse: Eigenvalues Sigma = ", sort(esv), "\n")
+		if (min(esv) < delta0)
+		{
+			delta <- delta0
+			tau <- pmax(delta, esv)
+	#		cat("Smallest eigenvalue of Sigma now is ",
+	#					min(esv),"; make posdef.\n")
+			xinv <- es$vectors %*% diag(1/tau, dim(x)[1]) %*% t(es$vectors)
 		}
-		xinv
 	}
+	xinv
+}
 
 
 ##@trafo link function rates

Modified: pkg/RSienaTest/R/sienaprint.r
===================================================================
--- pkg/RSienaTest/R/sienaprint.r	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/R/sienaprint.r	2019-01-15 16:54:20 UTC (rev 338)
@@ -700,11 +700,10 @@
 }
 
 ##@averageTheta.last Miscellaneous
-
 averageTheta.last <- function(z, groupOnly=0, nfirst=z$nwarm+1)
 {
 	ntot <- sum(!is.na(z$ThinPosteriorMu[,1]))
-	ntott <- dim(z$ThinParameters)[1]
+	ntott <- sum(!is.na(z$ThinParameters[,1,1]))
 
 	if (nfirst > ntot)
 	{
@@ -719,11 +718,12 @@
 	for (group in 1:z$nGroup)
 	{
 		thetaMean[z$ratePositions[[group]]] <- colMeans(
-				z$ThinParameters[nfirst:ntott, group,
+					z$ThinParameters[nfirst:ntott, group,
 					!z$generalParametersInGroup, drop=FALSE], na.rm=TRUE)
 		postVarMean[z$ratePositions[[group]]] <- apply(
-				z$ThinParameters[nfirst:ntott,
-				group, !z$generalParametersInGroup, drop=FALSE], 3, var, na.rm=TRUE)
+					z$ThinParameters[nfirst:ntott,
+					group, !z$generalParametersInGroup, drop=FALSE], 3,
+					var, na.rm=TRUE)
 	}
 
 	if (is.null(z$priorRatesFromData))
@@ -734,32 +734,33 @@
 	if (groupOnly != 0)
 	{
 		thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
-				z$ThinParameters[(nfirst):ntott, groupOnly,
-					z$varyingGeneralParametersInGroup, drop=FALSE], na.rm=TRUE)
+				z$ThinParameters[nfirst:ntott, groupOnly,
+				z$varyingGeneralParametersInGroup, drop=FALSE], na.rm=TRUE)
 	}
 	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)})
+			thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
+				z$ThinPosteriorMu[nfirst:ntot, , drop=FALSE], na.rm=TRUE)
+			postVarMean[z$varyingObjectiveParameters] <-
+				sapply(1:(dim(z$ThinPosteriorSigma)[2]),
+					function(i){mean(z$ThinPosteriorSigma[nfirst:ntot,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)
-	postVarMean[z$varyingObjectiveParameters] <- sapply(1:(dim(z$ThinPosteriorSigma)[2]),
-		function(i){mean(z$ThinPosteriorSigma[nfirst:dim(z$ThinPosteriorSigma)[1],i,i], na.rm=TRUE)}
+			thetaMean[(z$set1)&(!z$basicRate)] <- colMeans(
+				z$ThinPosteriorMu[nfirst:ntot,
+								z$objectiveInVarying, drop=FALSE], na.rm=TRUE)
+			postVarMean[z$varyingObjectiveParameters] <-
+			sapply(1:(dim(z$ThinPosteriorSigma)[2]),
+				function(i){mean(z$ThinPosteriorSigma[nfirst:ntot,i,i], na.rm=TRUE)}
 														)[z$objectiveInVarying]
+		}
 	}
-	}
-		thetaMean[z$set2] <-
-			colMeans(z$ThinPosteriorEta[nfirst:dim(z$ThinPosteriorEta)[1],, drop=FALSE],
-						na.rm=TRUE)
+	thetaMean[z$set2] <-
+			colMeans(z$ThinPosteriorEta[nfirst:ntot,, drop=FALSE], na.rm=TRUE)
 	thetaMean[z$fix & (!z$basicRate)] <- z$thetaMat[1,z$fix & (!z$basicRate)]
 	list(thetaMean, postVarMean)
 }
@@ -768,7 +769,7 @@
 sdTheta.last <- function(z, groupOnly=0, nfirst=z$nwarm+1)
 {
 	ntot <- sum(!is.na(z$ThinPosteriorMu[,1]))
-	ntott <- dim(z$ThinParameters)[1]
+	ntott <- sum(!is.na(z$ThinParameters[,1,1]))
 	if (nfirst >= ntot-1)
 	{
 		stop('Sample did not come beyond warming')
@@ -1261,7 +1262,15 @@
 	}
 	else
 	{
-		cat("Note: this summary does not contain a convergence check.\n\n")
+		cat("Note: this summary does not contain a convergence check.\n")
+		if (is.null(nfirst))
+		{
+			cat("Note: the print function for sienaBayesFit objects")
+			cat(" can also use a parameter nfirst,\n")
+			cat("      indicating the first run")
+			cat(" from which convergence is assumed.\n")
+		}
+		cat("\n")
 		if (length(x$f$groupNames) > 1)
 		{
 			cat("Groups:\n")
@@ -1563,3 +1572,32 @@
 	invisible(x)
 }
 
+##@shortBayesResult abbreviated sienaBayesFit results
+shortBayesResults <- function(x, nfirst=NULL){
+	if (!inherits(x, "sienaBayesFit"))
+	{
+		stop('x must be a sienaBayesFit object')
+	}
+	if (is.null(nfirst))
+	{
+		nfirst <- x$nwarm+1
+	}
+	df1 <- sienaFitThetaTable(x, fromBayes=TRUE, nfirst=nfirst)[[1]][,
+		c("text", "value", "se", "cFrom", "cTo", "postSd", "cSdFrom", "cSdTo" )]
+	df1$postSd[is.na(df1$cSdFrom)] <- NA
+	df1$postSd <- as.numeric(df1$postSd)
+	df1$cSdFrom <- as.numeric(df1$cSdFrom)
+	df1$cSdTo <- as.numeric(df1$cSdTo)
+	df2 <- as.data.frame(x$requestedEffects[,c("name","shortName", "interaction1", "interaction2",
+		"type", "randomEffects", "fix", "parm", "period", "effect1", "effect2", "effect3", "group")])
+	df2$period <- as.numeric(df2$period)
+	replace1 <- function(x){ifelse(x=="text", "effectName", x)}
+	replace2 <- function(x){ifelse(x=="value", "postMeanGlobal", x)}
+	replace3 <- function(x){ifelse(x=="se", "postSdGlobal", x)}
+	replace4 <- function(x){ifelse(x=="postSd", "postSdBetween", x)}
+	dfs <- cbind(df2, df1)
+	dfr <- dfs
+	names(dfr) <- replace1(replace2(replace3(replace4(names(dfs)))))
+	dfr
+}
+

Modified: pkg/RSienaTest/R/sienatable.r
===================================================================
--- pkg/RSienaTest/R/sienatable.r	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/R/sienatable.r	2019-01-15 16:54:20 UTC (rev 338)
@@ -6,18 +6,44 @@
 ##  * File: sienatable.r
 ##  *
 ##  * Description: This file contains the code to save a latex or html table of
-##  * estimates for a sienaFit object
+##  * estimates for a sienaFit or sienaBayesFit object
 ##  * Written by Charlotte Greenan; small modifications by Tom Snijders.
 ##  *
 ##  ***************************************************************************/
 
 ##@siena.table siena07 Saves latex or html table of estimates
-## for a sienaFit object
+## for a sienaFit or sienaBayesFit object
 siena.table <- function(x, type='tex',
 	file=paste(deparse(substitute(x)),'.',type,sep=""),
 	vertLine=TRUE, tstatPrint=FALSE,
-	sig=FALSE, d=3)
+	sig=FALSE, d=3, nfirst=NULL)
 {
+	fromBayes <- FALSE
+	xkind.string <- "sienaFit"
+	if (!inherits(x, "sienaFit"))
+	{
+		if (inherits(x, "sienaBayesFit"))
+		{
+			fromBayes <- TRUE
+			sig <- FALSE
+			tstatPrint <- FALSE
+			if (is.null(nfirst))
+			{
+				nfirst <- x$nwarm + 1
+				cat("Note: the print function for sienaBayesFit objects")
+				cat(" can also use a parameter nfirst,\n")
+				cat("      indicating the first run")
+				cat(" from which convergence is assumed.\n")
+				cat("      The default value used now is nfirst =", 
+					x$nwarm + 1, ".\n")
+			}			
+			xkind.string <- "sienaBayesFit"
+		}
+		else
+		{
+			stop('x must be a sienaFit or sienaBayesFit object')
+		}
+	}
 	tstat <- tstatPrint
 	effects <- x$requestedEffects
 	p <- x$pp
@@ -28,23 +54,34 @@
 	{
 		condrates <- length(x$rate)
 	}
-
-	theta <- x$theta
-	theta[diag(x$covtheta) < 0.0 | x$fixed] <- NA
-	ses <- sqrt(diag(x$covtheta))
-	ses[x$fixed] <- NA
-	max.t1 <- max(abs(x$tstat[!x$fixed]))
-	dd <- 2
-	max.t <- round(max.t1, digits = dd)
-	if (max.t < max.t1)
+	
+	if (fromBayes)
 	{
-		max.t <- max.t + 10^{-dd} #needs to be rounded up
+		xx <- shortBayesResults(x, nfirst=nfirst)
+		theta <- xx$postMeanGlobal
+		ses <- xx$postSdGlobal
+		se.string <- 'psd.'
 	}
-	maxlincomb.t1 <- x$tconv.max
-	maxlincomb.t <- round(maxlincomb.t1, digits = dd)
-	if (maxlincomb.t < maxlincomb.t1)
+	else
 	{
-		maxlincomb.t <- maxlincomb.t + 10^{-dd} #needs to be rounded up
+		theta <- x$theta
+		theta[diag(x$covtheta) < 0.0 | x$fixed] <- NA
+		ses <- sqrt(diag(x$covtheta))
+		ses[x$fixed] <- NA
+		max.t1 <- max(abs(x$tstat[!x$fixed]))
+		dd <- 2
+		max.t <- round(max.t1, digits = dd)
+		if (max.t < max.t1)
+		{
+			max.t <- max.t + 10^{-dd} #needs to be rounded up
+		}
+		maxlincomb.t1 <- x$tconv.max
+		maxlincomb.t <- round(maxlincomb.t1, digits = dd)
+		if (maxlincomb.t < maxlincomb.t1)
+		{
+			maxlincomb.t <- maxlincomb.t + 10^{-dd} #needs to be rounded up
+		}
+		se.string <- 's.e.'
 	}
 	if (length(x$condvarno) == 0)
 	{
@@ -302,19 +339,28 @@
 
 		startTable <- tableSection(c("<TABLE border=1  rules=none frame = hsides>",
 				paste("<TR><TD>Effect</TD><TD>   par.</TD><TD></TD>
-					<TD>   (s.e.)</TD>",start.tstat,"</TR>")))
+					<TD>   ",se.string,"</TD>",start.tstat,"</TR>")))
 		midTable <- tableSection(c("",""))
 		indentTable <- tableSection("")
 		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>
+		if (fromBayes)
+		{
+			footnote <- "<TR> <TD colspan=9 align=left> par=posterior mean;
+						psd = posterior standard deviation.
+							</TD> </TR> <TR> </TR></TABLE>"
+		}
+		else
+		{
+			footnote <- c(paste(" <TR> <TD colspan=9 align=left>
 							all convergence t ratios < ",
 							max.t,".</TD> </TR> <TR> </TR>",
 							" <TR> <TD colspan=9 align=left>
 							Overall maximum convergence ratio ",
 							maxlincomb.t,".</TD> </TR> <TR> </TR>",
 							sep="",collapse=""),"</TABLE>")
+		}
 		if (sig)
 		{
 			footnote <- c(footnoteStart, "<TR> <TD colspan=4 align=left> &#134 p < 0.1;
@@ -346,7 +392,7 @@
 		{
 			linesep=""
 		}
-		startTable <- tableSection(c(paste("% Table based on sienaFit object",
+		startTable <- tableSection(c(paste("% Table based on", xkind.string, "object",
 					deparse(substitute(x)), ',', date()),
 				paste("\\begin{tabular}{l",
 					linesep,
@@ -356,14 +402,23 @@
 				"\\rule{0pt}{2ex}\\relax",
 				paste("Effect &\\multicolumn{2}{c}{par.}&\\multicolumn{2}{c",
 					linesep,
-					"}{(s.e.)}",
+					"}{",se.string,"}",
 					start.tstat2,"\\\\[0.5ex]"),
 				"\\hline"))
 		midTable <- tableSection(c("\\hline",
 				"\\rule{0pt}{2ex}\\relax"))
 		indentTable <- tableSection("\\rule{0pt}{2ex}\\relax")
 		ruleTable <- tableSection("\\hline")
-		footnote <- c(paste("\\multicolumn{5}{l}\n   ",
+		if (fromBayes)
+		{
+			footnote <- c(paste("\\multicolumn{5}{l}\n   ",
+				"{\\footnotesize{par = posterior mean; psd = posterior standard deviation.}}\\\\\n",
+				sep="",collapse=""),
+			"\\end{tabular}")
+		}
+		else
+		{
+			footnote <- c(paste("\\multicolumn{5}{l}\n   ",
 				"{\\footnotesize{convergence $t$ ratios all $<$ ", max.t,
 				".}}\\\\\n",
 				"\\multicolumn{5}{l}",
@@ -371,13 +426,13 @@
 				maxlincomb.t,".}}",
 				sep="",collapse=""),
 			"\\end{tabular}")
-
-		if (sig == TRUE)
-		{
-			footnote <- c("\\multicolumn{5}{l}{\\footnotesize{$^\\dagger$ $p$ $<$ 0.1;
-				$^\\ast$ $p$ $<$ 0.05; $^{\\ast\\ast}$ $p$ $<$ 0.01;
-				$^{\\ast\\ast\\ast}$ $p$ $<$ 0.001;}}\\\\" ,footnote)
-		}
+			if (sig == TRUE)
+			{
+				footnote <- c("\\multicolumn{5}{l}{\\footnotesize{$^\\dagger$ $p$ $<$ 0.1;
+					$^\\ast$ $p$ $<$ 0.05; $^{\\ast\\ast}$ $p$ $<$ 0.01;
+					$^{\\ast\\ast\\ast}$ $p$ $<$ 0.001;}}\\\\" ,footnote)
+			}
+		}		
 	}
 
 	endTable <- tableSection(footnote)

Modified: pkg/RSienaTest/data/allEffects.csv
===================================================================
--- pkg/RSienaTest/data/allEffects.csv	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/data/allEffects.csv	2019-01-15 16:54:20 UTC (rev 338)
@@ -289,6 +289,8 @@
 covarNonSymmetricObjective,outd. act. to hom. xxxxxx,sum sqr. outd. to hom. values on xxxxxx,homXOutAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
 covarNonSymmetricObjective,outd. act. weight alt. xxxxxx,sum sqr. outd. weight alt. xxxxxx,altXOutAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
 covarNonSymmetricObjective,outd. act. to dif. xxxxxx,sum sqr. outd. to dif. values on xxxxxx,diffXOutAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
+covarNonSymmetricObjective,rec.deg. act. to same xxxxxx,sum sqr. outd. to same values on xxxxxx,sameXReciAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
+covarNonSymmetricObjective,rec.deg. act. to dif. xxxxxx,sum sqr. outd. to dif. values on xxxxxx,diffXReciAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
 covarNonSymmetricObjective,transitive triplets same xxxxxx,Number of transitive triplets same on xxxxxx,sameXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
 covarNonSymmetricObjective,transitive triplets diff. xxxxxx,Number of transitive triplets diff. on xxxxxx,diffXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
 covarNonSymmetricObjective,transitive triplets homog. xxxxxx,Number of transitive triplets homogeneous on xxxxxx,homXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE

Modified: pkg/RSienaTest/doc/RSiena.bib
===================================================================
--- pkg/RSienaTest/doc/RSiena.bib	2018-12-05 21:44:35 UTC (rev 337)
+++ pkg/RSienaTest/doc/RSiena.bib	2019-01-15 16:54:20 UTC (rev 338)
@@ -79,11 +79,14 @@
   year = {2010}
 }
 
+
+
 @book{Agresti2012,
   author = {Alan Agresti},
   publisher = {Wiley-Interscience},
   title = {Categorical Data Analysis},
   series = {Wiley Series in Probability and Statistics},
+  address = {New York},
   edition = {3rd},
   year = {2012}
 }
@@ -418,13 +421,31 @@
 
 
 @book{Blau55,
-   Author = {Blau, Peter},
+   Author = {Blau, Peter M.},
    Title = {The Dynamics of Bureaucracy},
    Publisher = {University of Chicago Press},
    Address = {Chicago},
    Year = {1955} }
 
 
+ at book{Blau77,
+   Author = {Blau, Peter M.},
+   Title = {Inequality and heterogeneity: {A} primitive theory of social structure },
+   Publisher = {Free Press},
+   Address = {New York},
+   Year = {1977}
+}
+
+
+ at book{Byrn71,
+   Author = {Byrne, Donn Erwin},
+   Title = {The Attraction Paradigm},
+   Publisher = {Academic Press},
+   Address = {New York},
+   Year = {1971}
+}
+
+
 @article{Block2015,
 title = "Reciprocity, transitivity, and the mysterious three-cycle",
 journal = "Social Networks ",
@@ -918,6 +939,16 @@
   year={2011}
 }
 
+ at article{CheadleSchwadel2012,
+title = "The 'friendship dynamics of religion,' or the 'religious dynamics of friendship'?
+            {A} social network analysis of adolescents who attend small schools",
+journal = "Social Science Research",
+volume = "41",
+pages = "1198--1212",
+year = "2012",
+author = "Jacob E. Cheadle and Philip Schwadel"
+}
+
 @article{Cheadle_etal2013,
   author ={Jacob E. Cheadle and Michael Stevens and Deadric T. Williams and
              Bridget J. Goosby},
@@ -1045,7 +1076,18 @@
  publisher= {Belknap Press of Harvard University Press},
   year =         1990}
 
+ at Article{CookSchwadelCheadle2017,
+    author="Cook, J. Benjamin and Schwadel, Philip and Cheadle, Jacob E.",
+    title="The Origins of Religious Homophily in a Medium and Large School",
+    journal="Review of Religious Research",
+    year="2017",
+    volume="59",
+    number="1",
+    pages="65--80"}
+}
 
+
+
 @book{Coombs1964,
   author =       {Clyde H. Coombs},
   title =        {A Theory of Data},
@@ -1117,6 +1159,15 @@
     pages={843--852}
 }
 
+ at article{Davis1967,
+  title={Clustering and structural balance in graphs},
+  author={Davis, James A},
+  journal={Human Relations},
+  volume={20},
+  pages={181--187},
+  year={1967}
+}
+
 @INCOLLECTION{Davis79,
 AUTHOR = "James A. Davis",
 TITLE = {The Davis/Holland/Leinhardt studies: {An} overview},
@@ -1185,7 +1236,7 @@
 
 @article{Delitsch1900,
   author =       {Johannes {Delitsch}},
-  title =        {\"{U}ber Sch\"{u}lerfreundschaften in einer {V}olksschulklasse},
+  title =        {\"{U}ber {S}ch\"{u}lerfreundschaften in einer {V}olksschulklasse},
   journal =  {Zeitschrift f\"{u}r {K}inderforschung},
   year =     1900,
   volume =   5,
@@ -1445,8 +1496,15 @@
  publisher={Houghton-Mifflin}
  }
 
+ at article{Emerson1976,
+    author = {Richard M. Emerson},
+    year = {1976},
+    title = {Social  exchange  theory},
+    journal = {Annual  Review  of Sociology},
+    volume = {2},
+    pages = {335--362}
+}
 
-
 @ARTICLE{EmirbayerGoodwin94,
 AUTHOR = "M. {Emirbayer} and J. {Goodwin}",
 TITLE = {Network Analysis, Culture, and the Problem of Agency},
@@ -1476,6 +1534,13 @@
 PAGES = "1495--1533"
 }
 
+ at book{Epstein2006,
+  title={Generative social science: {S}tudies in agent-based computational modeling},
+  author={Epstein, Joshua M},
+  year={2006},
+  location={Princeton},
+  publisher={Princeton University Press}
+}
 
 % Erdos first name is Paul
 
@@ -1574,6 +1639,15 @@
     ADDRESS = "Oxford, U.K."
  }
 
+ at article{FelmleeSprecherBassin1990,
+ author = {Diane Felmlee and Susan Sprecher and Edward Bassin},
+ journal = {Social Psychology Quarterly},
+ pages = {13--30},
+ title = {The Dissolution of Intimate Relationships: {A} Hazard Model},
+ volume = {53},
+ year = {1990}
+}
+
 @article{Field2003,
   title={The problems in using fixed-effects models of meta-analysis on real-world data},
   author={Field, Andy P},
@@ -1807,6 +1881,17 @@
   year={2017}
 }
 
+ at article{FujimotoEA2018,
+  author={Kayo Fujimoto and {Tom A.B.} Snijders and Thomas W. Valente},
+  title={Multivariate dynamics of one-mode and two-mode networks:
+  {E}xplaining similarity in sports participation among friends},
+  volume={6},
+  issue={3},
+  journal={Network Science},
+  year={2018},
+    pages={370–395}
+}
+
 @ARTICLE{GalaskiewiczBurt1991,
 AUTHOR = {Joseph {Galaskiewicz} and Ronald S. {Burt}},
 TITLE = {Interorganization Contagion in Corporate Philanthropy},
@@ -2363,6 +2448,31 @@
    Address = {Cambridge},
    Year = {2005} }
 
+ at book{HedstromSwedberg1998,
+  title={Social mechanisms: An analytical approach to social theory},
+  editor={Hedstr{\"o}m, Peter and Swedberg, Richard},
+  year={1998},
+  address = {Cambridge},
+  publisher={Cambridge University Press}
+}
+
+ at book{HedstromSwedberg,
+   Author = {Peter Hedstr\"om},
+   Title = {Dissecting the Social: On the Principles of Analytical Sociology},
+   Publisher = {Cambridge University Press},
+   Address = {Cambridge},
+   Year = {2005} }
+
+
+ at article{Heider1948,
+   Author = {Fritz Heider},
+   Title = {Attitudes and cognitive organization},
+   Journal = {Journal of Psychology},
+   Volume = {21},
+   Pages = {107--112},
+   Year = {1948} }
+
+
 @BOOK{Heider58,
 AUTHOR = "Fritz {Heider}",
 TITLE = {The Psychology of Interpersonal Relations},
@@ -2623,8 +2733,7 @@
   year={2013}
 }
 
- at article{
-Hubert85,
+ at article{Hubert85,
    Author = {Hubert, Lawrence J.},
    Title = {Combinatorial Data Analysis: Association and Partial Association},
    Journal = {Psychometrika},
@@ -2635,8 +2744,7 @@
 
 
 
- at book{
-Hubert87,
+ at book{Hubert87,
    Author = {Hubert, Lawrence J.},
    Title = {Assignment Methods in Combinatorial Data Analysis},
    Publisher = {Marcel Dekker, INC.},
@@ -2645,8 +2753,7 @@
    Series = {Statistics: Textbooks and Monographs},
    Year = {1987} }
 
- at article{
-HubertGolledge81,
+ at article{HubertGolledge81,
    Author = {Hubert, Lawrence J. and Golledge, Reginald G.},
    Title = {A Heuristic Method for the Comparison of Related Structures},
    Journal = {Journal of Mathematical Psychology},
@@ -2769,6 +2876,15 @@
   year={2000}
 }
 
+ at article{HustonLevinger1978,
+author = {Huston, T L and Levinger, G},
+title = {Interpersonal Attraction and Relationships},
+journal = {Annual Review of Psychology},
+volume = {29},
+pages = {115--156},
+year = {1978}
+}
+
 @article{IacobucciWasserman1990,
   title={Social networks with two sets of actors},
   author={Iacobucci, Dawn and Wasserman, Stanley},
@@ -2954,6 +3070,26 @@
   pages = {  863--871}
 }
 
+ at Article{KalterKroneberg2014,
+author="Kalter, Frank and Kroneberg, Clemens",
+title="Between Mechanism Talk And Mechanism Cult:
+       {N}ew Emphases in Explanatory Sociology And Empirical Research",
+journal="KZfSS K{\"o}lner Zeitschrift f{\"u}r Soziologie und Sozialpsychologie",
+year="2014",
+volume="66",
+pages="91--115"
+}
+
+ at incollection{Kalter2016,
+  author = {Kalter, Frank},
+  publisher = {Wiley},
+  title = {Social Network Analysis in the Study of Ethnic Inequalities},
+  booktitle = {Emerging Trends in the Social and Behavioral Sciences},
+  editor = {R. A. Scott and S. M. Kosslyn},
+  note = {doi:10.1002/9781118900772.etrds0397},
+  year = {2016}
+}
+
 @TechReport{CILS4EU,
   title={Children of Immigrants Longitudinal Survey in Four {E}uropean Countries
   ({CILS4EU}): {M}otivation, Aims, and Design},
@@ -2964,21 +3100,50 @@
   year={2013}
 }
 
- at InCollection{KalterKruse2015,
+
+ at TechReport{CILS4EU2016,
+  title={Children of Immigrants Longitudinal Survey in Four {E}uropean Countries.
+  {S}ociometric Fieldwork Report},
+  institution={Mannheim University},
+  address={Mannheim},
+  author={Hanno Kruse and K. Jacob},
+  note = {Wave 1 - 2010/2011, v1.2.0},
+  year={2016}
+}
+
+ at TechReport{CILS4EU2016B,
+  title={Children of Immigrants Longitudinal Survey in Four {E}uropean Countries.
+  {S}ociometric Fieldwork Report},
+  institution={Mannheim University},
+  address={Mannheim},
+  author={Hanno Kruse and M. Wei{\ss}man and K. Jacob},
+  note = {Wave 2 - 2011/2012, v2.3.0},
+  year={2016}
+}
+
+ at TechReport{CILS4EU2017,
+  title={Children of Immigrants Longitudinal Survey in Four {E}uropean Countries
+  ({CILS4EU}) -- Full Version},
+  author={Kalter, Frank and Heath, Anthony F and Hewstone, Miles and Jonsson, Janne O
+  and Kalmijn, Matthijs and Kogan, Irena and {van Tubergen}, Frank},
+  institution={GESIS: GESIS Data Archive},
+  address={Cologne},
+  note = {ZA5353 Data file Version 3.3.0, doi:10.4232/cils4eu.5353.3.3.0},
+  doi = {10.4232/cils4eu.5353.3.3.0},
+  year={2017}
+}
+
+ at InCollection{KalterKruse2014,
   title={Ethnic diversity, homophily, and network cohesion in {European} classrooms},
   author={Kalter, Frank and Kruse, Hanno},
   booktitle={Social Cohesion and Immigration in Europe and North America:
   {M}echanisms, Conditions, and Causality},
-  editors={Ruud Koopmans, Bram Lancee, Merlin Schaeffer},
-  pages={187-207},
+  editor={Ruud Koopmans, Bram Lancee, Merlin Schaeffer},
+  pages={187--207},
   chapter={10},
   year={2014},
   publisher={Routledge}
 }
-Kalter, F., Kruse, H., 2015. Ethnic diversity, homophily, and network cohesion inEuropean classrooms.
- In: Koopmans, R., Lancee, B., Schaeffer, M. (Eds.),
- SocialCohesion and Immigration in Europe and North America: Mechanisms,
-  Condi-tions, and Causality. Routledge, London, pp. 187–207.
 
 @article{KatzProctor1959,
   author = {Leo Katz and Charles H. Proctor},
@@ -3190,8 +3355,8 @@
  }
 
 @article{KnechtEA2010,
-AUTHOR = {Andrea Knecht and Tom A. B.  Snijders and Chris Baerveldt and
-   {Christian E. G.} Steglich and Werner Raub},
+AUTHOR = {Andrea Knecht and Tom A. B. Snijders and Chris Baerveldt and
+   Christian E. G. Steglich and Werner Raub},
 YEAR = {2010},
 TITLE = {Friendship and Delinquency: Selection and Influence Processes in Early Adolescence},
 journal ={Social Development},
@@ -3200,7 +3365,7 @@
 }
 
 @article{KnechtBurkEA2010,
-AUTHOR = {Andrea Knecht and William J. Burk and Jeroen Weesie and {Christian E. G.} Steglich},
+AUTHOR = {Andrea Knecht and William J. Burk and Jeroen Weesie and Christian E. G. Steglich},
 YEAR = {2010},
 TITLE = {Friendship and alcohol use in early adolescence: {A} multilevel social network approach},
 journal ={Journal of Research on Adolescence},
@@ -3266,10 +3431,10 @@
 ADDRESS = "New York"
  }
 
- at report{KoskinenSnijders18,
+ at report{KoskinenSnijders19,
   author =       {Johan H. Koskinen and Tom A. B.  Snijders},
   title =        {Multilevel Longitudinal Analysis of Social Networks},
-  year =         2018,
+  year =         2019,
   note = {In preparation}}
 
 
@@ -3789,6 +3954,18 @@
 publisher = {Aldine de Gruyter},
 address = {New York}}
 
+
+ at INCOLLECTION{Lindenberg1992,
+AUTHOR = "Siegwart M. {Lindenberg}",
+TITLE = {The Method of Decreasing Abstraction},
+BOOKTITLE = "Rational Choice Theory. {A}dvocacy and Critique",
+PAGES = "3--20",
+PUBLISHER = "Sage",
+YEAR = "1992",
+EDITOR = "James S. Coleman and Thomas J. Fararo",
+ADDRESS = "Newbury Park, CA"
+}
+
 @INCOLLECTION{Lindenberg93,
 AUTHOR = "Siegwart M. {Lindenberg}",
 TITLE = {Framing, empirical evidence and applications},
@@ -4090,6 +4267,15 @@
    Volume = {48},
    Pages = {35--71}}
 
+ at article{Manzo2010,
+  title={Analytical sociology and its critics},
+  author={Manzo, Gianluca},
+  journal={European Journal of Sociology/Archives europ{\'e}ennes de sociologie},
+  volume={51},
+  pages={129--170},
+  year={2010}
+}
+
 @ARTICLE{Mark98,
   AUTHOR="Noah {Mark}",
   TITLE = "Beyond individual differences: Social differentiation from first
@@ -4243,6 +4429,15 @@
   year={2004}
 }
 
+ at article{MeerTolsma2014,
+author = {Tom {van der Meer} and Jochem Tolsma},
+title = {Ethnic Diversity and Its Effects on Social Cohesion},
+journal = {Annual Review of Sociology},
+volume = {40},
+pages = {459--478},
+year = {2014}
+}
+
 @article{MerckenEA09,
    Author = {Liesbeth Mercken and Tom A. B. Snijders and Christian E. G. Steglich and Hein de Vries},
    Title = {Dynamics of adolescent friendship networks and smoking behavior:
@@ -4402,6 +4597,15 @@
   year={2003}
 }
 
+ at article{Moody2001,
+ author = {James Moody},
+ journal = {American Journal of Sociology},
+ pages = {679--716},
+ title = {Race, School Integration, and Friendship Segregation in America},
+ volume = {107},
+ year = {2001}
+}
+
 @article{Moran1950,
   title={Notes on continuous stochastic phenomena},
   author={Moran, Patrick A.P.},
@@ -4423,6 +4627,15 @@
    year = {2008},
    URL = {http://jasss.soc.surrey.ac.uk/11/1/5.html}}
 
+ at article{MouwEntwisle2006,
+ author = {Ted Mouw and Barbara Entwisle},
+ journal = {American Journal of Sociology},
+ pages = {394--441},
+ title = {Residential Segregation and Interracial Friendship in Schools},
+ volume = {112},
+ year = {2006}
+}
+
 @article{MSF2007,
   author = {John W. McDonald and Peter W.F. Smith and Jonathan J. Forster},
   title = {Markov chain {M}onte {C}arlo exact inference for social networks},
@@ -4610,8 +4823,17 @@
 pages="111--134"
 }
 
+ at Manual{nlme,
+    title = {{nlme}: {L}inear and Nonlinear Mixed Effects Models},
+    author = {Jose Pinheiro and Douglas Bates and Saikat DebRoy
+                and Deepayan Sarkar and {R Core Team}},
+    year = {2018},
+    note = {R package version 3.1-137},
+    url = {https://CRAN.R-project.org/package=nlme}
+}
 
 
+
 @PhdThesis{Nordlie58,
   author =       {P.G. Nordlie},
   title =        {A longitudinal study of interpersonal attraction in a natural group setting},
@@ -4755,8 +4977,15 @@
 }
 
 
+ at book{Pajek2018,
+  title={Exploratory social network analysis with Pajek},
+  author={De Nooy, Wouter and Mrvar, Andrej and Batagelj, Vladimir},
+  year={2018},
+  edition={3rd},
+  publisher={Cambridge University Press},
+  location={Cambridge}
+}
 
-
[TRUNCATED]

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


More information about the Rsiena-commits mailing list