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

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Oct 24 14:49:21 CEST 2019


Author: tomsnijders
Date: 2019-10-24 14:49:20 +0200 (Thu, 24 Oct 2019)
New Revision: 342

Added:
   pkg/RSienaTest/src/model/effects/AverageGroupEgoEffect.cpp
   pkg/RSienaTest/src/model/effects/AverageGroupEgoEffect.h
Modified:
   pkg/RSienaTest/ChangeLog
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/R/effects.r
   pkg/RSienaTest/R/sienaBayes.r
   pkg/RSienaTest/R/sienaGOF.r
   pkg/RSienaTest/R/sienaprint.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/setEffect.Rd
   pkg/RSienaTest/man/sienaDependent.Rd
   pkg/RSienaTest/src/model/effects/AllEffects.h
   pkg/RSienaTest/src/model/effects/CovariateDependentNetworkEffect.cpp
   pkg/RSienaTest/src/model/effects/EffectFactory.cpp
   pkg/RSienaTest/src/sources.list
Log:
This R-Forge upload again only RSienaTest.

Modified: pkg/RSienaTest/ChangeLog
===================================================================
--- pkg/RSienaTest/ChangeLog	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/ChangeLog	2019-10-24 12:49:20 UTC (rev 342)
@@ -1,3 +1,13 @@
+2019-10-24 R-Forge Revision 342, package version 1.2-19.
+In this R-forge revision, only RSienaTest is updated.
+Changes in RSiena and RSienaTest:
+   * New effect avGroupEgoX.
+   * CovariateDependentNetworkEffect:  + lSimulatedOffset taken out of
+     definition missings for ChangingCovariate (seems wrong).
+Changes in RSienaTest:
+   * In sienaBayes: more precise check that 
+     prevAns has same specification as effects.
+
 2019-10-16 R-Forge Revision 341, package version 1.2-18.
 In this R-forge revision, only RSienaTest is updated.
 Changes in RSiena and RSienaTest:

Modified: pkg/RSienaTest/DESCRIPTION
===================================================================
--- pkg/RSienaTest/DESCRIPTION	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/DESCRIPTION	2019-10-24 12:49:20 UTC (rev 342)
@@ -2,9 +2,10 @@
 Package: RSienaTest
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.2-18
-Date: 2019-10-16
-Author: Ruth Ripley, Krists Boitmanis, Tom A.B. Snijders, Felix Schoenenberger
+Version: 1.2-19
+Date: 2019-10-24
+Author: Ruth Ripley, Krists Boitmanis, Tom A.B. Snijders, Felix Schoenenberger,
+   Nynke Niezink
 Depends: R (>= 2.15.0)
 Imports: Matrix, tcltk, lattice, parallel, MASS, RUnit, methods
 Suggests: xtable, network, tools, codetools

Modified: pkg/RSienaTest/R/effects.r
===================================================================
--- pkg/RSienaTest/R/effects.r	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/R/effects.r	2019-10-24 12:49:20 UTC (rev 342)
@@ -184,7 +184,7 @@
 				tmp <- covarOneModeEff(names(xx$cCovars)[j],
 					attr(xx$cCovars[[j]], 'poszvar'),
 					attr(xx$cCovars[[j]], 'moreThan2'),
-					symmetric, name=varname)
+					symmetric, constant=TRUE, name=varname)
 				objEffects <-  rbind(objEffects, tmp$objEff)
 				rateEffects <- rbind(rateEffects, tmp$rateEff)
 			}
@@ -197,7 +197,7 @@
 				tmp <- covarOneModeEff(names(xx$depvars)[j],
 					poszvar=TRUE,
 					attr(xx$depvars[[j]], 'moreThan2'),
-					symmetric, name=varname)
+					symmetric, constant=FALSE, name=varname)
 				objEffects <- rbind(objEffects, tmp$objEff)
 				rateEffects <- rbind(rateEffects, tmp$rateEff)
 			}
@@ -209,7 +209,7 @@
 				tmp <- covarOneModeEff(names(xx$vCovars)[j],
 					attr(xx$vCovars[[j]], 'poszvar'),
 					attr(xx$vCovars[[j]], 'moreThan2'),
-					symmetric, name=varname)
+					symmetric, constant=FALSE, name=varname)
 				objEffects <- rbind(objEffects,tmp$objEff)
 				rateEffects<- rbind(rateEffects,tmp$rateEff)
 			}
@@ -767,7 +767,7 @@
 	##@continuousNet internal getEffects
     continuousNet <- function(depvars, varnames)
     {
-        nodeSet <- attr(depvars[[1]],'nodeSet')	## NN: nodeset should be the same for 
+        nodeSet <- attr(depvars[[1]],'nodeSet')	## NN: nodeset should be the same for
 						##     all continuous depvars
 
         rateEffects <- createEffects("continuousRate", name="sde",
@@ -785,26 +785,26 @@
                                  rateEffects[-c(1, 2), ])
         }
 
