[Rsiena-commits] r251 - in pkg: RSiena RSiena/R RSiena/data RSiena/inst/doc RSiena/man RSiena/src RSiena/src/model RSiena/src/model/effects RSiena/src/model/effects/generic RSiena/src/model/tables RSiena/src/model/variables RSiena/src/network RSiena/src/network/iterators RSiena/src/network/layers RSiena/src/utils RSienaTest RSienaTest/R RSienaTest/data RSienaTest/inst/doc RSienaTest/man RSienaTest/src/model/effects RSienaTest/src/model/effects/generic RSienaTest/src/model/tables

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Feb 14 00:03:26 CET 2014


Author: tomsnijders
Date: 2014-02-14 00:03:20 +0100 (Fri, 14 Feb 2014)
New Revision: 251

Added:
   pkg/RSiena/src/model/effects/HomCovariateTransitiveTripletseffect.cpp
   pkg/RSiena/src/model/effects/HomCovariateTransitiveTripletseffect.h
   pkg/RSiena/src/model/effects/generic/HomCovariateMixedTwopathFunction.cpp
   pkg/RSiena/src/model/effects/generic/HomCovariateMixedTwopathFunction.h
   pkg/RSiena/src/model/effects/generic/MixedInStarFunction.cpp
   pkg/RSiena/src/model/effects/generic/MixedInStarFunction.h
   pkg/RSiena/src/model/effects/generic/SumFunction.cpp
   pkg/RSiena/src/model/effects/generic/SumFunction.h
   pkg/RSiena/src/network/INetworkChangeListener.h
   pkg/RSiena/src/network/iterators/
   pkg/RSiena/src/network/iterators/CombinedTieIterator.cpp
   pkg/RSiena/src/network/iterators/CombinedTieIterator.h
   pkg/RSiena/src/network/iterators/ITieIterator.h
   pkg/RSiena/src/network/iterators/IntersectionTieIterator.cpp
   pkg/RSiena/src/network/iterators/IntersectionTieIterator.h
   pkg/RSiena/src/network/iterators/SymDiffTieIterator.cpp
   pkg/RSiena/src/network/iterators/SymDiffTieIterator.h
   pkg/RSiena/src/network/iterators/UnionTieIterator.cpp
   pkg/RSiena/src/network/iterators/UnionTieIterator.h
   pkg/RSiena/src/network/layers/
   pkg/RSiena/src/network/layers/DistanceTwoLayer.cpp
   pkg/RSiena/src/network/layers/DistanceTwoLayer.h
   pkg/RSiena/src/network/layers/NetworkLayer.h
   pkg/RSienaTest/src/model/effects/HomCovariateTransitiveTripletseffect.cpp
   pkg/RSienaTest/src/model/effects/HomCovariateTransitiveTripletseffect.h
   pkg/RSienaTest/src/model/effects/generic/HomCovariateMixedTwopathFunction.cpp
   pkg/RSienaTest/src/model/effects/generic/HomCovariateMixedTwopathFunction.h
   pkg/RSienaTest/src/model/effects/generic/MixedInStarFunction.cpp
   pkg/RSienaTest/src/model/effects/generic/MixedInStarFunction.h
   pkg/RSienaTest/src/model/effects/generic/SumFunction.cpp
   pkg/RSienaTest/src/model/effects/generic/SumFunction.h
