[Rsiena-commits] r6 - in pkg/RSiena: R src/data src/model/effects

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sat Aug 1 23:15:39 CEST 2009


Author: ripleyrm
Date: 2009-08-01 23:15:38 +0200 (Sat, 01 Aug 2009)
New Revision: 6

Added:
   pkg/RSiena/R/getTargets.r
   pkg/RSiena/src/data/DyadicCovariateValueIterator.cpp
   pkg/RSiena/src/data/DyadicCovariateValueIterator.h
   pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.cpp
   pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.h
   pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.cpp
   pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.h
   pkg/RSiena/src/model/effects/InverseOutdegreeEffect.cpp
   pkg/RSiena/src/model/effects/InverseOutdegreeEffect.h
   pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.cpp
   pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.h
   pkg/RSiena/src/model/effects/WWXClosureEffect.cpp
   pkg/RSiena/src/model/effects/WWXClosureEffect.h
   pkg/RSiena/src/model/effects/WXXClosureEffect.cpp
   pkg/RSiena/src/model/effects/WXXClosureEffect.h
   pkg/RSiena/src/model/effects/XWXClosureEffect.cpp
   pkg/RSiena/src/model/effects/XWXClosureEffect.h
Log:
New files omitted by mistake.

Added: pkg/RSiena/R/getTargets.r
===================================================================
--- pkg/RSiena/R/getTargets.r	                        (rev 0)
+++ pkg/RSiena/R/getTargets.r	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,43 @@
+getTargets <- function(data, effects)
+{
+    f <- unpackData(data)
+    effects <- effects[effects$include,]
+    ##dyn.load(dllpath)
+    ##
+    ## dyn.load('d:/sienasvn/siena/src/RSiena.dll')
+    pData <- .Call('setupData', PACKAGE="RSiena",
+                   list(as.integer(f$observations)),
+                   list(f$nodeSets))
+    ## register a finalizer
+    ans <- reg.finalizer(pData, clearData, onexit = FALSE)
+    ans<- .Call('OneMode', PACKAGE="RSiena",
+                pData, list(f$nets))
+    ans<- .Call('Behavior', PACKAGE="RSiena", pData,
+               list(f$behavs))
+    ans<-.Call('ConstantCovariates', PACKAGE="RSiena",
+               pData, list(f$cCovars))
+    ans<-.Call('ChangingCovariates',PACKAGE="RSiena",
+               pData,list(f$vCovars))
+    ans<-.Call('DyadicCovariates',PACKAGE="RSiena",
+               pData,list(f$dycCovars))
+    ans<-.Call('ChangingDyadicCovariates',PACKAGE="RSiena",
+               pData, list(f$dyvCovars))
+    storage.mode(effects$parm) <- 'integer'
+    storage.mode(effects$group) <- 'integer'
+    storage.mode(effects$period) <- 'integer'
+    effects$effectPtr <- NA
+    myeffects <- split(effects, effects$name)
+    ans<- .Call('effects', PACKAGE="RSiena",
+                pData, myeffects)
+    pModel <- ans[[1]][[1]]
+        for (i in 1:length(ans[[2]])) ## ans[[2]] is a list of lists of
+            ## pointers to effects. Each list corresponds to one
+            ## dependent variable
+        {
+            effectPtr <- ans[[2]][[i]]
+            myeffects[[i]]$effectPtr <- effectPtr
+        }
+    ans <- .Call('getTargets', PACKAGE="RSiena",
+                 pData, pModel, myeffects)
+    ans
+}