-        objEffects <- fbicEffects <- wEffects <- NULL # general effects, feedback 
+        objEffects <- fbicEffects <- wEffects <- NULL # general effects, feedback
                                                       # and intercept, wiener
         for (j in seq(along=varnames)) # for all continuous variables
         {
 			for (k in seq(along=varnames))
             {
-				fbicEffects <- rbind(fbicEffects, createEffects("continuousFeedback", 
+				fbicEffects <- rbind(fbicEffects, createEffects("continuousFeedback",
                                 xName = varnames[j], yName = varnames[k],
 							    name=varnames[j], groupName=groupName, group=group,
                                 netType=netType))
-				if (j <= k) 
-				    wEffects <- rbind(wEffects, createEffects("continuousWiener", 
+				if (j <= k)
+				    wEffects <- rbind(wEffects, createEffects("continuousWiener",
                                 xName = varnames[k], yName = varnames[j],
 							    name=varnames[k], groupName=groupName, group=group,
                                 netType=netType))
 			}
-            fbicEffects <- rbind(fbicEffects, createEffects("continuousIntercept", 
-							xName = varnames[j], name = varnames[j], 
+            fbicEffects <- rbind(fbicEffects, createEffects("continuousIntercept",
+							xName = varnames[j], name = varnames[j],
 							groupName=groupName, group=group, netType=netType))
-            
+
             for (k in seq(along=depvars))
             {
                 if (types[k] == "oneMode" &&
@@ -811,7 +811,7 @@
                     attr(xx$depvars[[k]], "nodeSet") == nodeSet)
                 {
                     depvarname <- names(xx$depvars)[k]
-                    
+
                     tmpObjEffects <-
                             createEffects("continuousOneModeObjective",
                                           varnames[j], depvarname, name=varnames[j],
@@ -860,15 +860,15 @@
                 }
             }
 			interaction <- createEffects("unspecifiedContinuousInteraction",
-                                     varnames[j], name=varnames[j], 
-									 groupName=groupName, group=group, 
+                                     varnames[j], name=varnames[j],
+									 groupName=groupName, group=group,
 									 netType=netType)
 
-			objEffects <- rbind(objEffects, interaction[rep(1, behNintn),])			
+			objEffects <- rbind(objEffects, interaction[rep(1, behNintn),])
 		}
-        
+
 		fbicEffects$include <- TRUE
-        
+
         if (onePeriodSde)
         {
             wEffects$include <- TRUE
@@ -879,21 +879,21 @@
         {
             wEffects$fix[1] <- TRUE
             rateEffects$include[1:observations] <- TRUE
-            rateEffects$basicRate[1:observations] <- TRUE        
+            rateEffects$basicRate[1:observations] <- TRUE
         }
-        
+
 		if (nContinuous > 1)
 			wEffects$include <- TRUE
-	 
-        starts <- getContinuousStartingVals(depvars, onePeriodSde)	
+
+        starts <- getContinuousStartingVals(depvars, onePeriodSde)
         wEffects$initialValue <- starts$startWiener
 		rateEffects$initialValue[1:noPeriods] <- starts$startScale
 		fbicEffects$initialValue <- starts$startFbic
-                   
-        list(effects = rbind(rateEffects, wEffects, fbicEffects, objEffects), 
+
+        list(effects = rbind(rateEffects, wEffects, fbicEffects, objEffects),
              starts = starts)
     }
-	
+
 	##@bipartiteNet internal getEffects
 	bipartiteNet <- function(depvar, varname)
 	{
@@ -1138,7 +1138,7 @@
 	}
 
 	##@covarOneModeEff internal getEffects
-	covarOneModeEff<- function(covarname, poszvar, moreThan2, symmetric,
+	covarOneModeEff<- function(covarname, poszvar, moreThan2, symmetric, constant,
 		name)
 	{
 		if (symmetric)
@@ -1164,6 +1164,12 @@
 				netType=netType)
 		}
 
+		if (constant)
+		{
+			covObjEffects <-
+				covObjEffects[!(covObjEffects$shortName %in% c("avGroupEgoX")),]
+		}
+
 # these lines tentatively dropped version 1.2-5
 #		if (!tr & (!poszvar))  # not (positive variance of z, or any z missing)
 #		{
@@ -1208,7 +1214,7 @@
 					"degAbsDiffX", "degPosDiffX", "degNegDiffX",
 					"altInDist2", "totInDist2",
 					"simEgoInDist2", "sameXInPop", "diffXInPop",
-					"sameXCycle4", "inPopX", "inActX"), ]
+					"sameXCycle4", "inPopX", "inActX", "avGroupEgoX"), ]
 			covRateEffects <- createEffects("covarBipartiteRate", covarname,
 				name=varname,
 				groupName=groupName, group=group,
@@ -1385,7 +1391,7 @@
 		}
 		objEffects
 	}
-	
+
 	##@covContEff internal getEffects
 	covContEff <- function(varname, covarname, nodeSet, same=FALSE,
                          ## same indicates that varname and covarname are
@@ -1403,7 +1409,7 @@
 		}
 		list(objEff=covObjEffects)
 	}
-	
+
 	###################################
 	## start of function getEffects
 	##################################
@@ -1453,12 +1459,12 @@
 	effects <- vector('list',n+1) 			# n+1 th place for all sde parameters
 	#nodeSetNames <- sapply(xx$nodeSets, function(x)attr(x, 'nodeSetName'))
 	names(effects) <- names(xx$depvars) 	# n+1 th place has no name
-	
+
 	if (onePeriodSde && xx$observations > 2)
-		stop('onePeriodSde only possible in case of 2 observations')	
+		stop('onePeriodSde only possible in case of 2 observations')
 
 	if (onePeriodSde && groupx)
-		stop('onePeriodSde not possible in combination with multi-group')	
+		stop('onePeriodSde not possible in combination with multi-group')
 
 	for (i in 1:(n-nContinuous))
 	{
@@ -1518,12 +1524,12 @@
         	group <- 1
 	        noPeriods <- xx$observations - 1
 		netType <- "continuous"
-		contIndices <- (n-nContinuous+1):n ## indicates continuous depvars 
+		contIndices <- (n-nContinuous+1):n ## indicates continuous depvars
 		varnames <- names(xx$depvars)[contIndices]
-        	depvars <- xx$depvars[contIndices] 
+        	depvars <- xx$depvars[contIndices]
 		tmp <- continuousNet(depvars,varnames)
 		effects[[n+1]] <- tmp$effects
-		attr(effects[[n+1]], 'starts') <- tmp$starts 
+		attr(effects[[n+1]], 'starts') <- tmp$starts
 		for (i in contIndices)
 		{
 			# all the continuous variable specific effects are currently
@@ -1713,7 +1719,7 @@
 				depvars <- xx$depvars[contIndices]
 				starts <- getContinuousStartingVals(depvars, onePeriodSde = FALSE)
 				## At this point, onePeriodSde is always FALSE, as the combination
-				## of multi-group and onePeriodSde = TRUE is not feasible 
+				## of multi-group and onePeriodSde = TRUE is not feasible
 				for (i in 1:nContinuous) ## check whether all continous vars match
 				{
 					eff <- match(varnames[i], names(effects))
@@ -1731,7 +1737,7 @@
 												  groupNames[group], group,
 												  1:noPeriods)
 			}
-			
+
 			period <-  period + xx$observations ##periods used so far
 		}
 	}
@@ -1830,26 +1836,26 @@
 	nActors <- nrow(depvar)           # no. of actors
 	nPeriods <- ncol(depvar) - 1	  # no. of periods
 	nCont <- length(depvars)          # no. of continuous variables
-    
+
 	if(nCont > 1)
 		stop("getContinuousStartingVals not defined for more than one continuous variable")
 
 	# determine SDE parameters by regressing each observation on the
 	# preceding observation, using the Bergstrom formula
-	# note: wiener process parameter G is set to 1 for identifiability 
-	LL <- function(theta) 
+	# note: wiener process parameter G is set to 1 for identifiability
+	LL <- function(theta)
 	{
 		a <- theta[1]
 		b0 <- theta[2]
 		tau <- theta[3:(2+nPeriods)]
 		minlogliks <- rep(0, nPeriods)
-        
+
 		for(i in 1:nPeriods)
 		{	# actors present at time i and i+1
 			act <- which(!is.na(depvar[,i] + depvar[,i+1]))
-			R <- depvar[act,i+1] - exp(a * tau[i]) * depvar[act,i] - 
+			R <- depvar[act,i+1] - exp(a * tau[i]) * depvar[act,i] -
 				(exp(a*tau[i]) - 1) * b0 / a
-			R <- suppressWarnings(dnorm(R, 0, sqrt((exp(2 * a * tau[i]) - 1) / (2*a)), 
+			R <- suppressWarnings(dnorm(R, 0, sqrt((exp(2 * a * tau[i]) - 1) / (2*a)),
 				log = TRUE))
 			minlogliks[i] <- -sum(R)
 		}
@@ -1863,13 +1869,13 @@
 		g <- theta[3]
 		# actors present at time 1 and 2
 		act <- which(!is.na(depvar[,1] + depvar[,2]))
-		R <- depvar[act,2] - exp(a) * depvar[act,1] - 
+		R <- depvar[act,2] - exp(a) * depvar[act,1] -
 			(exp(a) - 1) * b0 / a
-		R <- suppressWarnings(dnorm(R, 0, sqrt((exp(2 * a) - 1) * g^2 / (2*a)), 
+		R <- suppressWarnings(dnorm(R, 0, sqrt((exp(2 * a) - 1) * g^2 / (2*a)),
 			log = TRUE))
 		-sum(R)
 	}
-    
+
 	if (onePeriodSde)
 		fit <- optim(theta <- c(-0.5, 3, 1), LLonePeriodSde, hessian = TRUE)
 	else
@@ -1885,10 +1891,10 @@
 	cat("SDE par stand errors:", sqrt(diag(solve(fit$hessian))), '\n')
 
 	if (onePeriodSde) # return: tau, g, a, b0
-		list(startScale = 1, startWiener = fit$par[3], startFbic = fit$par[1:2]) 
+		list(startScale = 1, startWiener = fit$par[3], startFbic = fit$par[1:2])
 	else
-		list(startScale = fit$par[3:(2+nPeriods)], startWiener = 1, 
-			 startFbic = fit$par[1:2]) 
+		list(startScale = fit$par[3:(2+nPeriods)], startWiener = 1,
+			 startFbic = fit$par[1:2])
 }
 ##@getNetworkStartingVals DataCreate
 getNetworkStartingVals <- function(depvar)

Modified: pkg/RSienaTest/R/sienaBayes.r
===================================================================
--- pkg/RSienaTest/R/sienaBayes.r	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/R/sienaBayes.r	2019-10-24 12:49:20 UTC (rev 342)
@@ -1664,12 +1664,35 @@
 				(dim(prevAns$requestedEffects)[1] == sum(effects$include)) &
 				!prevAns$x$cconditional)
 			{
-				nsub <- 0
-				if (prevAns$n3 >= 500)
+				e1 <- prevAns$requestedEffects[prevAns$requestedEffects$include,]
+				e2 <- effects[effects$include,]
+				if (all(e1$name == e2$name) & all(e1$shortName == e2$shortName) &
+					all(e1$type == e2$type) & all(e1$effect1 == e2$effect1) &
+					all(e1$effect2 == e2$effect2) &
+					all(e1$effect3 == e2$effect3) &
+					all(e1$interaction1 == e2$interaction1) &
+					all(e1$interaction2 == e2$interaction2) &
+					all(e1$parm == e2$parm))
 				{
-					startupSkip <- TRUE
+					nsub <- 0
+					if (prevAns$n3 >= 500)
+					{
+						startupSkip <- TRUE
+					}
+					else
+					{
+						message('prevAns is given with low value of n3.\n')
+					}
 				}
+				else
+				{
+					message('prevAns does not have same specification.\n')
+				}
 			}
+			else
+			{
+				message('prevAns does not have same number of effects.\n')
+			}
 		}
 		startupModel <- sienaAlgorithmCreate(n3=500, nsub=nsub, cond=FALSE,
 						firstg=initgainGlobal, lessMem=TRUE,

Modified: pkg/RSienaTest/R/sienaGOF.r
===================================================================
--- pkg/RSienaTest/R/sienaGOF.r	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/R/sienaGOF.r	2019-10-24 12:49:20 UTC (rev 342)
@@ -235,7 +235,6 @@
 		attr(ret, "key") <- plotKey
 		ret
 	}
-
 	res <- lapply(1:length(simStats),
 					function (i) {
 				 applyTest(obsStats[[i]], simStats[[i]]) })

Modified: pkg/RSienaTest/R/sienaprint.r
===================================================================
--- pkg/RSienaTest/R/sienaprint.r	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/R/sienaprint.r	2019-10-24 12:49:20 UTC (rev 342)
@@ -397,12 +397,11 @@
 					rep('\n',x$qq), sep='')
 			}
 			cat(as.matrix(mymess1),'\n', sep='')