Modified:
   pkg/RSiena/DESCRIPTION
   pkg/RSiena/R/effects.r
   pkg/RSiena/R/effectsMethods.r
   pkg/RSiena/R/sienaGOF.r
   pkg/RSiena/R/sienaeffects.r
   pkg/RSiena/R/sienaprint.r
   pkg/RSiena/changeLog
   pkg/RSiena/data/allEffects.csv
   pkg/RSiena/inst/doc/RSiena.bib
   pkg/RSiena/inst/doc/RSiena_Manual.pdf
   pkg/RSiena/inst/doc/RSiena_Manual.tex
   pkg/RSiena/inst/doc/effects.pdf
   pkg/RSiena/man/RSiena-package.Rd
   pkg/RSiena/man/Wald.Rd
   pkg/RSiena/man/getEffects.Rd
   pkg/RSiena/man/includeInteraction.Rd
   pkg/RSiena/man/print.sienaEffects.Rd
   pkg/RSiena/man/setEffect.Rd
   pkg/RSiena/man/siena07.Rd
   pkg/RSiena/man/siena08.Rd
   pkg/RSiena/man/sienaFit.Rd
   pkg/RSiena/man/sienaGOF-auxiliary.Rd
   pkg/RSiena/man/sienaGOF.Rd
   pkg/RSiena/src/model/StatisticCalculator.cpp
   pkg/RSiena/src/model/effects/AllEffects.h
   pkg/RSiena/src/model/effects/EffectFactory.cpp
   pkg/RSiena/src/model/effects/FourCyclesEffect.cpp
   pkg/RSiena/src/model/effects/FourCyclesEffect.h
   pkg/RSiena/src/model/effects/StructuralRateEffect.cpp
   pkg/RSiena/src/model/effects/StructuralRateEffect.h
   pkg/RSiena/src/model/effects/generic/GwespFunction.cpp
   pkg/RSiena/src/model/effects/generic/GwespFunction.h
   pkg/RSiena/src/model/tables/TwoNetworkCache.cpp
   pkg/RSiena/src/model/tables/TwoNetworkCache.h
   pkg/RSiena/src/model/variables/DependentVariable.cpp
   pkg/RSiena/src/model/variables/DependentVariable.h
   pkg/RSiena/src/network/CommonNeighborIterator.cpp
   pkg/RSiena/src/network/CommonNeighborIterator.h
   pkg/RSiena/src/network/IncidentTieIterator.cpp
   pkg/RSiena/src/network/IncidentTieIterator.h
   pkg/RSiena/src/network/Network.cpp
   pkg/RSiena/src/network/Network.h
   pkg/RSiena/src/network/OneModeNetwork.cpp
   pkg/RSiena/src/network/OneModeNetwork.h
   pkg/RSiena/src/siena07internals.cpp
   pkg/RSiena/src/utils/Utils.cpp
   pkg/RSiena/src/utils/Utils.h
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/R/effects.r
   pkg/RSienaTest/R/effectsMethods.r
   pkg/RSienaTest/R/print01Report.r
   pkg/RSienaTest/R/siena07.r
   pkg/RSienaTest/R/siena08.r
   pkg/RSienaTest/R/sienaBayes.r
   pkg/RSienaTest/R/sienaGOF.r
   pkg/RSienaTest/R/sienaeffects.r
   pkg/RSienaTest/R/sienaprint.r
   pkg/RSienaTest/changeLog
   pkg/RSienaTest/data/allEffects.csv
   pkg/RSienaTest/inst/doc/RSiena.bib
   pkg/RSienaTest/inst/doc/RSiena_Manual.pdf
   pkg/RSienaTest/inst/doc/RSiena_Manual.tex
   pkg/RSienaTest/inst/doc/effects.pdf
   pkg/RSienaTest/man/RSiena-package.Rd
   pkg/RSienaTest/man/getEffects.Rd
   pkg/RSienaTest/man/print.sienaEffects.Rd
   pkg/RSienaTest/man/setEffect.Rd
   pkg/RSienaTest/man/siena07.Rd
   pkg/RSienaTest/man/siena08.Rd
   pkg/RSienaTest/man/sienaBayes.Rd
   pkg/RSienaTest/man/sienaFit.Rd
   pkg/RSienaTest/man/sienaGOF-auxiliary.Rd
   pkg/RSienaTest/man/sienaGOF.Rd
   pkg/RSienaTest/src/model/effects/AllEffects.h
   pkg/RSienaTest/src/model/effects/EffectFactory.cpp
   pkg/RSienaTest/src/model/effects/FourCyclesEffect.cpp
   pkg/RSienaTest/src/model/effects/FourCyclesEffect.h
   pkg/RSienaTest/src/model/effects/generic/GwespFunction.cpp
   pkg/RSienaTest/src/model/effects/generic/GwespFunction.h
   pkg/RSienaTest/src/model/tables/TwoNetworkCache.cpp
   pkg/RSienaTest/src/model/tables/TwoNetworkCache.h
Log:
Version 251, extensive updates, see changelog.

Modified: pkg/RSiena/DESCRIPTION
===================================================================
--- pkg/RSiena/DESCRIPTION	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/DESCRIPTION	2014-02-13 23:03:20 UTC (rev 251)
@@ -1,8 +1,8 @@
 Package: RSiena
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.1-250
-Date: 2013-12-04
+Version: 1.1-251
+Date: 2014-02-13
 Author: Ruth Ripley, Krists Boitmanis, Tom A.B. Snijders
 Depends: R (>= 2.15.0)
 Imports: Matrix

Modified: pkg/RSiena/R/effects.r
===================================================================
--- pkg/RSiena/R/effects.r	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/R/effects.r	2014-02-13 23:03:20 UTC (rev 251)
@@ -88,16 +88,6 @@
         tmp
     }
 
-##@addSettingseffects internal getEffects add effects for settings model
-addSettingsEffects <- function(effects)
-{
-depvar <- attr(effects, "depvar")
-	## This processes the settings (constant dyadic covariate) structure.
-	## Only for one-mode network.
-	nbrSettings <- length(attr(depvar,"settings"))
-	## This leads to a warning in R CMD Check.
-	## Not important since this is just a stub, to be developed later.
-}
     ##@networkRateEffects internal getEffects create a set of rate effects
     networkRateEffects <- function(depvar, varname, symmetric, bipartite)
     {
@@ -333,6 +323,11 @@
         rateEffects[1:noPeriods, "initialValue"] <-  starts$startRate
         rateEffects$basicRate[1:observations] <- TRUE
 
+		objEffects[objEffects$shortName == "density" &
+                       objEffects$type == "eval",'randomEffects'] <- TRUE # added dec2013
+		objEffects[objEffects$shortName == "linear" &
+                       objEffects$type == "eval",'randomEffects'] <- TRUE # added dec2013
+
         objEffects$untrimmedValue <- rep(0, nrow(objEffects))
         if (attr(depvar,'symmetric'))
         {

Modified: pkg/RSiena/R/effectsMethods.r
===================================================================
--- pkg/RSiena/R/effectsMethods.r	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/R/effectsMethods.r	2014-02-13 23:03:20 UTC (rev 251)
@@ -11,7 +11,7 @@
 ## ****************************************************************************/
 ##@print.sienaEffects Methods
 print.sienaEffects <- function(x, fileName=NULL, includeOnly=TRUE,
-                               expandDummies=FALSE, ...)
+                               expandDummies=FALSE, includeRandoms = FALSE, ...)
 {
     if (!inherits(x, "sienaEffects"))
         stop("not a legitimate Siena effects object")
@@ -44,6 +44,7 @@
         nDependents <- length(unique(x$name))
         userSpecifieds <- x$shortName[x$include] %in% c("unspInt", "behUnspInt")
         endowments <- !x$type[x$include] %in% c("rate", "eval")
+											# includes creations
         timeDummies <- !x$timeDummy[x$include] == ","
         specs <- x[, c("name", "effectName", "include", "fix", "test",
                        "initialValue", "parm")]
@@ -71,6 +72,10 @@
                 specs <- cbind(specs, effect3=x[x$include, "effect3"])
             }
         }