Added: pkg/RSiena/src/data/DyadicCovariateValueIterator.cpp
===================================================================
--- pkg/RSiena/src/data/DyadicCovariateValueIterator.cpp	                        (rev 0)
+++ pkg/RSiena/src/data/DyadicCovariateValueIterator.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,108 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: DyadicCovariateValueIterator.cpp
+ *
+ * Description: This file contains the implementation of the class
+ * DyadicCovariateValueIterator.
+ *****************************************************************************/
+
+#include "DyadicCovariateValueIterator.h"
+#include "utils/Utils.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ * @param[in] rValues the map storing the non-zero values w_{ij} for each j
+ * @param[in] rMissings a set of actors for which the values w_{ij} are missing
+ */
+DyadicCovariateValueIterator::DyadicCovariateValueIterator(
+	map<int, double> & rValues,
+	set<int> & rMissings)
+{
+	this->lcurrent = rValues.begin();
+	this->lend = rValues.end();
+	this->lmissingCurrent = rMissings.begin();
+	this->lmissingEnd = rMissings.end();
+
+	this->skipMissings();
+}
+
+
+/**
+ * Returns the current actor j with a non-zero non-missing value
+ * w_{ij} of the covariate.
+ */
+int DyadicCovariateValueIterator::actor() const
+{
+	if (!this->valid())
+	{
+		throw InvalidIteratorException();
+	}
+
+	return this->lcurrent->first;
+}
+
+
+/**
+ * Returns the current non-zero non-missing value w_{ij} of the covariate.
+ */
+double DyadicCovariateValueIterator::value() const
+{
+	if (!this->valid())
+	{
+		throw InvalidIteratorException();
+	}
+
+	return this->lcurrent->second;
+}
+
+
+/**
+ * Indicates if the iterator still points to a valid actor j with a non-zero
+ * non-missing covariate value w_{ij}.
+ */
+bool DyadicCovariateValueIterator::valid() const
+{
+	return this->lcurrent != this->lend;
+}
+
+
+/**
+ * Moves the iterator to the next actor j with a non-zero non-missing covariate
+ * value w_{ij}.
+ */
+void DyadicCovariateValueIterator::next()
+{
+	this->lcurrent++;
+	this->skipMissings();
+}
+
+
+/**
+ * Makes sure that lcurrent points to the next non-zero value of the
+ * covariate that is not missing.
+ */
+void DyadicCovariateValueIterator::skipMissings()
+{
+	while (this->lmissingCurrent != this->lmissingEnd &&
+		this->lcurrent != this->lend &&
+		(*this->lmissingCurrent) <= this->lcurrent->first)
+	{
+		if ((*this->lmissingCurrent) == this->lcurrent->first)
+		{
+			// The current iterator points to a non-zero value,
+			// but it is missing, so we skip it.
+
+			this->lcurrent++;
+		}
+
+		this->lmissingCurrent++;
+	}
+}
+
+}

Added: pkg/RSiena/src/data/DyadicCovariateValueIterator.h
===================================================================
--- pkg/RSiena/src/data/DyadicCovariateValueIterator.h	                        (rev 0)
+++ pkg/RSiena/src/data/DyadicCovariateValueIterator.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,60 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: DyadicCovariateValueIterator.h
+ *
+ * Description: This file contains the definition of the
+ * DyadicCovariateValueIterator class.
+ *****************************************************************************/
+
+#ifndef DYADICCOVARIATEVALUEITERATOR_H_
+#define DYADICCOVARIATEVALUEITERATOR_H_
+
+#include <map>
+#include <set>
+
+using namespace std;
+
+namespace siena
+{
+
+/**
+ * Defines an iterator over non-zero values w_{ij} of a dyadic covariate
+ * for a specific actor i.
+ */
+class DyadicCovariateValueIterator
+{
+	// These classes needs access to the private constructor.
+
+	friend class ConstantDyadicCovariate;
+	friend class ChangingDyadicCovariate;
+
+public:
+	int actor() const;
+	double value() const;
+	bool valid() const;
+	void next();
+
+private:
+	DyadicCovariateValueIterator(map<int, double> & rValues,
+		set<int> & rMissings);
+	void skipMissings();
+
+	// Points to the current element in the map of values
+	map<int, double>::const_iterator lcurrent;
+
+	// Points to the end of the map of values
+	map<int, double>::const_iterator lend;
+
+	// Points to the current element in the set of missing values
+	set<int>::const_iterator lmissingCurrent;
+
+	// Points to the end of the set of missing values
+	set<int>::const_iterator lmissingEnd;
+};
+
+}
+
+#endif /*DYADICCOVARIATEVALUEITERATOR_H_*/

