Skip to content

Commit

Permalink
Implemented square root of triangle statistics, demonstrating both pr…
Browse files Browse the repository at this point in the history
…ivate and auxiliary storage.

fixes #3
  • Loading branch information
krivit committed Feb 10, 2025
1 parent 746f080 commit cdb7d9d
Show file tree
Hide file tree
Showing 6 changed files with 229 additions and 5 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: ergm.userterms
Version: 4.0.0
Date: 2019-05-15
Date: 2025-02-10
Title: User-specified Terms for the statnet Suite of Packages
Authors@R: c(
person("Mark S.", "Handcock", role=c("aut"), email="handcock@stat.ucla.edu"),
Expand Down
67 changes: 65 additions & 2 deletions R/InitErgmTerm.users.R
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,8 @@
#' same value of the `by` attribute.
#'
### Import the standard ergmTerm documentation template so that it
### gets indexed in ?ergmTerm.
### gets indexed in ?ergmTerm. This and other templates can be copied
### from 'ergm' source code on GitHub, in the man-roxygen/ directory.
###
#' @template ergmTerm-general
#'
Expand All @@ -82,7 +83,6 @@
###
#' @concept undirected
#' @concept categorical nodal attribute
#' @concept frequently-used
###
### No @export!
InitErgmTerm.mindegree <- function(nw, arglist, ...) {
Expand Down Expand Up @@ -116,8 +116,71 @@ InitErgmTerm.mindegree <- function(nw, arglist, ...) {
)
}

#' @templateVar name sqrt.triangle
#'
#' @title Square root of the number of triangles
#'
#' @description These terms add one network statistic to the model,
#' the square root of the number of triangles. They demonstrate the
#' private and auxiliary storage mechanisms. The change statistic
#' for the square root of the number of triangles depends on the
#' initial number of triangles, so it is costly to compute -- unless
#' one can keep track of the number of triangles. These terms can
#' only be used with undirected networks.
#'
#' @usage
#' # binary: sqrt.triangle
#'
#' @template ergmTerm-general
#'
#' @examples
#'
#' data(florentine)
#'
#' sqrt(summary(flomarriage~triangle))
#' summary(flomarriage~sqrt.triangle)
#'
#' stopifnot(sqrt(summary(flomarriage~triangle)) == summary(flomarriage~sqrt.triangle))
#'
#' @concept undirected
#' @concept triadic
InitErgmTerm.sqrt.triangle <- function(nw, arglist, ...) {
# No arguments:
a <- check.ErgmTerm(nw, arglist, directed=FALSE, bipartite=FALSE)

# coef.names can have nonstandard characters:
list(name = "sqrt_triangle", coef.names = "sqrt(triangle)", dependence = TRUE)
}

### This also demonstrates how to document multiple terms in one
### file. The following two Roxygen lines generate code to merge the
### documentation into the sqrt.triangle-ergmTerm documentation. Note
### that the alias has to be set manually.
#' @templateVar name sqrt.triangle
#' @template ergmTerm-rdname
#' @aliases sqrt.triangle.aux-ergmTerm
#' @usage
#' # binary: sqrt.triangle.aux
#'
#' @examples
#' summary(flomarriage~sqrt.triangle.aux)
#'
#' stopifnot(sqrt(summary(flomarriage~triangle)) == summary(flomarriage~sqrt.triangle.aux))
InitErgmTerm.sqrt.triangle.aux <- function(nw, arglist, ...) {
# No arguments:
a <- check.ErgmTerm(nw, arglist, directed=FALSE, bipartite=FALSE)

# coef.names can have nonstandard characters:
list(name = "sqrt_triangle_aux", coef.names = "sqrt(triangle)", dependence = TRUE,
auxiliaries = ~.triangle) # Request the triangles auxiliary.
}

### Auxiliaries don't generally get public documentation, since they
### are not invoked by end-users directly.
InitErgmTerm..triangle <- function(nw, arglist, ...) {
# No arguments:
a <- check.ErgmTerm(nw, arglist, directed=FALSE, bipartite=FALSE)

# coef.names can have nonstandard characters:
list(name = "_triangle") # coef.names is an empty vector -> auxiliary
}
11 changes: 11 additions & 0 deletions man-roxygen/ergmTerm-rdname.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
# File man-roxygen/ergmTerm-rdname.R in package ergm, part of the
# Statnet suite of packages for network analysis, https://statnet.org .
#
# This software is distributed under the GPL-3 license. It is free,
# open source, and has the attribution requirements (GPL Section 7) at
# https://statnet.org/attribution .
#
# Copyright 2003-2025 Statnet Commons
################################################################################
#' <% name <- if(startsWith(name, "'")) substr(name, 2, 1000) else name %>
#' @rdname <%= ergm:::.term.rdname("ergmTerm", name) %>
1 change: 0 additions & 1 deletion man/mindegree-ergmTerm-eabdf279.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

42 changes: 42 additions & 0 deletions man/sqrttriangle-ergmTerm-c7f8ea09.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

111 changes: 110 additions & 1 deletion src/changestats.users.c
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@
*
* Copyright 2012-2019 Statnet Commons
*/
#include "ergm_changestat.h"
#include "ergm_changestat.h" // change statistics API and helper functions
#include "ergm_storage.h" // storage API and helper functions

C_CHANGESTAT_FN(c_mindegree) {
Rboolean attrflag = IINPUT_PARAM[0];
Expand Down Expand Up @@ -39,3 +40,111 @@ C_CHANGESTAT_FN(c_mindegree) {
}
}


/*****************
Square root of triangles: The private storage approach.
*****************/

/* Initializer: store the number of triangles in its private storage. */
I_CHANGESTAT_FN(i_sqrt_triangle) {
ALLOC_STORAGE(1, double, ntri); /* Allocate private storage for 1 number to store the current number of triangles. */

/* NB: In an undirected network, tail < head. */
EXEC_THROUGH_NET_EDGES(tail, head, e1, { /* For each edge (tail < head) in the network... */
EXEC_THROUGH_FOUTEDGES(head, e, node3, { /* and each edge (head < node3)... */
*ntri += IS_OUTEDGE(tail, node3); /* a triangle is formed if an edge exists between node3 and tail. */
});
});

/* *ntri now contains the number of triangles in the network. */
}

/* Updater: will be called when toggling (tail, head) with state edgestate is imminent. */
U_CHANGESTAT_FN(u_sqrt_triangle) {
GET_STORAGE(double, ntri); /* Obtain a pointer to private storage and cast it to the correct type. */
double change = 0;

EXEC_THROUGH_EDGES(head, e, node3, { /* For each edge of head... */
change += IS_UNDIRECTED_EDGE(node3, tail); /* A shared neighbor between tail and head exists if an edge exists between node3 and tail. */
});

/* Thus the toggle of (tail, head) will change the triangle statistic. */
*ntri += edgestate ? -change : change;
}

/* Cleanup; done automatically when STORAGE != NULL, so not needed in this case. */
/* F_CHANGESTAT_FN(f_sqrt_triangle) { */
/* Free(STORAGE); */
/* } */

/* Change statistic: can refer to its storage. */
C_CHANGESTAT_FN(c_sqrt_triangle) {
GET_STORAGE(double, ntri); /* Obtain a pointer to private storage and cast it to the correct type. */
double change = 0;

EXEC_THROUGH_EDGES(head, e, node3, { /* For each edge of head... */
change += IS_UNDIRECTED_EDGE(node3, tail); /* A shared neighbor between tail and head exists if an edge exists between node3 and tail. */
});

/* Now, we add the new value of the statistic and subtract the old. */
CHANGE_STAT[0] += sqrt(*ntri + (edgestate ? -change : change)) - sqrt(*ntri);
}


/*****************
Square root of triangles: The auxiliary approach.
*****************/

/*****
This is an auxiliary term .triangle which exports the number of
triangles that other change statistics can use. Notice that it
doesn't have a c_ or a d_ function.
*****/

/* Initializer: store the number of triangles in its private storage. */
I_CHANGESTAT_FN(i__triangle) {
ALLOC_AUX_STORAGE(1, double, ntri); /* Allocate public storage for 1 number to store the current number of triangles. */

/* NB: In an undirected network, tail < head. */
EXEC_THROUGH_NET_EDGES(tail, head, e1, { /* For each edge (tail < head) in the network... */
EXEC_THROUGH_FOUTEDGES(head, e, node3, { /* and each edge (head < node3)... */
*ntri += IS_OUTEDGE(tail, node3); /* a triangle is formed if an edge exists between node3 and tail. */
});
});

/* *ntri now contains the number of triangles in the network. */
}

/* Updater: will be called when toggling (tail, head) with state edgestate is imminent. */
U_CHANGESTAT_FN(u__triangle) {
GET_AUX_STORAGE(double, ntri); /* Obtain a pointer to its public storage and cast it to the correct type. */
double change = 0;

EXEC_THROUGH_EDGES(head, e, node3, { /* For each edge of head... */
change += IS_UNDIRECTED_EDGE(node3, tail); /* A shared neighbor between tail and head exists if an edge exists between node3 and tail. */
});

/* Thus the toggle of (tail, head) will change the triangle statistic. */
*ntri += edgestate ? -change : change;
}

/* Cleanup; done automatically when STORAGE != NULL, so not needed in this case. */
/* F_CHANGESTAT_FN(f__triangle) { */
/* Free(STORAGE); */
/* } */

/*****
This is a change statistic that expects a the number of triangles in its public storage.
*****/

C_CHANGESTAT_FN(c_sqrt_triangle_aux) {
GET_AUX_STORAGE(double, ntri); /* Obtain a pointer to public storage and cast it to the correct type. */
double change = 0;

EXEC_THROUGH_EDGES(head, e, node3, { /* For each edge of head... */
change += IS_UNDIRECTED_EDGE(node3, tail); /* A shared neighbor between tail and head exists if an edge exists between node3 and tail. */
});

/* Now, we add the new value of the statistic and subtract the old. */
CHANGE_STAT[0] += sqrt(*ntri + (edgestate ? -change : change)) - sqrt(*ntri);
}

0 comments on commit cdb7d9d

Please sign in to comment.