-			cat("\nSimulated statistics are in ...$sf")
-#						paste(objectName,'$sf',sep=""))
+			cat("\nSimulated statistics are in ", objectName,'$sf',sep="")
 			if (x$returnDeps)
 			{
-				cat("\nand simulated dependent variables in ...$sims.\n")
-#					paste(objectName,'$sims',sep=""), ".\n")
+				cat("\nand simulated dependent variables in ",
+								objectName,'$sims.\n',sep="")
 			}
 			else
 			{

Modified: pkg/RSienaTest/data/allEffects.csv
===================================================================
--- pkg/RSienaTest/data/allEffects.csv	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/data/allEffects.csv	2019-10-24 12:49:20 UTC (rev 342)
@@ -228,6 +228,7 @@
 covarSymmetricObjective,xxxxxx in-alter dist 2,xxxxxx in-alter dist 2,altInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarSymmetricObjective,xxxxxx tot in-alter dist 2,xxxxxx tot in-alter dist 2,totInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarSymmetricObjective,xxxxxx ego-in-alter dist 2 similarity,xxxxxx ego-in-alter dist 2 similarity,simEgoInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,dyadic,FALSE
+covarSymmetricObjective,xxxxxx group-av. ego,Sum of degr. x aver. xxxxxx,avGroupEgoX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego,FALSE
 covarBipartiteObjective,xxxxxx alter,Sum of indegrees x xxxxxx,altX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarBipartiteObjective,xxxxxx alter,Sum of indegrees x xxxxxx,altX,TRUE,xxxxxx,,gmm,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,gmm,NA,NA,0,0,0,0,dyadic,FALSE
 covarBipartiteObjective,xxxxxx squared alter,Sum of indegrees x squared xxxxxx,altSqX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
@@ -252,6 +253,7 @@
 covarBipartiteObjective,4-cycles (#) same xxxxxx,sum 4-cycles^1/# same xxxxxx,sameXCycle4,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,,FALSE
 covarBipartiteObjective,outd. act. to hom. xxxxxx,sum sqr. outd. to hom. values on xxxxxx,homXOutAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
 covarBipartiteObjective,outd. act. weight alt. xxxxxx,sum sqr. outd. weight alt. xxxxxx,altXOutAct,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
+covarBipartiteObjective,xxxxxx group-av. ego,Sum of outdegr. x aver. xxxxxx,avGroupEgoX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego,FALSE
 covarNonSymmetricObjective,xxxxxx alter,Sum indegrees x xxxxxx,altX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarNonSymmetricObjective,xxxxxx simmelian alter,Sum simm. indegrees x xxxxxx,simmelianAltX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarNonSymmetricObjective,xxxxxx alter,Sum indegrees x xxxxxx,altX,TRUE,xxxxxx,,gmm,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,gmm,NA,NA,0,0,0,0,dyadic,FALSE
@@ -311,6 +313,7 @@
 covarNonSymmetricObjective,xxxxxx in-alter dist 2,xxxxxx in-alter dist 2,altInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarNonSymmetricObjective,xxxxxx tot in-alter dist 2,xxxxxx tot in-alter dist 2,totInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,dyadic,FALSE
 covarNonSymmetricObjective,xxxxxx ego-in-alter dist 2 similarity,xxxxxx ego-in-alter dist 2 similarity,simEgoInDist2,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,1,objective,NA,NA,0,0,0,0,dyadic,FALSE
+covarNonSymmetricObjective,xxxxxx group-av. ego,Sum of outdegr. x aver. xxxxxx,avGroupEgoX,TRUE,xxxxxx,,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,ego,FALSE
 covarBehaviorNetObjective,xxxxxx: av. sim. (zzzzzz) x ego's yyyyyy,xxxxxx av. sim. (zzzzzz) x ego's yyyyyy,avSimEgoX,TRUE,yyyyyy,zzzzzz,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
 covarBehaviorNetObjective,xxxxxx: tot. sim. (zzzzzz) x ego's yyyyyy,xxxxxx tot. sim. (zzzzzz) x ego's yyyyyy,totSimEgoX,TRUE,yyyyyy,zzzzzz,eval,FALSE,FALSE,FALSE,FALSE,FALSE,",",0,0,objective,NA,NA,0,0,0,0,,FALSE
 covarBehaviorNetObjective,xxxxxx: av. alters (zzzzzz) x ego's yyyyyy,xxxxxx av. alters (zzzzzz) x ego's yyyyyy,avAltEgoX,TRUE,yyyyyy,zzzzzz,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	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/doc/RSiena.bib	2019-10-24 12:49:20 UTC (rev 342)
@@ -977,7 +977,7 @@
 }
 
 @article{CH56,
-author ={Cartwright, D., and F. Harary},
+author ={Dorwin Cartwright and Frank Harary},
 year = 1956,
 title = {Structural Balance: A Generalization of Heider’s Theory},
 journal = {Psychological Review},
@@ -1341,6 +1341,8 @@
     title={Transitivity correlation: {A} descriptive measure of network transitivity},
     journal={Network Science},
     author={Dekker, David and Krackhardt, David and Snijders, Tom A. B.},
+    volume = 7,
+    pages = {353--375},
     year={2019}
 }
 
@@ -1416,6 +1418,16 @@
    Pages = {331--357},
    Year = {1994} }
 