Added: pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,233 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: CovariateIndirectTiesEffect.cpp
+ *
+ * Description: This file contains the implementation of the class
+ * CovariateIndirectTiesEffect.
+ *****************************************************************************/
+#include <R.h>
+#include <stdexcept>
+
+#include "CovariateIndirectTiesEffect.h"
+#include "data/Network.h"
+#include "data/NetworkLongitudinalData.h"
+#include "data/IncidentTieIterator.h"
+#include "model/variables/NetworkVariable.h"
+#include "model/tables/ConfigurationTable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+CovariateIndirectTiesEffect::CovariateIndirectTiesEffect(
+	const EffectInfo * pEffectInfo) :
+		CovariateDependentNetworkEffect(pEffectInfo)
+{
+}
+
+
+/**
+ * Calculates the contribution of a tie flip to the given actor.
+ */
+double CovariateIndirectTiesEffect::calculateTieFlipContribution(int alter)
+	const
+{
+	double change = 0;
+
+	// If there are enough two-paths from the ego i to the alter j, then
+	// we loose the distance 2 pair (i,j) by introducing the tie between
+	// them.
+
+	if (this->pVariable()->pTwoPathTable()->get(alter) != 0)
+	{
+		change -= this->value(alter);
+	}
+
+	// This variable is to simplify the later tests if a two-path through
+	// the given alter makes a difference.
+
+	int criticalTwoPathCount = 0;
+
+	if (this->pVariable()->outTieExists(alter))
+	{
+		criticalTwoPathCount = 1;
+	}
+
+	// Consider each outgoing tie of the alter j.
+
+	for (IncidentTieIterator iter =
+			this->pVariable()->pNetwork()->outTies(alter);
+		iter.valid();
+		iter.next())
+	{
+		int h = iter.actor();
+
+		// If h is not the ego i, there's no tie from i to h, and the
+		// introduction or withdrawal of the tie (i,j) makes a difference
+		// for the pair <i,h> to be a valid distance two pair,
+		// then increment the contribution.
+
+		if (h != this->pVariable()->ego() &&
+			!this->pVariable()->outTieExists(h) &&
+			this->pVariable()->pTwoPathTable()->get(h) == criticalTwoPathCount)
+		{
+			change += this->value(h);
+		}
+	}
+
+	// For dissolutions of ties the contribution works in the opposite way.
+
+	if (this->pVariable()->outTieExists(alter))
+	{
+		change = -change;
+	}
+	return change;
+}
+
+
+/**
+ * Returns if the given configuration table is used by this effect
+ * during the calculation of tie flip contributions.
+ */
+bool CovariateIndirectTiesEffect::usesTable(const ConfigurationTable * pTable)
+	const
+{
+	return pTable == this->pVariable()->pTwoPathTable();
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the evaluation function with respect to the given network.
+ */
+double CovariateIndirectTiesEffect::evaluationStatistic(Network * pNetwork)
+	const
+{
+	double statistic = 0;
+	int n = pNetwork->n();
+
+	const Network * pStartMissingNetwork =
+		this->pData()->pMissingTieNetwork(this->period());
+	const Network * pEndMissingNetwork =
+		this->pData()->pMissingTieNetwork(this->period() + 1);
+
+	// A helper array of marks
+
+	int * mark = new int[n];
+
+	for (int i = 0; i < n; i++)
+	{
+		mark[i] = -1;
+	}
+
+	// Treat the distance-two pairs <i,h> for each i separately.
+
+	for (int i = 0; i < n; i++)
+	{
+		// Invariant: mark[h] = i if and only if a two-path from i
+		// to h has been found.
+
+		// Traverse all two-paths from i
+
+		for (IncidentTieIterator iterI = pNetwork->outTies(i);
+			iterI.valid();
+			iterI.next())
+		{
+			int j = iterI.actor();
+
+			for (IncidentTieIterator iterJ = pNetwork->outTies(j);
+				iterJ.valid();
+				iterJ.next())
+			{
+				int h = iterJ.actor();
+
+				if (mark[h] < i)
+				{
+					// The first two-path from i to h is found.
+
+					mark[h] = i;
+					statistic += this->value(h);
+				}
+			}
+		}
+
+		// Okay, if there's a tie (i,h) then <i,h> cannot possibly be a
+		// distance-two pair. Hence we iterate over outgoing ties (i,h) of i,
+		// and if value(h) has been added to the statistic, we subtract it.
+
+		for (IncidentTieIterator iter = pNetwork->outTies(i);
+			iter.valid();
+			iter.next())
+		{
+			int h = iter.actor();
+
+			if (mark[h] == i)
+			{
+				mark[h] = -1;
+				statistic -= this->value(h);
+			}
+		}
+
+		// We do a similar fix for missing ties (i,h) at either end of
+		// the period.
+
+		for (IncidentTieIterator iter = pStartMissingNetwork->outTies(i);
+			iter.valid();
+			iter.next())
+		{
+			int h = iter.actor();
+
+			if (mark[h] == i)
+			{
+				mark[h] = -1;
+				statistic -= this->value(h);
+			}
+		}
+
+		for (IncidentTieIterator iter = pEndMissingNetwork->outTies(i);
+			iter.valid();
+			iter.next())
+		{
+			int h = iter.actor();
+
+			if (mark[h] == i)
+			{
+				mark[h] = -1;
+				statistic -= this->value(h);
+			}
+		}
+
+		// Ignore the trivial pair <i,i>.
+
+		if (mark[i] == i)
+		{
+			statistic -= this->value(i);
+		}
+	}
+
+	delete[] mark;
+
+	return statistic;
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the endowment function with respect to an initial network
+ * and a network of lost ties. The current network is implicit as
+ * the introduced ties are not relevant for calculating
+ * endowment statistics.
+ */
+double CovariateIndirectTiesEffect::endowmentStatistic(Network * pInitialNetwork,
+	Network * pLostTieNetwork) const
+{
+	throw logic_error(
+		"CovariateIndirectTiesEffect: Endowment effect not supported");
+}
+
+}

Added: pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.h
===================================================================
--- pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.h	                        (rev 0)
+++ pkg/RSiena/src/model/effects/CovariateIndirectTiesEffect.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,37 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: CovariateIndirectTiesEffect.h
+ *
+ * Description: This file contains the declaration of the class
+ * CovariateIndirectTiesEffect.
+ *****************************************************************************/
+
+#ifndef COVARIATEINDIRECTTIESEFFECT_H_
+#define COVARIATEINDIRECTTIESEFFECT_H_
+
+#include "model/effects/CovariateDependentNetworkEffect.h"
+
+namespace siena
+{
+
+/**
+ * Covariate of indirect ties effect (see manual).
+ */
+class CovariateIndirectTiesEffect : public CovariateDependentNetworkEffect
+{
+public:
+	CovariateIndirectTiesEffect(const EffectInfo * pEffectInfo);
+
+	virtual double calculateTieFlipContribution(int alter) const;
+	virtual bool usesTable(const ConfigurationTable * pTable) const;
+	virtual double evaluationStatistic(Network * pNetwork) const;
+	virtual double endowmentStatistic(Network * pInitialNetwork,
+		Network * pLostTieNetwork) const;
+};
+
+}
+
+#endif /*COVARIATEINDIRECTTIESEFFECT_H_*/

Added: pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,89 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: DyadicCovariateReciprocityEffect.cpp
+ *
+ * Description: This file contains the implementation of the
+ * DyadicCovariateReciprocityEffect class.
+ *****************************************************************************/
+
+#include "DyadicCovariateReciprocityEffect.h"
+#include "data/Network.h"
+#include "data/CommonNeighborIterator.h"
+#include "model/variables/NetworkVariable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+DyadicCovariateReciprocityEffect::DyadicCovariateReciprocityEffect(
+	const EffectInfo * pEffectInfo) :
+		DyadicCovariateDependentNetworkEffect(pEffectInfo)
+{
+}
+
+
+/**
+ * Calculates the contribution of a tie flip to the given actor.
+ */
+double DyadicCovariateReciprocityEffect::calculateTieFlipContribution(
+	int alter) const
+{
+	double change = 0;
+	int ego = this->pVariable()->ego();
+
+	if (this->pVariable()->inTieExists(alter) && !this->missing(ego, alter))
+	{
+		change = this->value(ego, alter);
+
+		if (this->pVariable()->outTieExists(alter))
+		{
+			// The ego would loose the tie and consequently the covariate value
+			change = -change;
+		}
+	}
+
+	return change;
+}
+
+
+/**
+ * Detailed comment in the base class.
+ */
+double DyadicCovariateReciprocityEffect::statistic(Network * pNetwork,
+	Network * pSummationTieNetwork) const
+{
+	double statistic = 0;
+	int n = pNetwork->n();
+
+	// The summation network is a subnetwork of the (main) network.
+	// So essentially, we are iterating over ties of the summation network
+	// that are reciprocated in the main network, and add up the (non-missing)
+	// covariate values for these ties.
+
+	for (int i = 0; i < n; i++)
+	{
+		CommonNeighborIterator iter(pSummationTieNetwork->outTies(i),
+			pNetwork->inTies(i));
+
+		while (iter.valid())
+		{
+			int j = iter.actor();
+
+			if (!this->missing(i, j))
+			{
+				statistic += this->value(i, j);
+			}
+
+			iter.next();
+		}
+	}
+
+	return statistic;
+}
+
+}