+		if (includeRandoms)
+		{
+		     specs <- cbind(specs, randomEffects=x[x$include, "randomEffects"])
+   		}
         specs[, "initialValue"] <- format(round(specs$initialValue,digits=5),
                                           width=10)
         if (nrow(specs) > 0)

Modified: pkg/RSiena/R/sienaGOF.r
===================================================================
--- pkg/RSiena/R/sienaGOF.r	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/R/sienaGOF.r	2014-02-13 23:03:20 UTC (rev 251)
@@ -22,6 +22,11 @@
 	require(MASS)
 	## require(Matrix)
 	##	Check input
+	if (sienaFitObject$maxlike)
+	{
+		stop(
+	"sienaGOF can only operate on results from Method of Moments estimation.")
+	}
 	if (! sienaFitObject$returnDeps)
 	{
 		stop("You must instruct siena07 to return the simulated networks")
@@ -219,6 +224,7 @@
 				InvCovSimStats=a,
 				Rank=arank)
 		class(ret) <- "sienaGofTest"
+		attr(ret,"sienaFitName") <- deparse(substitute(sienaFitObject))
 		attr(ret,"auxiliaryStatisticName") <-
 				attr(obsStats,"auxiliaryStatisticName")
 		attr(ret, "key") <- plotKey
@@ -663,14 +669,15 @@
 	trellis.par.set("plot.symbol", plot.symbol)
 
 	panelFunction <- function(..., x=x, y=y, box.ratio){
-		ind.lower = max( round(itns * perc/2), 1)
-		ind.upper = round(itns * (1-perc/2))
-		yperc.lower = sapply(1:ncol(sims), function(i)
+		ind.lower <- max( round(itns * perc/2), 1)
+		ind.upper <- round(itns * (1-perc/2))
+		yperc.lower <- sapply(1:ncol(sims), function(i)
 					sort(sims[,i])[ind.lower]  )
-		yperc.upper = sapply(1:ncol(sims), function(i)
+		yperc.upper <- sapply(1:ncol(sims), function(i)
 					sort(sims[,i])[ind.upper]  )
 		if (violin) {
-			panel.violin(x, y, box.ratio=box.ratio, col = "transparent", ...)
+			panel.violin(x, y, box.ratio=box.ratio, col = "transparent",
+					bw="nrd", ...)
 		}
 		panel.bwplot(x, y, box.ratio=.1, fill = "gray", ...)
 		panel.xyplot(xAxis, yperc.lower, lty=3, col = "gray", lwd=3, type="l",
@@ -799,8 +806,8 @@
 # values in X to structural values in S
 # X must have values 0, 1.
 # NA values in X will be 0 in the result.
-changeToStructural <- function(X, S)
-	{if (any(S >= 10, na.rm=TRUE))
+changeToStructural <- function(X, S) {
+	if (any(S >= 10, na.rm=TRUE))
 		{
 			S[is.na(S)] <- 0
 			S0 <- Matrix(S==10)
@@ -817,8 +824,7 @@
 # for tie variables that have no structural values in SBefore.
 # X must have values 0, 1.
 # NA values in X or SBefore or SAfter will be 0 in the result.
-changeToNewStructural <- function(X, SBefore, SAfter)
-	{
+changeToNewStructural <- function(X, SBefore, SAfter) {
 		SB <- Matrix(SBefore>=10)
 		SA <- Matrix(SAfter>=10)
 		if (any(SA>SB, na.rm=TRUE))
@@ -946,12 +952,10 @@
 	dimsOfDepVar<- attr(obsData[[groupName]]$depvars[[varName]], "netdims")
 	isbipartite <- (attr(obsData[[groupName]]$depvars[[varName]], "type")
 						=="bipartite")
-# sparseData may be dropped - if that's OK
-#	sparseData <- (attr(obsData[[groupName]]$depvars[[varName]], "sparse"))
 	# For bipartite networks in package <network>,
 	# the number of nodes is equal to
 	# the number of actors (rows) plus the number of events (columns)
-	# with all actors preceeding all events.
+	# with all actors preceding all events.
 	# Therefore the bipartiteOffset will come in handy:
 	bipartiteOffset <- ifelse (isbipartite, 1 + dimsOfDepVar[1], 1)
 
@@ -977,10 +981,17 @@
 # the 1 in the 3d column of cbind below is redundant
 # because of the default ignore.eval=TRUE in network.edgelist.
 # But it is good to be explicit.
+	if (sum(matrixNetwork) <= 0) # else network.edgelist() below will not work
+	{
+		returnValue <- emptyNetwork
+	}
+	else
+	{
 		returnValue <- network.edgelist(
 					cbind(sparseMatrixNetwork at i + 1,
 					sparseMatrixNetwork at j + bipartiteOffset, 1),
 					emptyNetwork)
+	}
   returnValue
 }
 

Modified: pkg/RSiena/R/sienaeffects.r
===================================================================
--- pkg/RSiena/R/sienaeffects.r	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/R/sienaeffects.r	2014-02-13 23:03:20 UTC (rev 251)
@@ -218,7 +218,8 @@
 
 ##@setEffect DataCreate
 setEffect <- function(myeff, shortName, parameter=0,
-                      fix=FALSE, test=FALSE, initialValue=0,
+					fix=FALSE, test=FALSE, random=FALSE,
+					initialValue=0,
                       timeDummy=",",
                       include=TRUE, name=myeff$name[1],
                       type="eval", interaction1="", interaction2="",
@@ -236,7 +237,7 @@
     myeff$interaction2 == interaction2 &
     (is.na(myeff$period) | myeff$period == period) &
     myeff$group == group
-	if (shortName == "unspInt")
+	if (shortName %in% c("unspInt", "behUnspInt"))
 	{
 		use <- use & (myeff$include) & (myeff$effect1 == effect1) &
 			(myeff$effect2 == effect2) & (myeff$effect3 == effect3)
@@ -249,7 +250,7 @@
 		cat(paste("interaction2 = <",interaction2,">, ", sep=""))
 		cat(paste("type = <",type,">, ", sep=""))
 		cat(paste("period = <",period,">, ", sep=""))
-		if (shortName == "unspInt")
+		if (shortName %in% c("unspInt", "behUnspInt"))
 		{
 		cat(paste("effects1-2-3 = <",effect1, effect2, effect3,">,", sep=" "))
 		}
@@ -267,10 +268,10 @@
     myeff[use, "test"] <- test
     myeff[use, "initialValue"] <- initialValue
     myeff[use, "timeDummy"] <- timeDummy
+	myeff[use, "randomEffects"] <- random
 #    print.data.frame(myeff[use, c("name", "shortName", "type", "interaction1",
 #                       "interaction2", "include", "parm", "fix", "test",
 #                       "initialValue", "timeDummy", "period", "group")])
-	print.sienaEffects(myeff[use,])
-
+	print.sienaEffects(myeff[use,], includeRandoms = random)
     myeff
 }

Modified: pkg/RSiena/R/sienaprint.r
===================================================================
--- pkg/RSiena/R/sienaprint.r	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/R/sienaprint.r	2014-02-13 23:03:20 UTC (rev 251)
@@ -73,10 +73,13 @@
 		mymat <- matrix("", 7, 2)
 		mymat[1,] <- c("Dependent variable", attr(xj, "name"))
 		mymat[2,] <- c("Type",               attr(xj, "type"))
+		if (attr(xj,"type") == "oneMode")
+		{
 		if (attr(xj,"symmetric"))
 		{
 			mymat[2,2] <- c(mymat[2,2],", symmetric")
 		}
+		}
 		mymat[3,] <- c("Observations",       attr(xj,  "netdims")[3])
 		if (attr(xj, "type") == "bipartite")
 		{
@@ -276,12 +279,12 @@
 	cat('\nEstimated means and standard deviations, standard errors of the mean \n')
 			dmsf <- diag(x$msf)
 			mean.stats <- colMeans(x$sf) + x$targets
-#  cov.dev may be droppec - just for now (07-10-13) I keep it in
+#  cov.dev may be dropped - just for now (07-10-13) I keep it in
 #			cov.dev <- x$msf
 			sem <- sqrt(dmsf/dim(x$sf)[1])
 			if (x$x$dolby)
 			{
-				scores <- apply(x$ssc, c(1,3), sum)  # z$nit by z$pp matrix
+				scores <- apply(x$ssc, c(1,3), sum)  # x$nit by x$pp matrix
 				mean.scores <- colMeans(scores)
 				mean.stats <- mean.stats - (x$regrCoef * mean.scores)
 				sem <- sem*sqrt(1 - (x$regrCor)^2)
@@ -515,10 +518,17 @@
     invisible(x)
 }
 ##@sienaFitThetaTable Miscellaneous
-sienaFitThetaTable <- function(x, tstat=FALSE)
+sienaFitThetaTable <- function(x, fromBayes=FALSE, tstat=FALSE)
 {
-    effects <- x$requestedEffects
+    theEffects <- x$requestedEffects
+    if (fromBayes)
+	{
+		pp <- x$TruNumPars
+	}
+	else
+{
     pp <- x$pp
+	}
     if (x$cconditional)
     {
         nrates <- length(x$rate)
@@ -527,6 +537,7 @@
     {
         nrates <- 0
     }
+	xp <- pp
     pp <- pp + nrates
     ## mydf stores the data before formatting
     mydf <- data.frame(dummy=rep(" ", pp),
@@ -607,7 +618,7 @@
 
     if (nBehavs > 0)
     {
-        behEffects <- effects[effects$netType == 'behavior',]
+        behEffects <- theEffects[theEffects$netType == 'behavior',]
         behNames <- unique(behEffects$name)
     }
     if (nBehavs > 1)
@@ -617,27 +628,27 @@
                                                          behNames)],
                                        '> ', behEffects$effectName,
                                        sep='')
-        effects$effectName[effects$netType=='behavior'] <-
+        theEffects$effectName[theEffects$netType=='behavior'] <-
             behEffects$effectName
     }
-    mydf[nrates + (1:x$pp), 'row'] <-  1:x$pp
-    mydf[nrates + (1:x$pp), 'type' ] <- ifelse(effects$type == "creation",
-                                               "creat", effects$type)
-    mydf[nrates + (1:x$pp), 'text' ] <- effects$effectName
-    mydf[nrates + (1:x$pp), 'value' ] <- theta
+    mydf[nrates + (1:xp), 'row'] <-  1:xp
+    mydf[nrates + (1:xp), 'type' ] <- ifelse(theEffects$type == "creation",
+                                               "creat", theEffects$type)
+    mydf[nrates + (1:xp), 'text' ] <- theEffects$effectName
+    mydf[nrates + (1:xp), 'value' ] <- theta
 	if (exists("ses"))
 	{
-		mydf[nrates + (1:x$pp), 'se' ] <- ses
+		mydf[nrates + (1:xp), 'se' ] <- ses
 	}
     if (!is.null(x$tstat))
     {
         mydf[1:nrates, "tstat"] <- NA
-        mydf[nrates + (1:x$pp), 'tstat' ] <- x$tstat
+        mydf[nrates + (1:xp), 'tstat' ] <- x$tstat
     }
 
     if (nBehavs > 0 && nNetworks > 0)
     {
-        nNetworkEff <- nrow(effects) - nrow(behEffects)
+        nNetworkEff <- nrow(theEffects) - nrow(behEffects)
         addtorow$command[addsub] <-
             'Behavior Dynamics'
         addtorow$pos[[addsub]] <- nrates + 2 + nNetworkEff
@@ -758,19 +769,24 @@
 			x$requestedEffects[x$requestedEffects$groupName==name1,]
 		x$pp <- length(x$theta)
 		x$fixed <- x$fixed[x$effects$groupName==name1]
-		tmp <- sienaFitThetaTable(x)
+		tmp <- sienaFitThetaTable(x, fromBayes=TRUE)
 		mydf <- tmp$mydf
 		mymat <- as.matrix(mydf[,names(mydf)!="tstat"])
+		mynames <- colnames(mymat)
+		mymat <- cbind(mymat, rep.int(NA, dim(mymat)[1]))
+		colnames(mymat) <- c(mynames, 'random')
 		mymat[, 'value'] <- format(round(mydf$value, digits=4))
 		mymat[, 'se'] <- format(round(mydf$se, digits=4))
+		mymat[, 'random'] <-
+				ifelse(x$requestedEffects$randomEffects, "   +   ", "   -   ")
 		mymat[, 'type'] <- format(mymat[, 'type'])
 		mymat[, 'text'] <- format(mymat[, 'text'])
 		mymat[mydf$row < 1, 'row'] <-
 			format(mydf[mydf$row < 1, 'row'])
 		mymat[mydf[,'row'] >= 1, 'row'] <-
 			paste(format(mydf[mydf$row >= 1, 'row']), '.', sep='')
-		mymat <- rbind(c(rep("", 4), "Post.   ", "", "Post.   ", ""),
-					   c(rep("", 4),  "mean    ", "", "s.d.    ", ""),
+		mymat <- rbind(c(rep("", 4), "Post.   ", "", "Post.   ", "", "varying"),
+					   c(rep("", 4),  "mean    ", "", "s.d.    ", "", ""),
 						mymat)
 		mymat <- apply(mymat, 2, format)
 		tmp1 <- apply(mymat, 1, function(x) paste(x, collapse=" "))
@@ -822,17 +838,34 @@
 		else
 		{
 			cat("for global mean parameters\n\n")
-			nmain <- dim(x$ThinPosteriorMu)[1]
+			ntot <- dim(x$ThinPosteriorMu)[1]
 			if (x$frequentist)
 			{
-			first <- nmain - x$lengthPhase3 + 1
+				first <- x$nwarm + x$nmain - x$lengthPhase3 + 1
 			}
 			else
 			{
-			first <- 1
+				first <- x$nwarm + 1
 			}
-			x$theta <- colMeans(x$ThinPosteriorMu[first:nmain,])
-			x$covtheta <- cov(x$ThinPosteriorMu)
+
+			if (ntot < x$nwarm + x$nmain)
+			{
+				cat("This object resulted from an intermediate save, after",
+					ntot, "MCMC runs.\n")
+			}
+			if (ntot > first+2)
+			{
+				cat("Posterior means and standard deviations are averages over",
+					ntot - first + 1, "MCMC runs (counted after thinning).\n\n")
+#				x$theta <- c(colMeans(x$ThinPosteriorMu[first:ntot,]),
+#						colMeans(x$ThinPosteriorEta[first:ntot,, drop=FALSE]))
+#				x$covtheta <- cov(cbind(x$ThinPosteriorMu[first:ntot,],
+#									x$ThinPosteriorEta[first:ntot,]))
+			}
+			else
+			{
+				stop("This object did not come beyond the warming phase.\n")
+			}
 		}
 		tmps <- makeTemp(x)
 		tmp <- tmps[[1]]
@@ -857,16 +890,29 @@
 		if (length(x$f$groupNames) > 1)
 		{
 			cat("\n")
+			if (x$frequentist)
+			{
+				mean.Sigma <- x$Sigma
+				cat("Estimated covariance matrix (varying parameters)\n")
+			}
+			else
+			{
 			mean.Sigma <-
-				apply(x$ThinPosteriorSigma[first:nmain,,], c(2,3), mean)
-			sd.Sigma <- apply(x$ThinPosteriorSigma[first:nmain,,], c(2,3), sd)
-			cat("Posterior mean of global covariance matrix\n")
+					apply(x$ThinPosteriorSigma[first:ntot,,], c(2,3), mean)
+				sd.Sigma <-
+					apply(x$ThinPosteriorSigma[first:ntot,,], c(2,3), sd)
+		cat("Posterior mean of global covariance matrix (varying parameters)\n")
+			}
 			printmat(mean.Sigma)
+			if (!x$frequentist)
+			{
 			cat("\nPosterior standard deviations of ")
 			cat("elements of global covariance matrix\n")
 			printmat(sd.Sigma)
 		}
-		cat("\nTotal of", dim(x$ThinPosteriorMu)[1], "samples.\n\n")
+		}
+#		cat("\nTotal of", ntot-nfirst+1, "samples.\n\n")
+		cat("\n")
 	}
 	invisible(x)
 }
@@ -884,19 +930,23 @@
 ##@print.summary.sienaBayesFit Methods
 print.summary.sienaBayesFit <- function(x, ...)
 {
+# Still to do: quantile(x$ThinPosteriorSigma, probs=c(0.025, 0.5, 0.975))
+# etcetera
 	if (!inherits(x, "summary.sienaBayesFit"))
 	{
         stop("not a legitimate summary of a Siena Bayes model fit")
 	}
-	nmain <- dim(x$ThinPosteriorMu)[1]
+	ntot <- dim(x$ThinPosteriorMu)[1]
+
 	if (x$frequentist)
 	{
 		cat("Frequentist estimation.\n")
-		first <- nmain - x$lengthPhase3 + 1
+		first <- x$nwarm + x$nmain - x$lengthPhase3 + 1
 	}
 	else
 	{
-		first <- 1
+		cat("Bayesian estimation.\n")
+		first <- x$nwarm + 1
 		cat("Prior distribution:\n")
 		cat("\nMu      ")
 		for (i in seq(along=x$priorMu))
@@ -913,11 +963,46 @@
 		{
 			cat("\nKappa  ",sprintf("%8.4f", x$priorKappa),"\n")
 		}
-		cat("\nFor the basic rate parameters, ")
-		cat("the prior is on the square root scale.\n\n")
+#		cat("\nFor the basic rate parameters, ")
+#		cat("the prior is on the square root scale.\n\n")
 	}
+	if (x$incidentalBasicRates)
+	{
+		cat("\nBasic rates parameters are treated as incidental parameters.\n\n")
+	}
+	cat("\nAlgorithm specifications were nwarm =",x$nwarm,", nmain =", x$nmain,
+	    ", nrunMHBatches =", x$nrunMHBatches, ".\n")
+	if (ntot < x$nwarm + x$nmain)
+	{
+		cat("This object resulted from an intermediate save, after",
+			ntot, " MCMC runs.")
+	}
+	if (x$frequentist)
+	{
+		cat("Lengths of phases were:\n")
+		cat("Phase 1:", x$lengthPhase1, ", phase 2:",
+			x$nmain - x$lengthPhase3 - x$lengthPhase1,
+			", phase 3:", x$lengthPhase1, ".\n")
+		cat("Posterior means and standard deviations are")
+		cat(" averages over phase 3.\n\n")
+	}
+	else
+	{
+		cat("Posterior means and standard deviations are averages over")
+		cat(" the last", ntot - first + 1, "runs.\n\n")
+	}
+	if (ntot > first+2)
+	{
+		cat("Proportion of acceptances in MCMC proposals after warming up:\n")
+		cat(sprintf("%4.2f",
+			colMeans(x$ThinBayesAcceptances[first:ntot,])/x$nrunMHBatches),
+			fill=TRUE,"\n")
+		cat("This should ideally be close to 0.25.\n")
+	}
 	print.sienaBayesFit(x)
 
+	if (ntot > first+2)
+	{
 	cat("Posterior means and standard deviations per group\n")
 	for (i in 1:length(x$f$groupNames))
 	{
@@ -925,8 +1010,8 @@
 		# Make temporary changes to make x look like a sienaFit object
 		# so that sienaFitThetaTable can be applied.
 		# This is done in function makeTemp.
-		x$theta <- colMeans(x$ThinParameters[first:nmain,i,])
-		x$covtheta <- cov(x$ThinParameters[first:nmain,i,])
+			x$theta <- colMeans(x$ThinParameters[first:ntot,i,])
+			x$covtheta <- cov(x$ThinParameters[first:ntot,i,])
 		tmps <- makeTemp(x)
 		tmp <- tmps[[1]]
 		tmp1 <- tmps[[2]]
@@ -946,6 +1031,7 @@
 				}
 			}
 			cat(tmp1[i], '\n')
+			}
 		}
 	}
 	invisible(x)

Modified: pkg/RSiena/changeLog
===================================================================
--- pkg/RSiena/changeLog	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/changeLog	2014-02-13 23:03:20 UTC (rev 251)
@@ -1,3 +1,36 @@
+2014-02-13 R-Forge Revision 251
+Changes in RSiena and RSienaTest:
+   * Also cater for behavior user-specified interactions in includeInteraction
+     and setEffect (sienaeffects.r).
+   * New effects: "cl.XWX", "homXTransTrip", "homWXClosure", and "sharedPop".
+   * Effect "cycle4" extended to non-directed one-mode networks
+   * (for directed one-mode networks it is "sharedPop").
+   * Effects "gwesp.." modified; extended to non-directed networks.
+   * Correction: Effect "to" is not a dyadic effect (allEffects.csv)
+   * sienaGOF: added the name of the siena fit object
+     as attribute "sienaFitName" to each of the sienaGofTest objects.
+   * Manual: added paragraph about how to import results from
+     xtable() and siena.table() into MS-Word.
+   * Correction in sparseNetworkExtraction() to avoid errors occurring
+     when the extracted network has no edges (sienaGOF.r).
+   * In the help page for sienaGOF-auxiliary, geodesic distances
+     changed to non-directed; which avoids a further error
+     when the extracted network has no edges.
+   * Correction of an error in print.siena for data sets including
+     other types than "oneMode".
+   * Changed bandwidth selector for violin plots in plot.sienaGOF to "nrd",
+     to avoid long violins in cases where all simulations have the same outcome.
+   * Added parameter "includeRandoms" to print.sienaEffects.
+   * sienaGOF checks that the sienaFitObject object was not made
+     by maximum likelihood estimation.
+Changes in RSiena:
+   * Ported effects outRateLog and outTrunc2 from RSienaTest.
+   * Ported changes (new folders and files) in \src\network\ from RSienaTest.
+Changes in RSienaTest:
+   * Major changes to sienaBayes and print.sienaBayes,
+     to permit estimation of multilevel stochastic actor-oriented model with
+     effects varying between groups for only a subset of the effects.
+
 2013-12-04 R-Forge Revision 250
 Changes in RSiena and RSienaTest:
    * New option "centered" in coCovar and varCovar (sienautils.r,
@@ -3,5 +36,5 @@
      sienaDataCreate.r, print01Report.r, sienaprint.r).
    * setEffect, updateTheta, and prevAns in siena07() now also cater
-     for unspecified interactions (sienaeffects.r, initializeFRAN.r).
+     for user-specified interactions (sienaeffects.r, initializeFRAN.r).
    * Wald.RSiena and Multipar.RSiena added (Sienatest.r).
    * Error occurrence with message about cvalue in EvaluateTestStatistic

Modified: pkg/RSiena/data/allEffects.csv
===================================================================
--- pkg/RSiena/data/allEffects.csv	2013-12-04 16:15:33 UTC (rev 250)
+++ pkg/RSiena/data/allEffects.csv	2014-02-13 23:03:20 UTC (rev 251)
@@ -67,14 +67,17 @@
 nonSymmetricRate,indegree effect on rate xxxxxx,Amount of change x indegrees,inRate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
 nonSymmetricRate,reciprocity effect on rate xxxxxx,Amount of change x reciprocity,recipRate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
 nonSymmetricRate,effect 1/outdegree on rate xxxxxx,Amount of change x (1/outdegrees),outRateInv,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
+nonSymmetricRate,effect ln(outdegree+1) on rate xxxxxx,Amount of change x ln(outdegrees+1),outRateLog,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,rate,NA,structural,0,0,0,0,
 bipartiteRate,basic rate parameter xxxxxx,Amount of network change,Rate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,1,NA,0,0,0,0,
 bipartiteRate,constant xxxxxx rate (period nnnnnn),Amount of network change in period nnnnnn,Rate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,nnnnnn,NA,0,0,0,0,
 bipartiteRate,outdegree effect on rate xxxxxx,Amount of change x outdegrees,outRate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
 bipartiteRate,effect 1/outdegree on rate xxxxxx,Amount of change x (1/outdegrees),outRateInv,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
+bipartiteRate,effect ln(outdegree+1) on rate xxxxxx,Amount of change x ln(outdegrees+1),outRateLog,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,rate,NA,structural,0,0,0,0,
 symmetricRate,basic rate parameter xxxxxx,Amount of network change,Rate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,1,NA,0,0,0,0,
 symmetricRate,constant xxxxxx rate (period nnnnnn),Amount of network change in period nnnnnn,Rate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,nnnnnn,NA,0,0,0,0,
 symmetricRate,degree effect on rate xxxxxx,Amount of change x outdegrees,outRate,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
 symmetricRate,effect 1/degree on rate xxxxxx,Amount of change x (1/outdegrees),outRateInv,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,rate,NA,structural,0,0,0,0,
+symmetricRate,effect ln(degree+1) on rate xxxxxx,Amount of change x ln(outdegrees+1),outRateLog,NA,,,rate,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,rate,NA,structural,0,0,0,0,
 dyadObjective,xxxxxx,Sum of ties x xxxxxx,X,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 dyadObjective,xxxxxx x reciprocity,Sum reciprocated  ties x xxxxxx,XRecip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 dyadObjective,WW=>X closure of xxxxxx,WW=>X closure of xxxxxx,WWX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
@@ -94,6 +97,9 @@
 covarSymmetricObjective,xxxxxx squared,Sum of degrees x squared xxxxxx,altSqX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarSymmetricObjective,xxxxxx similarity,xxxxxx similarity,simX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarSymmetricObjective,same xxxxxx,same xxxxxx,sameX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
+covarSymmetricObjective,transitive triads same xxxxxx,Number of transitive triads same on xxxxxx,sameXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
+covarSymmetricObjective,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,
+covarSymmetricObjective,transitive triads jumping xxxxxx,Number of transitive triads jumping xxxxxx,jumpXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 covarSymmetricObjective,xxxxxx ego x xxxxxx alter,xxxxxx ego x xxxxxx alter,egoXaltX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarSymmetricObjective,xxxxxx of indirect ties,xxxxxx of indirect ties,IndTies,FALSE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarSymmetricObjective,xxxxxx alter at distance 2 (#),xxxxxx alter at distance 2 (#),altDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,dyadic
@@ -112,6 +118,7 @@
 covarNonSymmetricObjective,same xxxxxx,Same values on xxxxxx,sameX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarNonSymmetricObjective,same xxxxxx x reciprocity,Same values x reciprocity on xxxxxx,sameXRecip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 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,
+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,
 covarNonSymmetricObjective,transitive triplets jumping xxxxxx,Number of transitive triplets jumping xxxxxx,jumpXTransTrip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 covarNonSymmetricObjective,xxxxxx ego x xxxxxx alter,Sum xxxxxx ego x xxxxxx alter,egoXaltX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
 covarNonSymmetricObjective,xxxxxx ego x xxxxxx alter x recipr.,Sum xxxxxx ego x xxxxxx rec.alter,egoXaltXRecip,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
@@ -129,7 +136,8 @@
 bipartiteObjective,indegree - popularity (sqrt),Sum of indegrees x sqrt(indegree),inPopSqrt,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 bipartiteObjective,outdegree - activity,Sum of squared outdegrees,outAct,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 bipartiteObjective,outdegree - activity (sqrt),Sum of outdegrees^(1.5),outActSqrt,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
-bipartiteObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
+bipartiteObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
+bipartiteObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc2,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
 bipartiteObjective,1/(outdegree + #),Sum 1/(outdegrees + #),outInv,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 bipartiteObjective,1/(outdegree+#)(outdegree+1+#),Sum 1/(outdegrees + #)(outdegrees + 1 + #),outSqInv,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 bipartiteObjective,anti in-isolates,Number of indegrees at least 1,antiInIso,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego
@@ -154,6 +162,7 @@
 nonSymmetricObjective,GWESP I <- K -> J (#),Number of edgewise shared partners by out two stars (#),gwespFB,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,69,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,GWESP I -> K <- J (#),Number of edgewise shared partners by in two stars (#),gwespBF,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,69,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,GWESP I <> K <> J (#),Number of edgewise shared partners both in AND out two stars (#),gwespRR,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,69,objective,NA,NA,0,0,0,0,
+nonSymmetricObjective,shared popularity,(Number 2-2PU)^1/#),sharedPop,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,indegree - popularity,Sum of squared indegrees,inPop,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,indegree - popularity (sqrt),Sum of indegrees x sqrt(indegree),inPopSqrt,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,outdegree - popularity,Sum of crossproducts indegree x outdegree,outPop,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic
@@ -162,7 +171,8 @@
 nonSymmetricObjective,indegree - activity (sqrt),Sum of outdegrees x sqrt(indegree),inActSqrt,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego
 nonSymmetricObjective,outdegree - activity,Sum of squared outdegrees,outAct,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,outdegree - activity (sqrt),Sum of outdegrees^(1.5),outActSqrt,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
-nonSymmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
+nonSymmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
+nonSymmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc2,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,1/(outdegree + #),Sum 1/(outdegrees + #),outInv,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,1/(outdegree+#)(outdegree+1+#),Sum 1/(outdegrees + #)(outdegrees + 1 + #),outSqInv,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 nonSymmetricObjective,in-isolate Outdegree,Sum outdegrees for in-isolates,inIsDegree,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego
@@ -183,10 +193,13 @@
 symmetricObjective,balance,Amount of balance,balance,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 symmetricObjective,number of actor pairs at distance 2,Number of distances equal to 2,nbrDist2,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 symmetricObjective,number pairs at doubly achieved distance 2,Number of doubly achieved distances 2,nbrDist2twice,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
+symmetricObjective,GWESP (#),Number of edgewise shared partners (#),gwesp,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,69,objective,NA,NA,0,0,0,0,
+symmetricObjective,4-cycles,(Number 4-cycles)^1/#),cycle4ND,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
 symmetricObjective,degree of alter,Sum of squared degrees,inPop,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 symmetricObjective,sqrt degree of alter,Sum of degrees x sqrt(degree),inPopSqrt,TRUE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
 symmetricObjective,degree^(1.5),Sum of degrees^(1.5),outActSqrt,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,
-symmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
+symmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
+symmetricObjective,outdegree-trunc(#),Sum of outdegrees trunc(#),outTrunc2,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,5,objective,NA,NA,0,0,0,0,
 symmetricObjective,1/(degree + #),Sum 1/(degrees + #),outInv,FALSE,,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,
[TRUNCATED]

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


More information about the Rsiena-commits mailing list