+ at article{DonnatHolmes2018,
+    author = "Donnat, Claire and Holmes, Susan",
+    journal = "The Annals of Applied Statistics",
+    issue = "2",
+    pages = "971--1012",
+    title = "Tracking network dynamics: {A} survey using graph distances",
+    volume = "12",
+    year = "2018"
+}
+
 @article{Doreian1980,
   title={Linear models with spatially distributed data: {S}patial disturbances or spatial effects?},
   author={Doreian, Patrick},
@@ -2627,8 +2639,9 @@
 
 @book{HBPM2012,
    Author = {Marina Hennig and Ulrik Brandes and J\"{u}rgen Pfeffer and Ines Mergel},
-   title = {Studying Social Networks: A Guide to Empirical Research},
+   title = {Studying Social Networks: {A} Guide to Empirical Research},
    Publisher = {Campus-Verlag},
+   address = {Frankfurt/New York},
    Year = "2012"
    }
 
@@ -4284,6 +4297,17 @@
 }
 
 
+
+ at article{LospinosoSnijders2019,
+    AUTHOR = {Joshua A. Lospinoso and {Tom A. B.} Snijders},
+    title   = "Goodness of fit for Stochastic Actor-Oriented Models",
+    publisher = "Presentation at the XXXI Sunbelt Social Networks conference,
+       February 8-13, St. Pete's Beach, Florida",
+    journal = {Methodological Innovations},
+    year    = "2019",
+    pages = {in press}
+}
+
 @article{LottLott1965,
    year={1965},
    journal={Psychological Bulletin },

Modified: pkg/RSienaTest/doc/RSiena_Manual.pdf
===================================================================
(Binary files differ)

Modified: pkg/RSienaTest/doc/RSiena_Manual.tex
===================================================================
--- pkg/RSienaTest/doc/RSiena_Manual.tex	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/doc/RSiena_Manual.tex	2019-10-24 12:49:20 UTC (rev 342)
@@ -186,7 +186,7 @@
 by Mark Huisman, Michael Schweinberger, and Christian Steglich.
 
 This manual is frequently updated, mostly only in a minor way.
-This version was renewed for \RS version 1.2-17.
+This version was renewed for \RS version 1.2-18.
 \end{abstract}
 
 
@@ -350,7 +350,8 @@
 standard errors of the Method of Moments estimators.
 For assessing and
 correcting time heterogeneity, and goodness of fit assement and associated model
-selection considerations, refer to \citet*{Lospinoso2011} and \citet{Lospinoso2012}.
+selection considerations, refer to \citet*{Lospinoso2011} and
+\citet{LospinosoSnijders2019}.
 A basic reference for the Bayesian estimation is \citet{KoskinenSnijders07}
 and for the maximum likelihood estimation \citet*{SnijdersEA10a}.
 For Generalized Method of Moments estimators,
@@ -894,7 +895,7 @@
             \end{itemize}
 
             Installation from a downloaded file can be done as follows, assuming
-            the root name of the file is \texttt{RSienaTest\_1.2-17}, and filling in the correct path name.
+            the root name of the file is \texttt{RSienaTest\_1.2-18}, and filling in the correct path name.
             It will be convenient to first navigate to the directory
             containing the \RS binary or source file so that this is the current directory.
             Then the pathname consists only of the filename.
@@ -901,17 +902,17 @@
             \begin{itemize}
             \item In \R from binary:\\
             for Windows:\\
-             \texttt{install.packages("pathname to RSienaTest\_1.2-17.zip", repos = NULL, type="binary")}\\
+             \texttt{install.packages("pathname to RSienaTest\_1.2-18.zip", repos = NULL, type="binary")}\\
             for Mac:\\
-             \texttt{install.packages("pathname to RSienaTest\_1.2-17.tgz", repos = NULL, type="binary")}
+             \texttt{install.packages("pathname to RSienaTest\_1.2-18.tgz", repos = NULL, type="binary")}
              \item In \R from source:\\
-            \texttt{install.packages("RSienaTest\_1.2-17.tar.gz", repos = NULL, type="source")}
+            \texttt{install.packages("RSienaTest\_1.2-18.tar.gz", repos = NULL, type="source")}
             \item In \text{command.com} or in batch mode (Windows) from binary:\\
-            \texttt{R CMD INSTALL RSienaTest\_1.2-17.zip}
+            \texttt{R CMD INSTALL RSienaTest\_1.2-18.zip}
             \item In the terminal (Mac) from binary:\\
-            \texttt{R CMD INSTALL RSienaTest\_1.2-17.tgz}
+            \texttt{R CMD INSTALL RSienaTest\_1.2-18.tgz}
             \item In \text{command.com} or in batch mode (Windows) or in the terminal (Mac) from source:\\
-            \texttt{R CMD INSTALL RSienaTest\_1.2-17.tar.gz}
+            \texttt{R CMD INSTALL RSienaTest\_1.2-18.tar.gz}
             \item In drop-down menu in \Rn:\\
             for Windows:  go to Packages  $\rightarrow$ Install package(s) from local zip file\\
             for Mac:  go to Packages \& Data $\rightarrow$ Package Installer
@@ -1111,7 +1112,7 @@
   of \rs. Details of the latest version available can
   be found at \small{\url{http://r-forge.r-project.org/R/?group_id=461}}.
   The version is
-  identified by a version number (e.g.\ 1.2-17) and an R-Forge revision
+  identified by a version number (e.g.\ 1.2-18) and an R-Forge revision
   number. You can find both numbers of your current installed version by
   opening \R, and typing \\
   \verb|packageDescription("RSiena")|. The version is
@@ -3840,7 +3841,8 @@
 also of these other statistics.
 
 The \sfn{sienaGOF} function, proposed and elaborated by
-\citet{Lospinoso2012}, operates basically by comparing
+\citet{Lospinoso2012} and presented further
+in \citet{LospinosoSnijders2019}, operates basically by comparing
 the observed values, at the ends of the periods, with the
 simulated values for the ends of the periods.
 The differences are assessed by combining the auxiliary statistics
@@ -8405,7 +8407,10 @@
  the number of actors to whom $i$
  is not directly tied, and tied through twopaths via at least two intermediaries,\\
  $s^{\rm net}_{i\vit}(x) =  \#\{j \mid x_{ij} = 0,\, \sum_h (x_{ih}\, x_{hj}) \geq 2 \}$;\\
- endowment effect only likelihood-based;
+ evidently, this is even more difficult to interpret than \texttt{(nbrDist2)};
+ both effects should be used if there are very specific
+ and convincing reasons to include them in the model;\\
+ endowment effect only likelihood-based;\\
 
 
  \item {\em number of dense triads} \texttt{(denseTriads)},
@@ -9650,6 +9655,18 @@
 \end{minipage}
 
 \setcounter{savenumi}{\value{enumi}}
+
+ \item {\em group average} \texttt{(avGroupEgoX)}, defined by ego's value multiplied by the
+ average of the covariate for this period,  \\
+ $s^{\rm beh}_{i\vit}(x, z) =  \sum_j x_{ij} \, \overline {v}  $;\\
+ here $\overline {v}$ is the mean of the values $v_{ih}$ for all actors $h$
+ in the actor set: for changing covariate, the mean of the wave at the
+ start of the period; for behavioral dependent variables,
+ the current mean.
+ This effect is not meaningful for constant covariates.
+ It is useful especially for multigroup data sets, where the average value
+ varies between groups. 
+ Note that always, the average $\overline {v} $ is centered by the global mean.
 \end{enumerate}
 
 \noindent
@@ -12089,10 +12106,11 @@
  in the group, and $c_p$ is a centering constant depending on the internal effect parameter $p$.
  Denote the overall mean used for centering the observed $Z$ values by
  $m_Z$ (see the footnote on p.~\pageref{meandef}).
- If $p \leq 0$, centering is no different than for the $z_i$ values generally,
- so $c_p = 0$; if $p \geq 1$, centering is by $c_p = p - m_Z$.
+ If $p \leq 0.5$, centering is no different than for the $z_i$ values generally,
+ so $c_p = 0$; if $p > 0.5$, centering is by $c_p = p - m_Z$.
  For the original non-centered values of $Z$, this means that the mean
- is centered around the value $p$.\\
+ is centered around the value $p$, the effect parameter itself.
+ Note that this can be any real value, not necessarily integer.\\
  This effect is useful especially for multigroup data sets, where the average value
  varies between groups. For multigroup data sets, centering by the groupwise
  mean may be less desirable, and it will be better to center by a value $p$
@@ -15182,6 +15200,37 @@
 \begin{small}
 \begin{itemize} % Also update version number in abstract
 
+
+\item 2019-10-17 R-Forge Revision 341, RSienaTest version 1.2-18.
+
+Changes in RSienaTest:
+\begin{itemize}
+   \item Continuous dependent behavior variables implemented (Nynke Niezink).
+     This implies new effect types \texttt{continuousFeedback},
+     \texttt{ continuousIntercept}, \\
+     \texttt{continuousOneModeObjective},
+     \texttt{ continuousRate}, \texttt{ continuousWiener}, \\
+     \texttt{ unspecifiedContinuousInteraction}.
+   \item \texttt{imputationValues} allowed in \sfn{sienaDependent} (Nynke Niezink).
+   \item New effect \texttt{outMore}.
+   \item component \texttt{startingDate} added to \sfn{sienaFit} object;
+   this date is reported in  \sfn{siena.table(..., type='tex', ...)}.
+   \item Object names are given in \sfn{sienaFit.print} if \texttt{simOnly}.
+   \item Speeded up calculation of \sfn{IndegreeDistribution} and \sfn{OutdegreeDistribution}
+     for \sfn{sienaGOF} if there are no missings or structurals.
+   \item \texttt{regrCoef} and \texttt{regrCor} added to the \sfn{sienaFit} object
+   also when not \texttt{dolby}.
+   \item Immediate stop if \texttt{useCluster} and \texttt{returnChains}
+     both are used (in this case, no chains would be returned anyway).
+   \item \sfn{sienaDataCreate}: more informative message in case of constraints.
+   \item Small improvements in many help pages.
+   \item Corrected error in names of array returned by \sfn{extract.posteriorMeans}.
+   \item New parameter \texttt{excludeRates} in \sfn{extract.posteriorMeans},
+       \sfn{plotPostMeansMDS}.
+   \item Use parameter \texttt{pmonly} also in \sfn{plotPostMeansMDS}.
+\end{itemize}
+
+
 \item 2019-05-20 R-Forge Revision 340, package version 1.2-17.
 
 Changes in RSiena and RSienaTest:
@@ -15433,7 +15482,7 @@
 Changes in RSienaTest:
 \begin{itemize}
    \item new function \sfn{extract.posteriorMeans} for \sfn{sienaBayes} results.
-   \item Restrict check of maximum
+   \item Restrict check in \sfn{sienaBayes} of maximum
      estimated parameter value after initialization to non-fixed effects.
    \item Correct construction of groupwise effects object in \sfn{sienaBayes}
     so that this
@@ -15444,7 +15493,8 @@
      In \sfn{print.sienaBayesFit}, include fixed parameters and
      give credibility intervals for rate parameters; include variance parameters;
      allow shorter \texttt{ThinParameters};
-     print objects returned through \texttt{partialBayesResult.RData}
+     print objects returned through \\
+     \texttt{partialBayesResult.RData}
      (by adding \texttt{na.rm=TRUE} to quantile).
    \item \sfn{multipleBayesTest} corrected (there was an error for testing
       2 or more linear combinations simultaneously)

Modified: pkg/RSienaTest/man/RSiena-package.Rd
===================================================================
--- pkg/RSienaTest/man/RSiena-package.Rd	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/man/RSiena-package.Rd	2019-10-24 12:49:20 UTC (rev 342)
@@ -49,8 +49,8 @@
   \tabular{ll}{
     Package: \tab RSienaTest\cr
     Type: \tab Package\cr
-    Version: \tab 1.2-18\cr
-    Date: \tab 2019-10-16\cr
+    Version: \tab 1.2-19\cr
+    Date: \tab 2019-10-24\cr
     Depends: \tab R (>= 3.0.0)\cr
     Imports: \tab Matrix\cr
     Suggests: \tab tcltk, network, codetools, lattice, MASS, parallel,
@@ -63,9 +63,10 @@
   }
 }
 \author{
-  Ruth Ripley, Krists Boitmanis, Tom Snijders, Felix Schoenenberger.
+  Ruth Ripley, Krists Boitmanis, Tom Snijders, Felix Schoenenberger,
+  Nynke Niezink.
   Contributions by Josh Lospinoso, Charlotte Greenan, Christian Steglich,
-  Johan Koskinen, Mark Ortmann, Nynke Niezink, Natalie Indlekofer,
+  Johan Koskinen, Mark Ortmann, Natalie Indlekofer,
   Christoph Stadtfeld, Per Block, Marion Hoffman, and Robert Hellpap.
 
   Maintainer: Tom A.B. Snijders <tom.snijders at nuffield.ox.ac.uk>

Modified: pkg/RSienaTest/man/setEffect.Rd
===================================================================
--- pkg/RSienaTest/man/setEffect.Rd	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/man/setEffect.Rd	2019-10-24 12:49:20 UTC (rev 342)
@@ -94,10 +94,9 @@
    The call of \link{setEffect} will set, for this effect,
    the column elements of the resulting effects object for \code{parameter},
    \code{fix}, \code{test}, \code{randomEffects}, \code{initialValue},
-    \code{timeDummy}, and \code{include} to the values requested.} 
-	
+    \code{timeDummy}, and \code{include} to the values requested.\cr	
 	The \code{shortName} must not be set between quotes,
-	unless you use \code{character=TRUE}.
+	unless you use \code{character=TRUE}.}
 \value{
   An object of class \code{\link{sienaEffects}} or
   \code{\link{sienaGroupEffects}}. This will be an updated version of the

Modified: pkg/RSienaTest/man/sienaDependent.Rd
===================================================================
--- pkg/RSienaTest/man/sienaDependent.Rd	2019-10-16 20:25:33 UTC (rev 341)
+++ pkg/RSienaTest/man/sienaDependent.Rd	2019-10-24 12:49:20 UTC (rev 342)
@@ -18,9 +18,14 @@
 nodeSet="Actors", sparse=is.list(netarray), allowOnly=TRUE, imputationValues=NULL)
 }
 \arguments{
-  \item{netarray}{matrix (type="behavior" or "continuous" only)
-    or (for the other types) array of values or list of sparse matrices
-    of type "dgTMatrix".}
+  \item{netarray}{type="behavior" or "continuous": matrix 
[TRUNCATED]

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


More information about the Rsiena-commits mailing list