Added: pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.h
===================================================================
--- pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.h	                        (rev 0)
+++ pkg/RSiena/src/model/effects/DyadicCovariateReciprocityEffect.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,38 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: DyadicCovariateReciprocityEffect.h
+ *
+ * Description: This file contains the definition of the
+ * DyadicCovariateReciprocityEffect class.
+ *****************************************************************************/
+
+#ifndef DYADICCOVARIATERECIPROCITYEFFECT_H_
+#define DYADICCOVARIATERECIPROCITYEFFECT_H_
+
+#include "DyadicCovariateDependentNetworkEffect.h"
+
+namespace siena
+{
+
+/**
+ * Dyadic covariate x reciprocity effect (see manual).
+ */
+class DyadicCovariateReciprocityEffect :
+	public DyadicCovariateDependentNetworkEffect
+{
+public:
+	DyadicCovariateReciprocityEffect(const EffectInfo * pEffectInfo);
+
+	virtual double calculateTieFlipContribution(int alter) const;
+
+protected:
+	virtual double statistic(Network * pNetwork,
+		Network * pSummationTieNetwork) const;
+};
+
+}
+
+#endif /*DYADICCOVARIATERECIPROCITYEFFECT_H_*/

Added: pkg/RSiena/src/model/effects/InverseOutdegreeEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/InverseOutdegreeEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/InverseOutdegreeEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,91 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: InverseOutdegreeEffect.cpp
+ *
+ * Description: This file contains the implementation of the class
+ * InverseOutdegreeEffect.
+ *****************************************************************************/
+
+#include <stdexcept>
+#include "InverseOutdegreeEffect.h"
+#include "data/Network.h"
+#include "model/EffectInfo.h"
+#include "model/variables/NetworkVariable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+InverseOutdegreeEffect::InverseOutdegreeEffect(
+	const EffectInfo * pEffectInfo) : NetworkEffect(pEffectInfo)
+{
+	this->lc = pEffectInfo->internalEffectParameter();
+
+	if (this->lc < 1)
+	{
+		throw invalid_argument(
+			"InverseOutdegreeEffect: Parameter value must be at least 1");
+	}
+}
+
+
+/**
+ * Calculates the contribution of a tie flip to the given actor.
+ */
+double InverseOutdegreeEffect::calculateTieFlipContribution(int alter) const
+{
+	double sum =
+		this->pVariable()->pNetwork()->outDegree(this->pVariable()->ego()) +
+			this->lc;
+
+	if (this->pVariable()->outTieExists(alter))
+	{
+		// Tie withdrawal
+		return 1.0 / ((sum - 1) * sum);
+	}
+	else
+	{
+		// Tie introduction
+		return -1.0 / ((sum + 1) * sum);
+	}
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the evaluation function with respect to the given network.
+ */
+double InverseOutdegreeEffect::evaluationStatistic(Network * pNetwork) const
+{
+	double statistic = 0;
+	int n = pNetwork->n();
+
+	for (int i = 0; i < n; i++)
+	{
+		statistic += 1.0 / (pNetwork->outDegree(i) + this->lc);
+	}
+
+	return statistic;
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the endowment function with respect to an initial network
+ * and a network of lost ties. The current network is implicit as
+ * the introduced ties are not relevant for calculating
+ * endowment statistics.
+ */
+double InverseOutdegreeEffect::endowmentStatistic(Network * pInitialNetwork,
+	Network * pLostTieNetwork) const
+{
+	throw logic_error(
+		"InverseOutdegreeEffect: Endowment effect not supported.");
+}
+
+}

Added: pkg/RSiena/src/model/effects/InverseOutdegreeEffect.h
===================================================================
--- pkg/RSiena/src/model/effects/InverseOutdegreeEffect.h	                        (rev 0)
+++ pkg/RSiena/src/model/effects/InverseOutdegreeEffect.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,41 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: InverseOutdegreeEffect.h
+ *
+ * Description: This file contains the declaration of the class
+ * InverseOutdegreeEffect.
+ *****************************************************************************/
+
+#ifndef INVERSEOUTDEGREEEFFECT_H_
+#define INVERSEOUTDEGREEEFFECT_H_
+
+#include "NetworkEffect.h"
+
+namespace siena
+{
+
+/**
+ * This class defines the inverse outdegree effect defined as
+ * s_i = 1/(outdegree(i) + c), where c is a parameter.
+ * See the manual for effect definitions.
+ */
+class InverseOutdegreeEffect : public NetworkEffect
+{
+public:
+	InverseOutdegreeEffect(const EffectInfo * pEffectInfo);
+
+	virtual double calculateTieFlipContribution(int alter) const;
+	virtual double evaluationStatistic(Network * pNetwork) const;
+	virtual double endowmentStatistic(Network * pInitialNetwork,
+		Network * pLostTieNetwork) const;
+
+private:
+	double lc;
+};
+
+}
+
+#endif /*INVERSEOUTDEGREEEFFECT_H_*/

Added: pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,94 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: InverseSquaredOutdegreeEffect.cpp
+ *
+ * Description: This file contains the implementation of the class
+ * InverseSquaredOutdegreeEffect.
+ *****************************************************************************/
+
+#include <stdexcept>
+#include "InverseSquaredOutdegreeEffect.h"
+#include "data/Network.h"
+#include "model/EffectInfo.h"
+#include "model/variables/NetworkVariable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+InverseSquaredOutdegreeEffect::InverseSquaredOutdegreeEffect(
+	const EffectInfo * pEffectInfo) : NetworkEffect(pEffectInfo)
+{
+	this->lc = pEffectInfo->internalEffectParameter();
+
+	if (this->lc < 1)
+	{
+		throw invalid_argument(
+			string("InverseSquaredOutdegreeEffect: ") +
+			"Parameter value must be at least 1");
+	}
+}
+
+
+/**
+ * Calculates the contribution of a tie flip to the given actor.
+ */
+double InverseSquaredOutdegreeEffect::calculateTieFlipContribution(int alter)
+	const
+{
+	double sum =
+		this->pVariable()->pNetwork()->outDegree(this->pVariable()->ego()) +
+			this->lc;
+
+	if (this->pVariable()->outTieExists(alter))
+	{
+		// Tie withdrawal
+		return 2.0 / ((sum - 1) * sum * (sum + 1));
+	}
+	else
+	{
+		// Tie introduction
+		return -2.0 / (sum * (sum + 1) * (sum + 2));
+	}
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the evaluation function with respect to the given network.
+ */
+double InverseSquaredOutdegreeEffect::evaluationStatistic(Network * pNetwork) const
+{
+	double statistic = 0;
+	int n = pNetwork->n();
+
+	for (int i = 0; i < n; i++)
+	{
+		double sum = pNetwork->outDegree(i) + this->lc;
+		statistic += 1.0 / (sum * (sum + 1));
+	}
+
+	return statistic;
+}
+
+
+/**
+ * Returns the statistic corresponding to this effect as part of
+ * the endowment function with respect to an initial network
+ * and a network of lost ties. The current network is implicit as
+ * the introduced ties are not relevant for calculating
+ * endowment statistics.
+ */
+double InverseSquaredOutdegreeEffect::endowmentStatistic(Network * pInitialNetwork,
+	Network * pLostTieNetwork) const
+{
+	throw logic_error(
+		"InverseSquaredOutdegreeEffect: Endowment effect not supported.");
+}
+
+}

Added: pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.h
===================================================================
--- pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.h	                        (rev 0)
+++ pkg/RSiena/src/model/effects/InverseSquaredOutdegreeEffect.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,41 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: InverseSquaredOutdegreeEffect.h
+ *
+ * Description: This file contains the declaration of the class
+ * InverseSquaredOutdegreeEffect.
+ *****************************************************************************/
+
+#ifndef INVERSESQUAREDOUTDEGREEEFFECT_H_
+#define INVERSESQUAREDOUTDEGREEEFFECT_H_
+
+#include "NetworkEffect.h"
+
+namespace siena
+{
+
+/**
+ * This class defines the inverse squared outdegree effect defined as
+ * s_i = 1/[(outdegree(i) + c) * (outdegree(i) + c + 1)], where c is
+ * a parameter. See the manual for effect definitions.
+ */
+class InverseSquaredOutdegreeEffect : public NetworkEffect
+{
+public:
+	InverseSquaredOutdegreeEffect(const EffectInfo * pEffectInfo);
+
+	virtual double calculateTieFlipContribution(int alter) const;
+	virtual double evaluationStatistic(Network * pNetwork) const;
+	virtual double endowmentStatistic(Network * pInitialNetwork,
+		Network * pLostTieNetwork) const;
+
+private:
+	double lc;
+};
+
+}
+
+#endif /*INVERSESQUAREDOUTDEGREEEFFECT_H_*/

Added: pkg/RSiena/src/model/effects/WWXClosureEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/WWXClosureEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/WWXClosureEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,162 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: WWXClosureEffect.cpp
+ *
+ * Description: This file contains the implementation of the
+ * WWXClosureEffect class.
+ *****************************************************************************/
+
+#include "WWXClosureEffect.h"
+#include "data/Network.h"
+#include "data/NetworkLongitudinalData.h"
+#include "data/IncidentTieIterator.h"
+#include "data/DyadicCovariateValueIterator.h"
+#include "model/variables/NetworkVariable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+WWXClosureEffect::WWXClosureEffect(const EffectInfo * pEffectInfo) :
+	DyadicCovariateDependentNetworkEffect(pEffectInfo)
+{
+	this->lsums = 0;
+}
+
+
+/**
+ * Destructor.
+ */
+WWXClosureEffect::~WWXClosureEffect()
+{
+	delete[] this->lsums;
+	this->lsums = 0;
+}
+
+
+/**
+ * Initializes this effect for the use with the given epoch simulation.
+ */
+void WWXClosureEffect::initialize(EpochSimulation * pSimulation)
+{
+	DyadicCovariateDependentNetworkEffect::initialize(pSimulation);
+
+	delete[] this->lsums;
+	this->lsums = new double[this->pVariable()->n()];
+}
+
+
+/**
+ * Initializes this effect for calculating the corresponding statistics.
+ * @param[in] pData the observed data
+ * @param[in] pState the current state of the dependent variables
+ * @param[in] period the period of interest
+ */
+void WWXClosureEffect::initialize(const Data * pData,
+	State * pState,
+	int period)
+{
+	DyadicCovariateDependentNetworkEffect::initialize(pData, pState, period);
+}
+
+
+/**
+ * Does the necessary preprocessing work for calculating the tie flip
+ * contributions for a specific ego. This method must be invoked before
+ * calling NetworkEffect::calculateTieFlipContribution(...).
+ */
+void WWXClosureEffect::preprocessEgo()
+{
+	this->calculateSums(this->pVariable()->ego(),
+		this->pVariable()->pNetwork(),
+		this->lsums);
+}
+
+
+/**
+ * For each j and the given i, this method calculates the sum
+ * sum_h w_{ih} w_{hj}.
+ */
+void WWXClosureEffect::calculateSums(int i, Network * pNetwork, double * sums)
+	const
+{
+	int n = pNetwork->n();
+
+	// Initialize
+
+	for (int j = 0; j < n; j++)
+	{
+		sums[j] = 0;
+	}
+
+	// Iterate over all h with non-zero non-missing w_{ih}
+
+	for (DyadicCovariateValueIterator iterH = this->rowValues(i);
+		iterH.valid();
+		iterH.next())
+	{
+		int h = iterH.actor();
+
+		// Iterate over all j with non-zero non-missing w_{hj}
+
+		for (DyadicCovariateValueIterator iterJ = this->rowValues(h);
+			iterJ.valid();
+			iterJ.next())
+		{
+			int j = iterJ.actor();
+
+			// Add the term w_{ih} w_{hj}
+			sums[j] += iterH.value() * iterJ.value();
+		}
+	}
+}
+
+
+/**
+ * Calculates the contribution of a tie flip to the given actor.
+ */
+double WWXClosureEffect::calculateTieFlipContribution(int alter) const
+{
+	double change = this->lsums[alter];
+
+	if (this->pVariable()->outTieExists(alter))
+	{
+		change = -change;
+	}
+
+	return change;
+}
+
+
+/**
+ * Detailed comment in the base class.
+ */
+double WWXClosureEffect::statistic(Network * pNetwork,
+	Network * pSummationTieNetwork) const
+{
+	double statistic = 0;
+	int n = pNetwork->n();
+	double * sums = new double[n];
+
+	for (int i = 0; i < n; i++)
+	{
+		this->calculateSums(i, pNetwork, sums);
+
+		for (IncidentTieIterator iter = pSummationTieNetwork->outTies(i);
+			iter.valid();
+			iter.next())
+		{
+			statistic += sums[iter.actor()];
+		}
+	}
+
+	delete[] sums;
+	return statistic;
+}
+
+}

Added: pkg/RSiena/src/model/effects/WWXClosureEffect.h
===================================================================
--- pkg/RSiena/src/model/effects/WWXClosureEffect.h	                        (rev 0)
+++ pkg/RSiena/src/model/effects/WWXClosureEffect.h	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,50 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: WWXClosureEffect.h
+ *
+ * Description: This file contains the definition of the
+ * WWXClosureEffect class.
+ *****************************************************************************/
+
+#ifndef WWXCLOSUREEFFECT_H_
+#define WWXCLOSUREEFFECT_H_
+
+#include "DyadicCovariateDependentNetworkEffect.h"
+
+namespace siena
+{
+
+/**
+ * WW => X closure of covariate effect (see manual).
+ */
+class WWXClosureEffect : public DyadicCovariateDependentNetworkEffect
+{
+public:
+	WWXClosureEffect(const EffectInfo * pEffectInfo);
+	virtual ~WWXClosureEffect();
+
+	virtual void initialize(EpochSimulation * pSimulation);
+	virtual void initialize(const Data * pData, State * pState, int period);
+
+	virtual void preprocessEgo();
+	virtual double calculateTieFlipContribution(int alter) const;
+
+protected:
+	virtual double statistic(Network * pNetwork,
+		Network * pSummationTieNetwork) const;
+
+private:
+	void calculateSums(int i, Network * pNetwork, double * sums) const;
+
+	// For a fixed i, this variable stores the value of sum_h w_{ih} w_{hj} for
+	// each j.
+
+	double * lsums;
+};
+
+}
+
+#endif /*WWXCLOSUREEFFECT_H_*/

Added: pkg/RSiena/src/model/effects/WXXClosureEffect.cpp
===================================================================
--- pkg/RSiena/src/model/effects/WXXClosureEffect.cpp	                        (rev 0)
+++ pkg/RSiena/src/model/effects/WXXClosureEffect.cpp	2009-08-01 21:15:38 UTC (rev 6)
@@ -0,0 +1,162 @@
+/******************************************************************************
+ * SIENA: Simulation Investigation for Empirical Network Analysis
+ *
+ * Web: http://www.stats.ox.ac.uk/~snijders/siena/
+ *
+ * File: WXXClosureEffect.cpp
+ *
+ * Description: This file contains the implementation of the
+ * WXXClosureEffect class.
+ *****************************************************************************/
+
+#include "WXXClosureEffect.h"
+#include "data/Network.h"
+#include "data/IncidentTieIterator.h"
+#include "data/NetworkLongitudinalData.h"
+#include "data/DyadicCovariateValueIterator.h"
+#include "model/variables/NetworkVariable.h"
+
+namespace siena
+{
+
+/**
+ * Constructor.
+ */
+WXXClosureEffect::WXXClosureEffect(const EffectInfo * pEffectInfo) :
+	DyadicCovariateDependentNetworkEffect(pEffectInfo)
+{
+	this->lsums = 0;
+}
+
+
+/**
+ * Destructor.
+ */
+WXXClosureEffect::~WXXClosureEffect()
+{
+	delete[] this->lsums;
+	this->lsums = 0;
+}
+
+
+/**
+ * Initializes this effect for the use with the given epoch simulation.
+ */
+void WXXClosureEffect::initialize(EpochSimulation * pSimulation)
+{
+	DyadicCovariateDependentNetworkEffect::initialize(pSimulation);
+
+	delete[] this->lsums;
+	this->lsums = new double[this->pVariable()->n()];
+}
+
+
+/**
+ * Initializes this effect for calculating the corresponding statistics.
+ * @param[in] pData the observed data
+ * @param[in] pState the current state of the dependent variables
+ * @param[in] period the period of interest
+ */
+void WXXClosureEffect::initialize(const Data * pData,
+	State * pState,
+	int period)
+{
[TRUNCATED]

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


More information about the Rsiena-commits mailing list