diff --git a/DESCRIPTION b/DESCRIPTION index 87b082b7..c5d086a6 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: manynet Title: Many Ways to Make, Modify, Map, Mark, and Measure Myriad Networks -Version: 1.2.6 -Date: 2024-10-05 +Version: 1.3.0 +Date: 2024-10-16 Description: Many tools for making, modifying, mapping, marking, measuring, and motifs and memberships of many different types of networks. All functions operate with matrices, edge lists, and 'igraph', 'network', and 'tidygraph' objects, @@ -39,7 +39,6 @@ Suggests: knitr, learnr, methods, - multiplex, netdiffuseR, patchwork, readxl, diff --git a/NAMESPACE b/NAMESPACE index f43d8a33..6dc747e8 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -50,6 +50,7 @@ S3method(as_network,network) S3method(as_network,network.goldfish) S3method(as_network,siena) S3method(as_network,tbl_graph) +S3method(as_nodelist,tbl_graph) S3method(as_siena,igraph) S3method(as_siena,tbl_graph) S3method(as_tidygraph,data.frame) @@ -158,6 +159,8 @@ S3method(print,tie_measure) S3method(summary,diff_model) S3method(summary,diffs_model) S3method(summary,learn_model) +S3method(summary,network_measure) +S3method(summary,network_motif) S3method(summary,node_measure) S3method(summary,node_member) S3method(summary,node_motif) @@ -244,6 +247,11 @@ S3method(to_redirected,igraph) S3method(to_redirected,matrix) S3method(to_redirected,network) S3method(to_redirected,tbl_graph) +S3method(to_signed,data.frame) +S3method(to_signed,igraph) +S3method(to_signed,matrix) +S3method(to_signed,network) +S3method(to_signed,tbl_graph) S3method(to_simplex,igraph) S3method(to_simplex,matrix) S3method(to_simplex,tbl_graph) @@ -294,6 +302,9 @@ S3method(to_waves,data.frame) S3method(to_waves,diff_model) S3method(to_waves,igraph) S3method(to_waves,tbl_graph) +S3method(to_weighted,igraph) +S3method(to_weighted,network) +S3method(to_weighted,tbl_graph) export("%>%") export(.E) export(.G) @@ -312,6 +323,7 @@ export(as_graphAM) export(as_igraph) export(as_matrix) export(as_network) +export(as_nodelist) export(as_siena) export(as_tidygraph) export(autographd) @@ -319,7 +331,9 @@ export(autographr) export(autographs) export(bind_node_attributes) export(bind_ties) +export(clear_glossary) export(cluster_concor) +export(cluster_cosine) export(cluster_hierarchical) export(create_components) export(create_core) @@ -356,6 +370,7 @@ export(generate_utilities) export(ggplot) export(ggsave) export(ggtitle) +export(gloss) export(graphr) export(graphs) export(grapht) @@ -391,12 +406,16 @@ export(labs) export(layout_tbl_graph_alluvial) export(layout_tbl_graph_concentric) export(layout_tbl_graph_configuration) +export(layout_tbl_graph_dyad) +export(layout_tbl_graph_hexad) export(layout_tbl_graph_hierarchy) export(layout_tbl_graph_ladder) export(layout_tbl_graph_lineage) export(layout_tbl_graph_multilevel) +export(layout_tbl_graph_pentad) export(layout_tbl_graph_quad) export(layout_tbl_graph_railway) +export(layout_tbl_graph_tetrad) export(layout_tbl_graph_triad) export(many_palettes) export(mutate) @@ -412,6 +431,7 @@ export(net_by_brokerage) export(net_by_dyad) export(net_by_mixed) export(net_by_quad) +export(net_by_tetrad) export(net_by_triad) export(net_change) export(net_closeness) @@ -528,6 +548,7 @@ export(node_by_dyad) export(node_by_exposure) export(node_by_path) export(node_by_quad) +export(node_by_tetrad) export(node_by_tie) export(node_by_triad) export(node_closeness) @@ -558,6 +579,7 @@ export(node_in_adopter) export(node_in_automorphic) export(node_in_betweenness) export(node_in_brokering) +export(node_in_community) export(node_in_component) export(node_in_eigen) export(node_in_equivalence) @@ -591,6 +613,8 @@ export(node_is_max) export(node_is_mentor) export(node_is_min) export(node_is_mode) +export(node_is_neighbor) +export(node_is_pendant) export(node_is_random) export(node_is_recovered) export(node_kernighanlin) @@ -624,6 +648,7 @@ export(node_thresholds) export(node_tie_census) export(node_transitivity) export(node_triad_census) +export(node_vitality) export(node_walktrap) export(node_weak_components) export(over_time) @@ -633,6 +658,7 @@ export(play_diffusion) export(play_diffusions) export(play_learning) export(play_segregation) +export(print_glossary) export(read_cran) export(read_dynetml) export(read_edgelist) @@ -695,6 +721,7 @@ export(tie_is_bridge) export(tie_is_cyclical) export(tie_is_feedback) export(tie_is_forbidden) +export(tie_is_imbalanced) export(tie_is_loop) export(tie_is_max) export(tie_is_min) @@ -713,12 +740,12 @@ export(to_anti) export(to_blocks) export(to_components) export(to_correlation) +export(to_cosine) export(to_directed) export(to_dominating) export(to_ego) export(to_egos) export(to_eulerian) -export(to_galois) export(to_giant) export(to_matching) export(to_mentoring) @@ -731,6 +758,7 @@ export(to_onemode) export(to_permuted) export(to_reciprocated) export(to_redirected) +export(to_signed) export(to_simplex) export(to_slices) export(to_subgraph) @@ -744,6 +772,7 @@ export(to_unnamed) export(to_unsigned) export(to_unweighted) export(to_waves) +export(to_weighted) export(with_graph) export(write_edgelist) export(write_graphml) diff --git a/NEWS.md b/NEWS.md index e4da3e59..5acb9e7a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,94 @@ +# manynet 1.3.0 + +## Package + +- Improved user information in the console + - manynet cli functions now inherit parent frame + - Added manynet cli functions for success and progress along, seq, and nodes +- Improved testing architecture + - Moving to nested testthats + - Added custom testthat function for expecting values and ignoring dimension names + +## Making + +- Added some names to created networks (`create_ego()`, `create_empty()`, +`create_filled()`, `create_ring()`, `create_star()`, `create_lattice()`) + +## Modifying + +- Fixed how `as_matrix()` handles signed networks +- Added `as_nodelist()` for extracting nodelists from networks into tibbles +- Added `to_cosine()` +- Dropped `to_galois()` until it can be refactored +- Split reformatting documentation into format, reformat, and deformat groups of functions + - Added `to_signed()` for adding signs to networks + - Added `to_weighted()` for adding weights to networks + +## Mapping + +- Fixed default color ordering so that red is the highlight +- Fixed bug in `graphr()` where line types were inferred incorrectly +- Improved `graphr()` so that layouts can now be `snap`ped to a grid, +mileage may vary +- Improved theme handling so that it is set globally (WIP) + - Added highlight themes + - Added background themes + - Added categorical themes +- Improved configurational layouts + - Added dyad, pentad, and hexad layouts to configurational layouts + - Renamed quad layout to tetrad layout + +## Marking + +- Added `node_is_pendant()` for identifying pendant nodes +- Added `node_is_neighbor()` for identifying adjacent nodes +- Added `tie_is_imbalanced()` for identifying ties in imbalanced configurations + +## Measuring + +- Added `summary.network_measure()` to return z-scores and p-values for measures +- Added `node_vitality()` for measuring closeness vitality centrality +- Fixed #98 by dropping scale and normalization for `node_eigenvector()` + +## Memberships + +- Improved community detection options for new users + - Community detection algorithms now reformat networks as necessary or suggest that it be used on only the giant component + - Added `node_in_community()` which runs through most salient community detection algorithms to find and return the one with the highest modularity + - Updated documentation on resolution parameters +- Improved `node_in_regular()` to inform user which census is being used +- Renamed `node_by_quad()` to `node_by_tetrad()` to be more consistent with Greek origins + - Restored and updated documentation about the various configurations +- Added `summary.network_motif()` which returns the z-scores for the motif scores based on random or configurational networks, traces progress +- Fixed bug in `plot.network_motif()` where motif names were not identified correctly, internal make_network_motif now inherits call information + +## Modelling + +- Added `cluster_cosine()` for another equivalence option +- Added internal documentation for depth_first_recursive_search + +## Practicing + +- Improved how `run_tute()` fuzzy matched so that insertions are not as costly +- Improved tutorials with glossary architecture + - Added `gloss()`, `clear_glossary()`, and `print_glossary()` for adding glossaries to tutorials +- Updated tutorials + - Updated community, position, and topology tutorials with glossaries, free play sections, and gifs + - Fixed miscellaneous issues in these tutorials + - Added faction section to community tutorial + +## Data + +- Added `irps_wwi`, a dynamic, signed network +- Renamed `ison_blogs` to `irps_blogs`, added info +- Renamed `ison_books` to `irps_books`, added info +- Renamed `ison_usstates` to `irps_usgeo`, added info +- Renamed `ison_friends` to `fict_friends`, added info and fixed directed issue +- Renamed `ison_greys` to `fict_greys`, added info +- Renamed `ison_lotr` to `fict_lotr`, added info +- Renamed `ison_thrones` to `fict_thrones`, added info and some additional nodal attributes +- Renamed `ison_potter` to `fict_potter`, added info and combined waves into single object + # manynet 1.2.6 ## Package diff --git a/R/class_measures.R b/R/class_measures.R index de450dcc..eef7e93b 100644 --- a/R/class_measures.R +++ b/R/class_measures.R @@ -24,6 +24,7 @@ make_tie_measure <- function(out, .data) { make_network_measure <- function(out, .data) { class(out) <- c("network_measure", class(out)) attr(out, "mode") <- net_dims(.data) + attr(out, "call") <- deparse(sys.calls()) out } @@ -101,6 +102,30 @@ summary.node_measure <- function(object, ..., out } +#' @export +summary.network_measure <- function(object, ..., + null = c("random","configuration"), + times = 500) { + null <- paste0("generate_", match.arg(null)) + callItems <- trimws(strsplit(unlist(attr(object, "call")), + split = "\\(|\\)|,")[[1]]) + idFun <- which(grepl("^net_", callItems))[1] + fun <- callItems[idFun] + dat <- callItems[idFun+1] + nulls <- vapply(mnet_progress_seq(times), function(r){ + suppressMessages(get(fun)(get(null)(get(dat)))) + }, FUN.VALUE = numeric(1)) + out <- (object - mean(nulls))/stats::sd(nulls) + out[is.nan(out)] <- 0 + p <- 2 * stats::pnorm(out, + mean = mean(nulls), sd = stats::sd(nulls), + lower.tail = ifelse(out>0, FALSE, TRUE)) + cli::cli_text(cli::style_bold(round(object,3)), + " (z = ", cli::style_italic(round(out,2)), + ", p = ", cli::style_italic(round(p,3)), + ")") +} + # Plotting #### #' @export plot.node_measure <- function(x, type = c("h", "d"), ...) { diff --git a/R/class_motifs.R b/R/class_motifs.R index 12e68465..5d0bf84a 100644 --- a/R/class_motifs.R +++ b/R/class_motifs.R @@ -8,6 +8,7 @@ make_node_motif <- function(out, .data) { make_network_motif <- function(out, .data) { class(out) <- c("network_motif", class(out)) attr(out, "mode") <- net_dims(.data) + attr(out, "call") <- deparse(sys.calls()) out } @@ -50,7 +51,7 @@ plot.node_motif <- function(x, ...) { #' @export plot.network_motif <- function(x, ...) { - motifs <- dimnames(x)[[2]] + motifs <- attr(x, "names") if("X4" %in% motifs){ graphs(create_motifs(4), waves = 1:11) } else if("021D" %in% motifs){ @@ -87,3 +88,23 @@ print.network_motif <- function(x, ...) { out <- as.data.frame(mat) print(dplyr::tibble(out)) } + +#' @export +summary.network_motif <- function(object, ..., + null = c("random","configuration"), + times = 500) { + null <- paste0("generate_", match.arg(null)) + callItems <- trimws(strsplit(unlist(attr(object, "call")), + split = "\\(|\\)|,")[[1]]) + idFun <- which(grepl("net_by_", callItems))[1] + fun <- callItems[idFun] + dat <- callItems[idFun+1] + nulls <- t(vapply(mnet_progress_seq(times), function(r){ + suppressMessages(get(fun)(get(null)(get(dat)))) + }, FUN.VALUE = numeric(length(object)))) + out <- (object - colMeans(nulls))/apply(nulls, 2, stats::sd) + out[is.nan(out)] <- 0 + out +} + + diff --git a/R/data_ison.R b/R/data_ison.R index 9bfe0bb7..7af77cc0 100644 --- a/R/data_ison.R +++ b/R/data_ison.R @@ -284,33 +284,6 @@ #' ``` "ison_physicians" -## US States #### - -#' One-mode undirected network of US state contiguity (Meghanathan 2017) -#' -#' @description -#' This network is of contiguity between US states. -#' States that share a border are connected by a tie in the network. -#' The data is a network of 107 ties among 50 US states (nodes). -#' States are named by their two-letter ISO-3166 code. -#' This data includes also the names of the capitol cities of each state, -#' which are listed in the node attribute 'capitol'. -#' @docType data -#' @keywords datasets -#' @name ison_usstates -#' @usage data(ison_usstates) -#' @references -#' Meghanathan, Natarajan. 2017. -#' "Complex network analysis of the contiguous United States graph." -#' _Computer and Information Science_, 10(1): 54-76. -#' \doi{10.5539/cis.v10n1p54} -#' @format -#' ```{r, echo = FALSE} -#' ison_usstates -#' ``` -"ison_usstates" - - ## High-tech #### #' One-mode multiplex, directed network of managers of a high-tech company (Krackhardt 1987) @@ -486,13 +459,13 @@ #' Interaction can be cooperative or conflictual. #' @docType data #' @keywords datasets -#' @name ison_lotr -#' @usage data(ison_lotr) +#' @name fict_lotr +#' @usage data(fict_lotr) #' @format #' ```{r, echo = FALSE} -#' ison_lotr +#' fict_lotr #' ``` -"ison_lotr" +"fict_lotr" ## Harry Potter #### @@ -511,8 +484,8 @@ #' gender, and their house assigned by the sorting hat are included. #' @docType data #' @keywords datasets -#' @name ison_potter -#' @usage data(ison_potter) +#' @name fict_potter +#' @usage data(fict_potter) #' @references #' Bossaert, Goele and Nadine Meidert (2013). #' "'We are only as strong as we are united, as weak as we are divided'. A dynamic analysis of the peer support networks in the Harry Potter books." @@ -520,30 +493,39 @@ #' \doi{10.4236/ojapps.2013.32024} #' @format #' ```{r, echo = FALSE} -#' ison_potter +#' fict_potter #' ``` -"ison_potter" +"fict_potter" ## Game of Thrones #### #' One-mode Game of Thrones kinship (Glander 2017) #' #' @description -#' Shirin Glander extended a data set on character deaths in the TV series Game of Thrones -#' with the kinship relationships between the characters, by scraping "A Wiki of Ice and Fire" -#' and adding missing information by hand. +#' The original dataset was put together by Erin Pierce and Ben Kahle for an +#' assignment for a course on Bayesian statistics. +#' The data included information on when characters died in the Song of Ice +#' and Fire books, +#' and some predictive factors such as whether they were nobles, married, etc. +#' Shirin Glander extended this data set on character deaths in the TV series +#' Game of Thrones with the kinship relationships between the characters, +#' by scraping "A Wiki of Ice and Fire" and adding missing information by hand. +#' There is certainly more that can be done here. #' @docType data #' @keywords datasets -#' @name ison_thrones -#' @usage data(ison_thrones) +#' @name fict_thrones +#' @usage data(fict_thrones) #' @references -#' Glander, Shirin (2017). +#' Pierce, Erin, and Ben Kahle. 2015. +#' "\href{http://allendowney.blogspot.com/2015/03/bayesian-survival-analysis-for-game-of.html}{Bayesian Survival Analysis in A Song of Ice and Fire}". +#' +#' Glander, Shirin. 2017. #' "\href{https://datascienceplus.com/network-analysis-of-game-of-thrones/}{Network analysis of Game of Thrones}". #' @format #' ```{r, echo = FALSE} -#' ison_thrones +#' fict_thrones #' ``` -"ison_thrones" +"fict_thrones" ## Star Wars #### @@ -584,33 +566,31 @@ ## Friends #### -#' One-mode Friends character connections (McNulty, 2020) +#' One-mode undirected Friends character scene co-appearances (McNulty, 2020) #' #' @description #' One-mode network collected by \href{https://github.com/keithmcnulty/friends_analysis/}{McNulty (2020)} #' on the connections between the Friends TV series characters #' from Seasons 1 to 10. -#' The `ison_friends` is a directed network +#' The `fict_friends` is an undirected network #' containing connections between characters organised by season number, #' which is reflected in the tie attribute 'wave'. #' The network contains 650 nodes #' Each tie represents the connection between a character pair (appear in the same scene), #' and the 'weight' of the tie is the number of scenes the character pair appears in together. #' For all networks, characters are named (eg. Phoebe, Ross, Rachel). -#' @details -#' The data contains both networks but each may be used separately. #' @docType data #' @keywords datasets -#' @name ison_friends -#' @usage data(ison_friends) +#' @name fict_friends +#' @usage data(fict_friends) #' @references #' McNulty, K. (2020). #' \emph{Network analysis of Friends scripts.}. #' @format #' ```{r, echo = FALSE} -#' ison_friends +#' fict_friends #' ``` -"ison_friends" +"fict_friends" ## Greys #### @@ -639,14 +619,14 @@ #' #' @docType data #' @keywords datasets -#' @name ison_greys +#' @name fict_greys #' @author Gary Weissman and Benjamin Lind -#' @usage data(ison_greys) +#' @usage data(fict_greys) #' @format #' ```{r, echo = FALSE} -#' ison_greys +#' fict_greys #' ``` -"ison_greys" +"fict_greys" # Political #### @@ -668,14 +648,14 @@ #' #' @docType data #' @keywords datasets -#' @name ison_books +#' @name irps_books #' @author Valdis Krebs, Mark Newman -#' @usage data(ison_books) +#' @usage data(irps_books) #' @format #' ```{r, echo = FALSE} -#' ison_books +#' irps_books #' ``` -"ison_books" +"irps_books" ## Blogs #### @@ -684,6 +664,7 @@ #' @description #' This network consists of the blogosphere around the time of the 2004 #' US presidential election until February 2005. +#' The 2004 election was the first in which blogging played a significant role. #' Ties were constructed from a crawl of the front page of each blog. #' #' Political leaning is indicated as "Liberal" (or left leaning) or @@ -692,14 +673,76 @@ #' based on incoming and outgoing links and posts. #' @docType data #' @keywords datasets -#' @name ison_blogs +#' @name irps_blogs +#' @references +#' Adamic, Lada, and Natalie Glance. 2005. +#' "The political blogosphere and the 2004 US Election: Divided they blog". +#' _LinkKDD '05: Proceedings of the 3rd international workshop on Link discovery_, 36-43. +#' \doi{10.1145/1134271.1134277} +#' @usage data(irps_blogs) +#' @format +#' ```{r, echo = FALSE} +#' irps_blogs +#' ``` +"irps_blogs" + +## WWI #### + +#' One-mode signed network of relationships between European major powers (Antal et al. 2006) +#' +#' @description +#' This network records the evolution of the major relationship changes +#' between the protagonists of World War I (WWI) from 1872 to 1907. +#' It is incomplete both in terms of (eventual) parties to the war as well +#' as some other relations, but gives a good overview of the main alliances +#' and enmities. +#' +#' The data series begins with the Three Emperors' League (1872, revived in 1881) +#' between Germany, Austria-Hungary, and Russia. +#' The Triple Alliance in 1882 joined Germany, Austria-Hungary, and Italy into +#' a bloc that lasted until WWI. +#' A bilateral alliance between Germany and Russia lapsed in 1890, +#' and a French-Russian alliance developed between 1891-1894. +#' The Entente Cordiale thawed and then fostered relations between Great Britain +#' and France in 1904, and a British-Russian agreement in 1907 bound +#' Great Britain, France, and Russia into the Triple Entente. +#' @docType data +#' @keywords datasets +#' @name irps_wwi #' @references -#' Adamic, Lada A., and Natalie Glance. 2005. -#' "The political blogosphere and the 2004 US Election", -#' _Proceedings of the WWW-2005 Workshop on the Weblogging Ecosystem_. -#' @usage data(ison_blogs) +#' Antal, Tibor, Pavel Krapivsky, and Sidney Redner. 2006. +#' "Social balance on networks: The dynamics of friendship and enmity". +#' _Physica D_ 224: 130-136. +#' \doi{10.1016/j.physd.2006.09.028} +#' @usage data(irps_wwi) #' @format #' ```{r, echo = FALSE} -#' ison_blogs +#' irps_wwi +#' ``` +"irps_wwi" + +## US States #### + +#' One-mode undirected network of US state contiguity (Meghanathan 2017) +#' +#' @description +#' This network is of contiguity between US states. +#' States that share a border are connected by a tie in the network. +#' The data is a network of 107 ties among 50 US states (nodes). +#' States are named by their two-letter ISO-3166 code. +#' This data includes also the names of the capitol cities of each state, +#' which are listed in the node attribute 'capitol'. +#' @docType data +#' @keywords datasets +#' @name irps_usgeo +#' @usage data(irps_usgeo) +#' @references +#' Meghanathan, Natarajan. 2017. +#' "Complex network analysis of the contiguous United States graph." +#' _Computer and Information Science_, 10(1): 54-76. +#' \doi{10.5539/cis.v10n1p54} +#' @format +#' ```{r, echo = FALSE} +#' irps_usgeo #' ``` -"ison_blogs" +"irps_usgeo" diff --git a/R/make_create.R b/R/make_create.R index fe7dbfd8..0c094006 100644 --- a/R/make_create.R +++ b/R/make_create.R @@ -200,7 +200,7 @@ create_ego <- function(max_alters = Inf, isolates <- roster[!roster %in% node_names(out)] out <- add_nodes(out, length(isolates), list(name = isolates)) } - out <- add_info(out, ties = ties, + out <- add_info(out, ties = ties, name = "Ego network", collection = "Interview", year = format(as.Date(Sys.Date(), format="%d/%m/%Y"),"%Y")) out @@ -363,7 +363,8 @@ create_empty <- function(n, directed = FALSE) { out <- as_igraph(out, twomode = TRUE) } if (!directed) out <- to_undirected(out) - as_tidygraph(out) + as_tidygraph(out) %>% + add_info(name = "Empty network") } #' @rdname make_create @@ -382,7 +383,8 @@ create_filled <- function(n, directed = FALSE) { out <- matrix(1, n[1], n[2]) out <- as_igraph(out, twomode = TRUE) } - as_tidygraph(out) + as_tidygraph(out) %>% + add_info(name = "Filled network") } #' @rdname make_create @@ -430,7 +432,8 @@ create_ring <- function(n, directed = FALSE, width = 1, ...) { mat[mat > 1] <- 1 out <- as_igraph(mat, twomode = TRUE) } - as_tidygraph(out) + as_tidygraph(out) %>% + add_info(name = "Ring network") } #' @rdname make_create @@ -454,7 +457,8 @@ create_star <- function(n, } out <- as_igraph(out, twomode = TRUE) } - as_tidygraph(out) + as_tidygraph(out) %>% + add_info(name = "Star network") } #' @rdname make_create @@ -548,11 +552,14 @@ create_lattice <- function(n, } if (!directed) nei1.5[lower.tri(nei1.5)] <- t(nei1.5)[lower.tri(nei1.5)] - as_tidygraph(nei1.5) + as_tidygraph(nei1.5) %>% + add_info(name = "Lattice network") } else if (width == 12) { - as_tidygraph(igraph::make_lattice(dims, nei = 2, directed = directed)) + as_tidygraph(igraph::make_lattice(dims, nei = 2, directed = directed)) %>% + add_info(name = "Lattice network") } else if (width == 4) { - as_tidygraph(igraph::make_lattice(dims, nei = 1, directed = directed)) + as_tidygraph(igraph::make_lattice(dims, nei = 1, directed = directed)) %>% + add_info(name = "Lattice network") } else cli::cli_abort("`max_neighbourhood` expected to be 4, 8, or 12") } else { divs1 <- divisors(n[1]) @@ -570,7 +577,8 @@ create_lattice <- function(n, mat[lower.tri(mat)] <- 0 out <- mat[rowSums(mat) ==2,] out <- do.call(rbind, replicate(nrow(mat)/nrow(out), out, simplify=FALSE)) - as_tidygraph(out) + as_tidygraph(out) %>% + add_info(name = "Lattice network") } } diff --git a/R/manip_as.R b/R/manip_as.R index 5550c5ff..fab96236 100644 --- a/R/manip_as.R +++ b/R/manip_as.R @@ -61,6 +61,18 @@ #' ``` NULL +# Nodelists #### + +#' @rdname manip_as +#' @export +as_nodelist <- function(.data) UseMethod("as_nodelist") + +#' @export +as_nodelist.tbl_graph <- function(.data) { + out <- .data + dplyr::tibble(data.frame(out)) +} + # Edgelists #### #' @rdname manip_as @@ -203,7 +215,8 @@ as_matrix.igraph <- function(.data, if ((!is.null(twomode) && twomode) | (is.null(twomode) & is_twomode(.data))) { if (is_weighted(.data) | is_signed(.data)) { mat <- igraph::as_biadjacency_matrix(.data, sparse = FALSE, - attr = ifelse(is_weighted(.data), "weight", NULL)) + attr = ifelse(is_weighted(.data), "weight", + ifelse(is_signed(.data), "sign", NULL))) } else { mat <- igraph::as_biadjacency_matrix(.data, sparse = FALSE, attr = NULL) @@ -211,7 +224,8 @@ as_matrix.igraph <- function(.data, } else { if (is_weighted(.data) | is_signed(.data)) { mat <- igraph::as_adjacency_matrix(.data, sparse = FALSE, - attr = ifelse(is_weighted(.data), "weight", NULL)) + attr = ifelse(is_weighted(.data), "weight", + ifelse(is_signed(.data), "sign", NULL))) } else { mat <- igraph::as_adjacency_matrix(.data, sparse = FALSE, attr = NULL) diff --git a/R/manip_correlation.R b/R/manip_correlation.R index ff4e3bf5..6ae65023 100644 --- a/R/manip_correlation.R +++ b/R/manip_correlation.R @@ -21,6 +21,9 @@ #' and "complex" compares pairs' reciprocal ties and their self ties. #' By default the appropriate method is chosen based on the network format. #' @family modifications +NULL + +#' @rdname manip_correlation #' @export to_correlation <- function(.data, method = NULL){ if(missing(.data)) {expect_nodes(); .data <- .G()} @@ -38,6 +41,23 @@ to_correlation <- function(.data, method = NULL){ diag = .corDiag(mat)) out } + +#' @rdname manip_correlation +#' @export +to_cosine <- function(.data){ + x <- as_matrix(.data) + co = array(0, c(ncol(x), ncol(x))) + f = colnames(x) + dimnames(co) = list(f, f) + for (i in 2:ncol(x)) { + for (j in 1:(i - 1)) { + co[i, j] = crossprod(x[, i], x[, j])/sqrt(crossprod(x[, i]) * crossprod(x[, j])) + } + } + co = co + t(co) + diag(co) = 1 + as.matrix(co) +} #' Network permutation #' diff --git a/R/manip_reformat.R b/R/manip_format.R similarity index 73% rename from R/manip_reformat.R rename to R/manip_format.R index b910ad38..b3d4d5b3 100644 --- a/R/manip_reformat.R +++ b/R/manip_format.R @@ -1,23 +1,21 @@ -# Reformatting #### +# Deformatting #### #' Modifying network formats #' #' @description #' These functions reformat manynet-consistent data. #' -#' - `to_uniplex()` reformats multiplex network data to a single type of tie. -#' - `to_undirected()` reformats directed network data to an undirected network. -#' - `to_directed()` reformats undirected network data to a directed network. -#' - `to_redirected()` reformats the direction of directed network data, flipping any existing direction. -#' - `to_reciprocated()` reformats directed network data such that every directed tie is reciprocated. -#' - `to_acyclic()` reformats network data to an acyclic graph. -#' - `to_unweighted()` reformats weighted network data to unweighted network data. -#' - `to_unsigned()` reformats signed network data to unsigned network data. #' - `to_unnamed()` reformats labelled network data to unlabelled network data. -#' - `to_named()` reformats unlabelled network data to labelled network data. +#' - `to_undirected()` reformats directed network data to an undirected network, +#' so that any pair of nodes with at least one directed edge will be +#' connected by an undirected edge in the new network. +#' This is equivalent to the "collapse" mode in `{igraph}`.. +#' - `to_unweighted()` reformats weighted network data to unweighted network +#' data, with all tie weights removed. +#' - `to_unsigned()` reformats signed network data to unsigned network data +#' keeping just the "positive" or "negative" ties. #' - `to_simplex()` reformats complex network data, containing loops, to simplex network data, without any loops. -#' - `to_anti()` reformats network data into its complement, where only ties _not_ present in the original network -#' are included in the new network. +#' - `to_uniplex()` reformats multiplex network data to a single type of tie. #' #' If the format condition is not met, #' for example `to_undirected()` is used on a network that is already undirected, @@ -32,68 +30,66 @@ #' Below are the currently implemented S3 methods: #' #' ```{r, echo = FALSE, cache = TRUE} -#' knitr::kable(available_methods(c("to_uniplex", "to_undirected", "to_directed", "to_redirected", -#' "to_reciprocated", "to_acyclic", "to_unweighted", "to_unsigned", "to_unnamed", "to_named", -#' "to_simplex"))) +#' knitr::kable(available_methods(c("to_undirected", "to_unweighted", +#' "to_unsigned", "to_unnamed", "to_simplex", "to_uniplex"))) #' ``` -#' @name manip_reformat -#' @family modifications #' @inheritParams mark_is -#' @param tie Character string naming a tie attribute to retain from a graph. -#' @param keep In the case of a signed network, whether to retain -#' the "positive" or "negative" ties. #' @param threshold For a matrix, the threshold to binarise/dichotomise at. -#' @param names Character vector of the node names. NULL by default. #' @returns #' All `to_` functions return an object of the same class as that provided. #' So passing it an igraph object will return an igraph object #' and passing it a network object will return a network object, #' with certain modifications as outlined for each function. +#' @name manip_deformat +#' @family modifications NULL - -#' @rdname manip_reformat -#' @importFrom igraph delete_edges edge_attr_names delete_edge_attr -#' E edge_attr_names -#' @examples -#' as_tidygraph(create_filled(5)) %>% -#' mutate_ties(type = sample(c("friend", "enemy"), 10, replace = TRUE)) %>% -#' to_uniplex("friend") +#' @rdname manip_deformat +#' @importFrom igraph delete_vertex_attr +#' @importFrom tidygraph as_tbl_graph +#' @importFrom network delete.vertex.attribute +#' @importFrom dplyr as_tibble #' @export -to_uniplex <- function(.data, tie) UseMethod("to_uniplex") +to_unnamed <- function(.data) UseMethod("to_unnamed") #' @export -to_uniplex.tbl_graph <- function(.data, tie){ - type <- NULL - out <- dplyr::filter(.data = tidygraph::activate(.data, "edges"), - type == tie) %>% dplyr::select(-type) - tidygraph::activate(out, "nodes") +to_unnamed.igraph <- function(.data) { + if ("name" %in% igraph::vertex_attr_names(.data)) { + igraph::delete_vertex_attr(.data, "name") + } else .data } #' @export -to_uniplex.igraph <- function(.data, tie){ - as_igraph(to_uniplex(as_tidygraph(.data), tie)) +to_unnamed.tbl_graph <- function(.data) { + if ("name" %in% igraph::vertex_attr_names(.data)) { + as_tidygraph(igraph::delete_vertex_attr(.data, "name")) + } else .data } #' @export -to_uniplex.network <- function(.data, tie){ - as_network(to_uniplex(as_igraph(.data), tie)) +to_unnamed.network <- function(.data) { + out <- network::delete.vertex.attribute(.data, "vertex.names") + out } #' @export -to_uniplex.data.frame <- function(.data, tie){ - as_edgelist(to_uniplex(as_igraph(.data), tie)) +to_unnamed.matrix <- function(.data) { + out <- .data + rownames(out) <- NULL + colnames(out) <- NULL + out } #' @export -to_uniplex.matrix <- function(.data, tie){ - as_matrix(to_uniplex(as_igraph(.data), tie)) +to_unnamed.data.frame <- function(.data) { + out <- .data + names <- unique(unlist(c(out[,1],out[,2]))) + out[,1] <- match(unlist(.data[,1]), names) + out[,2] <- match(unlist(.data[,2]), names) + dplyr::as_tibble(out) } -#' @describeIn manip_reformat Returns an object that has any edge direction removed, -#' so that any pair of nodes with at least one directed edge will be -#' connected by an undirected edge in the new network. -#' This is equivalent to the "collapse" mode in `{igraph}`. +#' @rdname manip_deformat #' @export to_undirected <- function(.data) UseMethod("to_undirected") @@ -126,104 +122,208 @@ to_undirected.data.frame <- function(.data) { as_edgelist(to_undirected(as_igraph(.data))) } -#' @rdname manip_reformat -#' @importFrom igraph as.directed +#' @rdname manip_deformat +#' @importFrom dplyr filter select #' @export -to_directed <- function(.data) UseMethod("to_directed") +to_unweighted <- function(.data, threshold = 1) UseMethod("to_unweighted") #' @export -to_directed.igraph <- function(.data) { - if(!is_directed.igraph(.data)) - igraph::as.directed(.data, mode = "random") - else .data +to_unweighted.tbl_graph <- function(.data, threshold = 1) { + if(is_weighted(.data)){ + edges <- weight <- NULL + .data %>% activate(edges) %>% + dplyr::filter(weight >= threshold) %>% + dplyr::select(-c(weight)) + } else .data } #' @export -to_directed.tbl_graph <- function(.data) { - as_tidygraph(to_directed(as_igraph(.data))) +to_unweighted.igraph <- function(.data, threshold = 1) { + as_igraph(to_unweighted(as_tidygraph(.data), threshold)) } #' @export -to_directed.matrix <- function(.data) { - as_matrix(to_directed(as_igraph(.data))) +to_unweighted.network <- function(.data, threshold = 1) { + as_network(to_unweighted(as_tidygraph(.data), threshold)) } #' @export -to_directed.network <- function(.data) { - as_network(to_directed(as_igraph(.data))) +to_unweighted.matrix <- function(.data, threshold = 1) { + (.data >= threshold)*1 } #' @export -to_directed.data.frame <- function(.data) { - as_edgelist(to_directed(as_igraph(.data))) +to_unweighted.data.frame <- function(.data, threshold = 1) { + if(is_edgelist(.data)) .data[,1:2] + else cli::cli_abort("Not an edgelist") } -#' @describeIn manip_reformat Returns an object that has any edge direction transposed, -#' or flipped, so that senders become receivers and receivers become senders. -#' This essentially has no effect on undirected networks or reciprocated ties. -#' @importFrom igraph reverse_edges -#' @importFrom tidygraph reroute +#' @rdname manip_deformat +#' @param keep In the case of a signed network, whether to retain +#' the "positive" or "negative" ties. +#' @importFrom igraph delete_edges E delete_edge_attr #' @export -to_redirected <- function(.data) UseMethod("to_redirected") +to_unsigned <- function(.data, + keep = c("positive", "negative")) UseMethod("to_unsigned") #' @export -to_redirected.tbl_graph <- function(.data) { - as_tidygraph(to_redirected.igraph(.data)) +to_unsigned.matrix <- function(.data, + keep = c("positive", "negative")){ + keep <- match.arg(keep) + out <- .data + if(keep == "positive"){ + out[out < 0] <- 0 + } else if (keep == "negative"){ + out[out > 0] <- 0 + out <- abs(out) + } else cli::cli_abort("Indicate whether 'positive' or 'negative' ties should be kept.") + out } #' @export -to_redirected.igraph <- function(.data) { - igraph::reverse_edges(.data) +to_unsigned.data.frame <- function(.data, + keep = c("positive", "negative")){ + keep <- match.arg(keep) + out <- .data + if(is_signed(.data)){ + if(keep == "positive"){ + out$sign[out$sign < 0] <- 0 + } else if (keep == "negative"){ + out$sign[out$sign > 0] <- 0 + out$sign <- out$sign(out) + } else cli::cli_abort("Indicate whether 'positive' or 'negative' ties should be kept.") + } + out } #' @export -to_redirected.data.frame <- function(.data) { - out <- .data - out$from <- .data$to - out$to <- .data$from - out +to_unsigned.tbl_graph <- function(.data, + keep = c("positive", "negative")){ + keep <- match.arg(keep) + out <- to_unsigned(as_igraph(.data), keep = keep) + as_tidygraph(out) } #' @export -to_redirected.matrix <- function(.data) { - t(.data) +to_unsigned.igraph <- function(.data, + keep = c("positive", "negative")){ + if (is_signed(.data)) { + keep <- match.arg(keep) + if (keep == "positive") { + out <- igraph::delete_edges(.data, + which(igraph::E(.data)$sign < 0)) + } else { + out <- igraph::delete_edges(.data, + which(igraph::E(.data)$sign > 0)) + } + out <- igraph::delete_edge_attr(out, "sign") + out + } else .data } #' @export -to_redirected.network <- function(.data) { - as_network(to_redirected(as_igraph(.data))) +to_unsigned.network <- function(.data, + keep = c("positive", "negative")){ + as_network(to_unsigned(as_igraph(.data))) } -#' @describeIn manip_reformat Returns an object where all ties are reciprocated. -#' @importFrom igraph as.directed +#' @rdname manip_deformat +#' @importFrom igraph simplify #' @export -to_reciprocated <- function(.data) UseMethod("to_reciprocated") +to_simplex <- function(.data) UseMethod("to_simplex") #' @export -to_reciprocated.igraph <- function(.data) { - igraph::as.directed(.data, mode = "mutual") +to_simplex.tbl_graph <- function(.data) { + as_tidygraph(to_simplex(as_igraph(.data))) } #' @export -to_reciprocated.tbl_graph <- function(.data) { - as_tidygraph(to_reciprocated(as_igraph(.data))) +to_simplex.igraph <- function(.data) { + igraph::simplify(.data) } #' @export -to_reciprocated.matrix <- function(.data) { - .data + t(.data) +to_simplex.matrix <- function(.data) { + out <- .data + diag(out) <- 0 + out } +#' @rdname manip_deformat +#' @param tie Character string naming a tie attribute to retain from a graph. +#' @importFrom igraph delete_edges edge_attr_names delete_edge_attr +#' E edge_attr_names +#' @examples +#' as_tidygraph(create_filled(5)) %>% +#' mutate_ties(type = sample(c("friend", "enemy"), 10, replace = TRUE)) %>% +#' to_uniplex("friend") #' @export -to_reciprocated.network <- function(.data) { - as_network(to_reciprocated(as_igraph(.data))) +to_uniplex <- function(.data, tie) UseMethod("to_uniplex") + +#' @export +to_uniplex.tbl_graph <- function(.data, tie){ + type <- NULL + out <- dplyr::filter(.data = tidygraph::activate(.data, "edges"), + type == tie) %>% dplyr::select(-type) + if(is_signed(out) && all(tie_signs(out)==1)) out <- out %>% dplyr::select(-sign) + if(is_weighted(out) && all(tie_weights(out)==1)) out <- out %>% dplyr::select(-weight) + if(is_longitudinal(out) && length(unique(tie_attribute(out, "wave")))==1) out <- out %>% dplyr::select(-wave) + tidygraph::activate(out, "nodes") } #' @export -to_reciprocated.data.frame <- function(.data) { - as_edgelist(to_reciprocated(as_igraph(.data))) +to_uniplex.igraph <- function(.data, tie){ + as_igraph(to_uniplex(as_tidygraph(.data), tie)) +} + +#' @export +to_uniplex.network <- function(.data, tie){ + as_network(to_uniplex(as_igraph(.data), tie)) +} + +#' @export +to_uniplex.data.frame <- function(.data, tie){ + as_edgelist(to_uniplex(as_igraph(.data), tie)) +} + +#' @export +to_uniplex.matrix <- function(.data, tie){ + as_matrix(to_uniplex(as_igraph(.data), tie)) } +# Reformatting #### + +#' Modifying network formats +#' +#' @description +#' These functions reformat manynet-consistent data. +#' +#' - `to_acyclic()` reformats network data to an acyclic graph. +#' - `to_anti()` reformats network data into its complement, where only ties _not_ present in the original network +#' are included in the new network. +#' - `to_redirected()` reformats the direction of directed network data, flipping any existing direction. +#' - `to_reciprocated()` reformats directed network data such that every directed tie is reciprocated. +#' +#' Unlike the `as_*()` group of functions, +#' these functions always return the same class as they are given, +#' only transforming these objects' properties. +#' @details +#' Not all functions have methods available for all object classes. +#' Below are the currently implemented S3 methods: +#' +#' ```{r, echo = FALSE, cache = TRUE} +#' knitr::kable(available_methods(c("to_acyclic", "to_anti", "to_redirected", "to_reciprocated"))) +#' ``` +#' @name manip_reformat +#' @family modifications +#' @inheritParams mark_is +#' @returns +#' All `to_` functions return an object of the same class as that provided. +#' So passing it an igraph object will return an igraph object +#' and passing it a network object will return a network object, +#' with certain modifications as outlined for each function. +NULL + #' @rdname manip_reformat #' @importFrom igraph as.directed feedback_arc_set #' @export @@ -256,156 +356,160 @@ to_acyclic.network <- function(.data) { as_network(to_acyclic(as_igraph(.data))) } -#' @describeIn manip_reformat Returns an object that has all edge weights removed. -#' @importFrom dplyr filter select +#' @rdname manip_reformat +#' @importFrom igraph complementer +#' @examples +#' to_anti(ison_southern_women) +#' #graphr(to_anti(ison_southern_women)) #' @export -to_unweighted <- function(.data, threshold = 1) UseMethod("to_unweighted") +to_anti <- function(.data) UseMethod("to_anti") #' @export -to_unweighted.tbl_graph <- function(.data, threshold = 1) { - if(is_weighted(.data)){ - edges <- weight <- NULL - .data %>% activate(edges) %>% - dplyr::filter(weight >= threshold) %>% - dplyr::select(-c(weight)) - } else .data +to_anti.matrix <- function(.data){ + matrix(1, nrow(.data), ncol(.data)) - .data } #' @export -to_unweighted.igraph <- function(.data, threshold = 1) { - as_igraph(to_unweighted(as_tidygraph(.data), threshold)) +to_anti.data.frame <- function(.data){ + as_edgelist.matrix(to_anti.matrix(as_matrix(.data))) } #' @export -to_unweighted.network <- function(.data, threshold = 1) { - as_network(to_unweighted(as_tidygraph(.data), threshold)) +to_anti.igraph <- function(.data){ + if(is_twomode(.data)){ + as_igraph(to_anti.matrix(as_matrix(.data))) + } else { + igraph::complementer(as_igraph(.data), + loops = is_complex(.data)) + } } #' @export -to_unweighted.matrix <- function(.data, threshold = 1) { - (.data >= threshold)*1 +to_anti.tbl_graph <- function(.data){ + if(is_twomode(.data)){ + as_tidygraph(to_anti.matrix(as_matrix(.data))) + } else { + as_tidygraph(igraph::complementer(as_igraph(.data), + loops = is_complex(.data))) + } } #' @export -to_unweighted.data.frame <- function(.data, threshold = 1) { - if(is_edgelist(.data)) .data[,1:2] - else cli::cli_abort("Not an edgelist") +to_anti.network <- function(.data){ + as_network(to_anti(as_igraph(.data))) } -#' @describeIn manip_reformat Returns a network with either just the "positive" ties -#' or just the "negative" ties -#' @importFrom igraph delete_edges E delete_edge_attr +#' @describeIn manip_reformat Returns an object that has any edge direction transposed, +#' or flipped, so that senders become receivers and receivers become senders. +#' This essentially has no effect on undirected networks or reciprocated ties. +#' @importFrom igraph reverse_edges +#' @importFrom tidygraph reroute #' @export -to_unsigned <- function(.data, - keep = c("positive", "negative")) UseMethod("to_unsigned") +to_redirected <- function(.data) UseMethod("to_redirected") #' @export -to_unsigned.matrix <- function(.data, - keep = c("positive", "negative")){ - keep <- match.arg(keep) - out <- .data - if(keep == "positive"){ - out[out < 0] <- 0 - } else if (keep == "negative"){ - out[out > 0] <- 0 - out <- abs(out) - } else cli::cli_abort("Indicate whether 'positive' or 'negative' ties should be kept.") - out +to_redirected.tbl_graph <- function(.data) { + as_tidygraph(to_redirected.igraph(.data)) } #' @export -to_unsigned.data.frame <- function(.data, - keep = c("positive", "negative")){ - keep <- match.arg(keep) - out <- .data - if(is_signed(.data)){ - if(keep == "positive"){ - out$sign[out$sign < 0] <- 0 - } else if (keep == "negative"){ - out$sign[out$sign > 0] <- 0 - out$sign <- out$sign(out) - } else cli::cli_abort("Indicate whether 'positive' or 'negative' ties should be kept.") - } - out +to_redirected.igraph <- function(.data) { + igraph::reverse_edges(.data) } #' @export -to_unsigned.tbl_graph <- function(.data, - keep = c("positive", "negative")){ - keep <- match.arg(keep) - out <- to_unsigned(as_igraph(.data), keep = keep) - as_tidygraph(out) +to_redirected.data.frame <- function(.data) { + out <- .data + out$from <- .data$to + out$to <- .data$from + out } #' @export -to_unsigned.igraph <- function(.data, - keep = c("positive", "negative")){ - if (is_signed(.data)) { - keep <- match.arg(keep) - if (keep == "positive") { - out <- igraph::delete_edges(.data, - which(igraph::E(.data)$sign < 0)) - } else { - out <- igraph::delete_edges(.data, - which(igraph::E(.data)$sign > 0)) - } - out <- igraph::delete_edge_attr(out, "sign") - out - } else .data +to_redirected.matrix <- function(.data) { + t(.data) } #' @export -to_unsigned.network <- function(.data, - keep = c("positive", "negative")){ - as_network(to_unsigned(as_igraph(.data))) +to_redirected.network <- function(.data) { + as_network(to_redirected(as_igraph(.data))) } -#' @describeIn manip_reformat Returns an object with all vertex names removed -#' @importFrom igraph delete_vertex_attr -#' @importFrom tidygraph as_tbl_graph -#' @importFrom network delete.vertex.attribute -#' @importFrom dplyr as_tibble +#' @describeIn manip_reformat Returns an object where all ties are reciprocated. +#' @importFrom igraph as.directed #' @export -to_unnamed <- function(.data) UseMethod("to_unnamed") +to_reciprocated <- function(.data) UseMethod("to_reciprocated") #' @export -to_unnamed.igraph <- function(.data) { - if ("name" %in% igraph::vertex_attr_names(.data)) { - igraph::delete_vertex_attr(.data, "name") - } else .data +to_reciprocated.igraph <- function(.data) { + igraph::as.directed(.data, mode = "mutual") } #' @export -to_unnamed.tbl_graph <- function(.data) { - if ("name" %in% igraph::vertex_attr_names(.data)) { - as_tidygraph(igraph::delete_vertex_attr(.data, "name")) - } else .data +to_reciprocated.tbl_graph <- function(.data) { + as_tidygraph(to_reciprocated(as_igraph(.data))) } #' @export -to_unnamed.network <- function(.data) { - out <- network::delete.vertex.attribute(.data, "vertex.names") - out +to_reciprocated.matrix <- function(.data) { + .data + t(.data) } #' @export -to_unnamed.matrix <- function(.data) { - out <- .data - rownames(out) <- NULL - colnames(out) <- NULL - out +to_reciprocated.network <- function(.data) { + as_network(to_reciprocated(as_igraph(.data))) } #' @export -to_unnamed.data.frame <- function(.data) { - out <- .data - names <- unique(unlist(c(out[,1],out[,2]))) - out[,1] <- match(unlist(.data[,1]), names) - out[,2] <- match(unlist(.data[,2]), names) - dplyr::as_tibble(out) +to_reciprocated.data.frame <- function(.data) { + as_edgelist(to_reciprocated(as_igraph(.data))) } -#' @describeIn manip_reformat Returns an object that has random vertex names added +# Formatting #### + +#' Modifying network formats +#' +#' @description +#' These functions add some format to manynet-consistent data. +#' +#' - `to_directed()` reformats undirected network data to a directed network. +#' - `to_redirected()` reformats the direction of directed network data, flipping any existing direction. +#' - `to_reciprocated()` reformats directed network data such that every directed tie is reciprocated. +#' - `to_acyclic()` reformats network data to an acyclic graph. +#' - `to_named()` reformats unlabelled network data to labelled network data +#' from a vector of names or random baby names. +#' - `to_signed()` reformats unsigned network data to signed network data +#' with signs from a mark vector or at random. +#' +#' If the format condition is not met, +#' for example `to_undirected()` is used on a network that is already undirected, +#' the network data is returned unaltered. +#' No warning is given so that these functions can be used to ensure conformance. +#' +#' Unlike the `as_*()` group of functions, +#' these functions always return the same class as they are given, +#' only transforming these objects' properties. +#' @details +#' Not all functions have methods available for all object classes. +#' Below are the currently implemented S3 methods: +#' +#' ```{r, echo = FALSE, cache = TRUE} +#' knitr::kable(available_methods(c("to_directed", "to_redirected", +#' "to_reciprocated", "to_acyclic", "to_named", "to_simplex"))) +#' ``` +#' @name manip_preformat +#' @family modifications +#' @inheritParams mark_is +#' @param names Character vector of the node names. NULL by default. +#' @returns +#' All `to_` functions return an object of the same class as that provided. +#' So passing it an igraph object will return an igraph object +#' and passing it a network object will return a network object, +#' with certain modifications as outlined for each function. +NULL + +#' @rdname manip_preformat +#' @param names Character vector of the node names. NULL by default. #' @importFrom dplyr mutate #' @importFrom igraph vcount V #' @export @@ -466,6 +570,7 @@ to_named.network <- function(.data, names = NULL) { .get_babynames <- function(n){ indic <- seq(from=1, length.out=n) %% 26 indic[indic == 0] <- 26 + mnet_info("Assigning alphabetic baby names at random.") # table(stringr::str_extract(manynet:::baby_names, "^.")) vapply(indic, function(x){ @@ -474,69 +579,111 @@ to_named.network <- function(.data, names = NULL) { }, FUN.VALUE = character(1)) } -#' @describeIn manip_reformat Returns an object that has all loops or self-ties removed -#' @importFrom igraph simplify +#' @rdname manip_reformat +#' @importFrom igraph as.directed #' @export -to_simplex <- function(.data) UseMethod("to_simplex") +to_directed <- function(.data) UseMethod("to_directed") #' @export -to_simplex.tbl_graph <- function(.data) { - as_tidygraph(to_simplex(as_igraph(.data))) +to_directed.igraph <- function(.data) { + if(!is_directed.igraph(.data)){ + mnet_info("Directions are assigned to existing ties at random.") + igraph::as.directed(.data, mode = "random") + } else .data } #' @export -to_simplex.igraph <- function(.data) { - igraph::simplify(.data) +to_directed.tbl_graph <- function(.data) { + as_tidygraph(to_directed(as_igraph(.data))) } #' @export -to_simplex.matrix <- function(.data) { - out <- .data - diag(out) <- 0 +to_directed.matrix <- function(.data) { + as_matrix(to_directed(as_igraph(.data))) +} + +#' @export +to_directed.network <- function(.data) { + as_network(to_directed(as_igraph(.data))) +} + +#' @export +to_directed.data.frame <- function(.data) { + as_edgelist(to_directed(as_igraph(.data))) +} + +#' @rdname manip_preformat +#' @param mark A mark (logical vector) the length of the ties in the network. +#' @export +to_signed <- function(.data, mark = NULL) UseMethod("to_signed") + +#' @export +to_signed.matrix <- function(.data, mark = NULL){ + if(is.null(mark)){ + out <- ifelse(stats::runif(length(.data))>=0.5, .data, -.data) + mnet_info("Since no mark given, signs are generated by splitting", + "a uniform distribution.") + } else out <- ifelse(mark, .data[.data!=0], -.data[.data!=0]) + if(is_labelled(.data)){ + out <- matrix(out, nrow(.data), ncol(.data), + dimnames = list(rownames(.data),colnames(.data))) + } else out <- matrix(out, nrow(.data), ncol(.data)) out } -#' @rdname manip_reformat -#' @importFrom igraph complementer -#' @examples -#' to_anti(ison_southern_women) -#' #graphr(to_anti(ison_southern_women)) #' @export -to_anti <- function(.data) UseMethod("to_anti") +to_signed.data.frame <- function(.data, mark = NULL){ + if(is.null(mark)) mark <- stats::runif(nrow(.data))>=0.5 + out <- data.frame(.data, sign = ifelse(mark, 1, -1)) + dplyr::tibble(out) +} #' @export -to_anti.matrix <- function(.data){ - matrix(1, nrow(.data), ncol(.data)) - .data +to_signed.tbl_graph <- function(.data, mark = NULL){ + if(is.null(mark)){ + ties <- net_ties(.data) + mnet_info("Since no mark given, signs are generated by splitting", + "a uniform distribution.") + .data %>% mutate_ties(sign = ifelse(stats::runif(ties)>=0.5, 1, -1)) + } else .data %>% mutate_ties(sign = ifelse(mark, 1, -1)) } #' @export -to_anti.data.frame <- function(.data){ - as_edgelist.matrix(to_anti.matrix(as_matrix(.data))) +to_signed.igraph <- function(.data, mark = NULL){ + as_igraph(to_signed.tbl_graph(as_tidygraph(.data), mark = mark)) } #' @export -to_anti.igraph <- function(.data){ - if(is_twomode(.data)){ - as_igraph(to_anti.matrix(as_matrix(.data))) - } else { - igraph::complementer(as_igraph(.data), - loops = is_complex(.data)) - } +to_signed.network <- function(.data, mark = NULL){ + as_network(to_signed.tbl_graph(as_tidygraph(.data), mark = mark)) } +#' @rdname manip_preformat +#' @param measure A numeric vector (measure) that will be added as the tie +#' weights to the network. +#' If this is NULL, then the tie weights will be drawn from a +#' Poisson distribution with \eqn{\lambda = 4}. #' @export -to_anti.tbl_graph <- function(.data){ - if(is_twomode(.data)){ - as_tidygraph(to_anti.matrix(as_matrix(.data))) - } else { - as_tidygraph(igraph::complementer(as_igraph(.data), - loops = is_complex(.data))) +to_weighted <- function(.data, measure = NULL) UseMethod("to_weighted") + +#' @export +to_weighted.tbl_graph <- function(.data, measure = NULL){ + if(is.null(measure)){ + measure <- stats::rpois(net_ties(.data), lambda = 4) + mnet_info("Since no measure values given, weights are generated from", + "a Poisson distribution with lambda = 4.") } + .data %>% mutate_ties(weight = measure) } #' @export -to_anti.network <- function(.data){ - as_network(to_anti(as_igraph(.data))) +to_weighted.igraph <- function(.data, measure = NULL){ + as_igraph(to_weighted.tbl_graph(as_tidygraph(.data), measure = measure)) +} + +#' @export +to_weighted.network <- function(.data, measure = NULL){ + as_network(to_weighted.tbl_graph(as_tidygraph(.data), measure = measure)) } # Levelling #### diff --git a/R/manip_reformed.R b/R/manip_reformed.R index 57e81ab9..3c0f5a2c 100644 --- a/R/manip_reformed.R +++ b/R/manip_reformed.R @@ -10,7 +10,7 @@ #' - `to_mode2()` projects a two-mode network to a one-mode network #' of the second node set's (e.g. columns) joint affiliations to nodes in the first node set (rows). #' - `to_ties()` projects a network to one where the ties become nodes and incident nodes become their ties. -#' - `to_galois()` projects a network to its Galois derivation. +# #' - `to_galois()` projects a network to its Galois derivation. #' @details #' Not all functions have methods available for all object classes. #' Below are the currently implemented S3 methods: @@ -188,20 +188,20 @@ to_ties.matrix <- function(.data){ as_matrix(to_ties(as_igraph(.data))) } -#' @rdname manip_project -#' @section Galois lattices: -#' Note that the output from `to_galois()` is very busy at the moment. -#' @export -to_galois <- function(.data) { - x <- as_matrix(.data) - thisRequires("multiplex") - out <- multiplex::galois(x, labeling = "reduced") - out <- multiplex::partial.order(out, type = "galois") - class(out) <- c("matrix", class(out)) - rownames(out)[!startsWith(rownames(out), "{")] <- "" - colnames(out)[!startsWith(colnames(out), "{")] <- "" - out -} +# #' @rdname manip_project +# #' @section Galois lattices: +# #' Note that the output from `to_galois()` is very busy at the moment. +# #' @export +# to_galois <- function(.data) { +# x <- as_matrix(.data) +# thisRequires("multiplex") +# out <- multiplex::galois(x, labeling = "reduced") +# out <- multiplex::partial.order(out, type = "galois") +# class(out) <- c("matrix", class(out)) +# rownames(out)[!startsWith(rownames(out), "{")] <- "" +# colnames(out)[!startsWith(colnames(out), "{")] <- "" +# out +# } # Scoping #### diff --git a/R/manynet-defunct.R b/R/manynet-defunct.R index 2a463682..da06708f 100644 --- a/R/manynet-defunct.R +++ b/R/manynet-defunct.R @@ -711,3 +711,27 @@ node_core <- function(.data) { node_is_core(.data) } +#' @describeIn defunct Deprecated on 2024-10-10. +#' @export +node_by_quad <- function(.data) { + .Deprecated("node_by_tetrad", package = "manynet", + old = "node_by_quad") + node_by_tetrad(.data) +} + +#' @describeIn defunct Deprecated on 2024-10-10. +#' @export +net_by_quad <- function(.data) { + .Deprecated("net_by_tetrad", package = "manynet", + old = "net_by_quad") + net_by_tetrad(.data) +} + +#' @describeIn defunct Deprecated on 2024-10-10. +#' @export +layout_tbl_graph_quad <- function(.data, circular = FALSE, times = 1000) { + .Deprecated("layout_tbl_graph_tetrad", package = "manynet", + old = "layout_tbl_graph_quad") + layout_tbl_graph_tetrad(.data, circular = circular, times = times) +} + diff --git a/R/manynet-tutorials.R b/R/manynet-tutorials.R index e8a228a5..4c0545a4 100644 --- a/R/manynet-tutorials.R +++ b/R/manynet-tutorials.R @@ -48,7 +48,8 @@ run_tute <- function(tute) { avails <- dplyr::bind_rows(tutelist) inftit <- grepl(tute, avails$title, ignore.case = TRUE) if(!any(inftit) | sum(inftit)>1) - inftit <- which.min(utils::adist(tute, avails$title, ignore.case = TRUE)) + inftit <- which.min(utils::adist(tute, avails$title, ignore.case = TRUE, + costs = list(ins=0, del=1, sub=1))) if(any(inftit) & sum(inftit)==1){ cli::cli_alert_success("And found one!") try(learnr::run_tutorial(avails$name[inftit], avails$package[inftit]), silent = TRUE) @@ -164,4 +165,76 @@ table_data <- function(pkg = c("manynet","migraph"), out <- dplyr::bind_rows(out) %>% dplyr::arrange(nodes) if(!is.null(filter)) out <- dplyr::filter(out, ...) out -} \ No newline at end of file +} + +# Glossary #### + + +#' Adding network glossary items +#' +#' @description +#' This function adds a glossary item, useful in tutorials. +#' +#' @param text The text to appear. +#' @param ref The name of the glossary item to index. +#' If NULL, then the function will search the glossary for 'text' instead. +#' @name glossary +NULL + +#' @rdname glossary +#' @export +gloss <- function(text, ref = NULL){ + if(is.null(ref)) ref <- tolower(text) + if(!ref %in% names(glossies)) + cli::cli_abort("No glossary entry for '{text}' exists.") else { + defn <- glossies[which(names(glossies)==ref)] + options(mnet_glossary = unique(c(ref, getOption("mnet_glossary", default = "")))) + paste(paste0(""), text, "") + } +} + +#' @rdname glossary +#' @export +print_glossary <- function(){ + defns <- getOption("mnet_glossary", default = "") + if(length(defns)!=0){ + glossd <- glossies[names(glossies) %in% defns] + glossn <- gsub("([[:alpha:]])([[:alpha:]]+)", "\\U\\1\\L\\2", names(glossd), perl=TRUE) + glosst <- data.frame(term = paste("
",glossn,"
"), + defn = paste("
",glossd,"
")) + paste("
",paste(paste(glosst$term, glosst$defn), collapse = " "),"
") + } +} + +#' @rdname glossary +#' @export +clear_glossary <- function(){ + options(mnet_glossary = vector()) +} + +## Definitions #### + +glossies <- list( + acyclic = "An acyclic network is a network without any cycles.", + adhesion = "The minimum number of ties to remove to increase the number of components.", + blockmodel = "A blockmodel reduces a network to a smaller comprehensible structure of the roles positions take with respect to one another.", + bridge = "A bridge is a tie whose deletion increases the number of components.", + cohesion = "The minimum number of nodes to remove to increase the number of components.", + component = "A component is a connected subgraph not part of a larger connected subgraph.", + cutpoint = "A cutpoint or articulation point is a node whose deletion increases the number of components.", + degree = "A node's degree is the number of connections it has.", + giant = "The giant component is the component that includes the most nodes in the network.", + graphlet = "A graphlet is a small, connected, induced, non-isomorphic subgraphs.", + induced = "An induced subgraph comprises all ties in a subset of the nodes in a network.", + lattice = "A network that can be drawn as a regular tiling.", + motif = "A subgraph that is exceptional or significant compared to a null model.", + neighborhood = "A node's neighborhood is the set of other nodes to which that node is connected.", + network = "A network comprises a set of nodes/vertices and a set of ties/edges among them.", + orbit = "An orbit is a unique position in a subgraph.", + reciprocity = "A measure of how often nodes in a directed network are mutually linked.", + reduced = "A reduced graph is a representation of the ties within and between blocks in the network.", + subgraph = "A subgraph comprises a subset of the nodes and ties in a network.", + transitivity = "Triadic closure is where if the connections A-B and A-C exist among three nodes, there is a tendency for B-C also to be formed.", + undirected = "An undirected network is one in which tie direction is undefined." +) + diff --git a/R/manynet-utils.R b/R/manynet-utils.R index ad3e1ca1..7904920f 100644 --- a/R/manynet-utils.R +++ b/R/manynet-utils.R @@ -1,5 +1,7 @@ # defining global variables more centrally -utils::globalVariables(c(".data", "obs", "from", "to", "name", "A","B","C","D")) +utils::globalVariables(c(".data", "obs", + "from", "to", "name", "weight","sign","wave", + "A","B","C","D")) # Helper function for declaring available methods available_methods <- function(fun_vctr) { diff --git a/R/map_autograph.R b/R/map_autograph.R index 504f3093..4f7f2bb8 100644 --- a/R/map_autograph.R +++ b/R/map_autograph.R @@ -86,6 +86,7 @@ #' it is recommended to calculate all edge-related statistics prior #' to using this function. #' Edges can also be sized by declaring a numeric size or vector instead. +#' @param snap Logical scalar, whether the layout should be snapped to a grid. #' @param ... Extra arguments to pass on to the layout algorithm, if necessary. #' @return A `ggplot2::ggplot()` object. #' The last plot can be saved to the file system using `ggplot2::ggsave()`. @@ -95,7 +96,7 @@ #' @examples #' graphr(ison_adolescents) #' ison_adolescents %>% -#' mutate(color = rep(c("extrovert", "introvert"), times = 4), +#' mutate(color = rep(c("introvert","extrovert"), times = 4), #' size = ifelse(node_is_cutpoint(ison_adolescents), 6, 3)) %>% #' mutate_ties(ecolor = rep(c("friends", "acquaintances"), times = 5)) %>% #' graphr(node_color = "color", node_size = "size", @@ -103,11 +104,11 @@ #' @export graphr <- function(.data, layout, labels = TRUE, node_color, node_shape, node_size, node_group, - edge_color, edge_size, ..., + edge_color, edge_size, snap = FALSE, ..., node_colour, edge_colour) { g <- as_tidygraph(.data) if (missing(layout)) { - if (length(g) == 3 | length(g) == 4) { + if (net_nodes(g) <= 6) { layout <- "configuration" } else if (is_twomode(g)) { layout <- "hierarchy" @@ -141,7 +142,10 @@ graphr <- function(.data, layout, labels = TRUE, edge_size <- as.character(substitute(edge_size)) } # Add layout ---- - p <- .graph_layout(g, layout, labels, node_group, ...) + p <- .graph_layout(g, layout, labels, node_group, snap, ...) + # Add background ---- + if(getOption("mnet_background", default = "#FFFFFF")!="#FFFFFF") + p <- p + ggplot2::theme(panel.background = ggplot2::element_rect(fill = getOption("mnet_background", default = "#FFFFFF"))) # Add edges ---- p <- .graph_edges(p, g, edge_color, edge_size, node_size) # Add nodes ---- @@ -150,10 +154,11 @@ graphr <- function(.data, layout, labels = TRUE, if (isTRUE(labels) & is_labelled(g)) { p <- .graph_labels(p, g, layout) } + # assign("last.warning", NULL, envir = baseenv()) # to avoid persistent ggrepel p } -.graph_layout <- function(g, layout, labels, node_group, ...) { +.graph_layout <- function(g, layout, labels, node_group, snap, ...) { name <- NULL dots <- list(...) if ("x" %in% names(dots) & "y" %in% names(dots)) { @@ -178,6 +183,14 @@ graphr <- function(.data, layout, labels = TRUE, ggplot2::scale_fill_manual(values = colorsafe_palette, guide = ggplot2::guide_legend("Group")) } + if(snap){ + mnet_info("Snapping layout coordinates to grid.") + if(grepl("lattice", + igraph::graph_attr(attr(p$data, "graph"), "grand")$name, + ignore.case = TRUE)) + p$data[,c("x","y")] <- round(p$data[,c("x","y")]) + else p$data[,c("x","y")] <- depth_first_recursive_search(p) + } p } @@ -202,7 +215,13 @@ graphr <- function(.data, layout, labels = TRUE, "Edge Weight", "Edge Size"))) if (length(unique(out[["ecolor"]])) == 1) { p <- p + ggplot2::guides(edge_colour = "none") - } else p <- p + ggraph::scale_edge_colour_manual(values = colorsafe_palette, + } else if (length(unique(out[["ecolor"]])) == 2){ + p <- p + ggraph::scale_edge_colour_manual(values = getOption("mnet_highlight", default = c("grey","black")), + guide = ggplot2::guide_legend( + ifelse(is.null(edge_color) & + is_signed(g), + "Edge Sign", "Edge Color"))) + } else p <- p + ggraph::scale_edge_colour_manual(values = getOption("mnet_cat", default = colorsafe_palette), guide = ggplot2::guide_legend( ifelse(is.null(edge_color) & is_signed(g), @@ -224,9 +243,15 @@ graphr <- function(.data, layout, labels = TRUE, if (length(unique(out[["nshape"]])) > 1) p <- p + ggplot2::guides(shape = ggplot2::guide_legend( title = ifelse(is_twomode(g) & is.null(node_shape), "Node Mode", "Node Shape"))) - if (length(unique(out[["ncolor"]])) > 1) - p <- p + ggplot2::scale_colour_manual(values = colorsafe_palette, - guide = ggplot2::guide_legend("Node Color")) + if (length(unique(out[["ncolor"]])) > 1){ + if(length(unique(out[["ncolor"]])) == 2){ + p <- p + ggplot2::scale_colour_manual(values = getOption("mnet_highlight", default = c("grey","black")), + guide = ggplot2::guide_legend("Node Color")) + } else { + p <- p + ggplot2::scale_colour_manual(values = colorsafe_palette, + guide = ggplot2::guide_legend("Node Color")) + } + } } # Consider rescaling nodes p <- p + ggplot2::scale_size(range = c(1/net_nodes(g)*50, 1/net_nodes(g)*100)) @@ -387,10 +412,11 @@ reduce_categories <- function(g, node_group) { .infer_line_type <- function(g) { if (is_signed(g)) { - out <- ifelse(as.numeric(tie_attribute(g, "sign")) >= 0, + out <- ifelse(as.numeric(tie_signs(g)) >= 0, "solid", "dashed") - ifelse(length(unique(out)) == 1, unique(out), out) - } else "solid" + # ifelse(length(unique(out)) == 1, unique(out), out) + } else out <- "solid" + out } check_edge_variables <- function(g, edge_color, edge_size) { @@ -430,7 +456,7 @@ map_directed_edges <- function(p, g, out) { arrow = ggplot2::arrow(angle = 15, type = "closed", length = ggplot2::unit(2, 'mm'))) } else { - p <- p + ggraph::geom_edge_arc(ggplot2::aes(edge_colour = out[["ecolor"]], + p <- p + ggraph::geom_edge_arc(ggplot2::aes(edge_colour = getOption("mnet_cat")[out[["ecolor"]]], edge_width = out[["esize"]], end_cap = ggraph::circle(c(out[["end_cap"]]), 'mm')), edge_linetype = out[["line_type"]], diff --git a/R/map_layouts.R b/R/map_layouts.R index 797e13f1..1981156a 100644 --- a/R/map_layouts.R +++ b/R/map_layouts.R @@ -4,7 +4,7 @@ #' #' @description #' Configurational layouts locate nodes at symmetric coordinates -#' to help illustrate the particular layouts. +#' to help illustrate particular configurations. #' Currently "triad" and "quad" layouts are available. #' The "configuration" layout will choose the appropriate configurational #' layout automatically. @@ -18,11 +18,27 @@ NULL #' @export layout_tbl_graph_configuration <- function(.data, circular = FALSE, times = 1000){ - if (net_nodes(.data) == 3) { + if (net_nodes(.data) == 2) { + layout_tbl_graph_dyad(.data, circular = circular, times = times) + } else if (net_nodes(.data) == 3) { layout_tbl_graph_triad(.data, circular = circular, times = times) } else if (net_nodes(.data) == 4) { - layout_tbl_graph_quad(.data, circular = circular, times = times) - }} + layout_tbl_graph_tetrad(.data, circular = circular, times = times) + } else if (net_nodes(.data) == 5) { + layout_tbl_graph_pentad(.data, circular = circular, times = times) + } else if (net_nodes(.data) == 6) { + layout_tbl_graph_hexad(.data, circular = circular, times = times) + } +} + +#' @rdname map_layout_configuration +#' @export +layout_tbl_graph_dyad <- function(.data, + circular = FALSE, times = 1000){ + res <- matrix(c(0,0, + 1,0), 2, 2, byrow = TRUE) + .to_lo(res) +} #' @rdname map_layout_configuration #' @export @@ -36,7 +52,7 @@ layout_tbl_graph_triad <- function(.data, #' @rdname map_layout_configuration #' @export -layout_tbl_graph_quad <- function(.data, +layout_tbl_graph_tetrad <- function(.data, circular = FALSE, times = 1000){ res <- matrix(c(0,0, 0,1, @@ -45,6 +61,31 @@ layout_tbl_graph_quad <- function(.data, .to_lo(res) } +#' @rdname map_layout_configuration +#' @export +layout_tbl_graph_pentad <- function(.data, + circular = FALSE, times = 1000){ + res <- matrix(c(0,1, + -0.9511,0.3090, + -0.5878,-0.8090, + 0.5878,-0.8090, + 0.9511,0.3090), 5, 2, byrow = TRUE) + .to_lo(res) +} + +#' @rdname map_layout_configuration +#' @export +layout_tbl_graph_hexad <- function(.data, + circular = FALSE, times = 1000){ + res <- matrix(c(1,0, + 1/2,sqrt(3)/2, + -1/2,sqrt(3)/2, + -1,0, + -1/2,-sqrt(3)/2, + 1/2,-sqrt(3)/2), 6, 2, byrow = TRUE) + .to_lo(res) +} + # Partitions #### #' Layout algorithms based on bi- or other partitions @@ -422,3 +463,103 @@ nrm <- function(x, digits = 3) { return(round((x - min(x))/(max(x) - min(x)), digits)) } } + +# Grid #### + +#' Layouts for snapping layouts to a grid +#' +#' @description The function uses approximate pattern matching +#' to redistribute coarse layouts on square grid points, while +#' preserving the topological relationships among the nodes (see Inoue et al. 2012). +#' @references +#' Inoue, Kentaro, Shinichi Shimozono, Hideaki Yoshida, and Hiroyuki Kurata. 2012. +#' “Application of Approximate Pattern Matching in Two Dimensional Spaces to Grid Layout for Biochemical Network Maps” edited by J. Bourdon. +#' _PLoS ONE_ 7(6):e37739. +#' \doi{https://doi.org/10.1371/journal.pone.0037739}. +#' @keywords internal +depth_first_recursive_search <- function(layout) { + if("ggraph" %in% class(layout)) layout <- layout$data[,c("x","y")] + layout <- as.data.frame(layout) + dims <- ceiling(2 * sqrt(nrow(layout))) + # evens <- 0:dims[0:dims %% 2 == 0] + vacant_points <- expand.grid(seq.int(0, dims, 1), seq.int(0, dims, 1)) # create options + vacant_points <- vacant_points - floor(dims / 2) # centre options + names(vacant_points) <- c("x", "y") + gridout <- layout[order(abs(layout[,1]) + abs(layout[,2])), ] # sort centroid distance + nodes <- seq_len(nrow(gridout)) + for (i in nodes) { + dists <- as.matrix(stats::dist(rbind(gridout[i, 1:2], vacant_points), + method = "manhattan"))[, 1] + mindist <- which(dists == min(dists[2:length(dists)]))[1] - 1 + vacpoint <- vacant_points[mindist, ] + changes <- vacpoint - gridout[i, 1:2] + gridout[nodes >= i, 1] <- gridout[nodes >= i, 1] + + changes[[1]] + gridout[nodes >= i, 2] <- gridout[nodes >= i, 2] + + changes[[2]] + vacant_points <- vacant_points[-mindist, ] + } + gridout[order(row.names(gridout)),] # reorder from centroid + # gridout + # plot(gridout[order(row.names(gridout)),]) +} + +# localmin <- function(layout, graph) { +# repeat { +# f0 <- sum(cost_function(layout, graph)) +# L <- get_vacant_points(layout) +# for (a in seq_len(nrow(layout))) { +# out <- t(apply(L, 1, function(y) { +# layout_new <- layout +# layout_new[a, 1:2] <- y +# c(a, y, sum(cost_function(layout_new, graph))) +# })) +# } +# if (out[which.min(out[, 4]), 4] < f0) { +# layout[out[which.min(out[, 4]), 1], 1:2] <- out[which.min(out[, 4]), 2:3] +# } else{ +# break +# } +# } +# layout +# } +# +# get_vacant_points <- function(layout) { +# all_points <- expand.grid(min(layout$x):max(layout$x), +# min(layout$y):max(layout$y)) +# names(all_points) <- c("x", "y") +# vacant_points <- rbind(all_points, +# layout[, c("x", "y")]) +# vacant_points <- subset(vacant_points, +# !(duplicated(vacant_points) | +# duplicated(vacant_points, fromLast = TRUE))) +# vacant_points +# } +# +# cost_function <- function(layout, graph, max_repulse_distance = max(layout[, 1]) * .75) { +# d <- as.matrix(dist(layout[, 1:2], method = "manhattan")) +# a <- as_matrix(graph) +# i <- diag(nrow(a)) +# m <- a + i +# w <- ifelse(m > 0, 3, +# ifelse(m == 0 & m %*% t(m) > 0, 0, -2)) # only three levels here +# # see Li and Kurata (2005: 2037) for more granulated option +# ifelse(w >= 0, w * d, w * min(d, max_repulse_distance)) +# } +# +# plot_gl <- function(x, tmax, tmin, rmin, fmin, ne, rc, p) { +# l <- index <- a <- NULL # initialize variables to avoid CMD check notes +# x <- as_tidygraph(x) +# lo <- ggraph::create_layout(x, layout = "igraph", algorithm = "randomly") +# lo[, 1] <- round(lo[, 1] * 1000) +# lo[, 2] <- round(lo[, 2] * 1000) +# dists <- as.matrix(dist(lo[, 1:2], method = "manhattan")) +# colMax <- function(data) apply(data, MARGIN = 1, FUN = max, na.rm = TRUE) +# diag(dists) <- NA +# rsep <- l * sum(ifelse(colMax(a / dists - 1) > 0, colMax(a / dists - 1), 0)) +# ggraph::ggraph(x, graph = lo) + +# ggraph::geom_edge_link(ggplot2::aes(alpha = ggplot2::stat(index)), +# show.legend = FALSE) + +# ggraph::geom_node_point() +# } + diff --git a/R/map_theme.R b/R/map_theme.R index 0b60e769..c9e8db79 100644 --- a/R/map_theme.R +++ b/R/map_theme.R @@ -20,15 +20,73 @@ NULL #' By default "default". #' @export set_manynet_theme <- function(theme = "default"){ - theme_opts <- c("default", "iheid", "ethz", "uzh", "rug", "crisp") + theme_opts <- c("default", + "iheid", "ethz", "uzh", "rug", + "crisp", "neon", "rainbow") if(theme %in% theme_opts){ options(mnet_theme = theme) - cli::cli_alert_success("Theme set to {theme}.") + set_highlight_theme(theme) + set_background_theme(theme) + set_categorical_theme(theme) + cli::cli_alert_success("Theme set to {.emph {theme}}.") } else { - cli::cli_alert_danger("Please choose one of the available themes: {.emph {theme_opts}}.") + cli::cli_alert_warning("Please choose one of the available themes: {.emph {theme_opts}}.") } } +set_highlight_theme <- function(theme){ + if(theme == "iheid"){ + options(mnet_highlight = c("#000010","#E20020")) + } else if(theme == "rug"){ + options(mnet_highlight = c("#000000", "#dc002d")) + } else if(theme == "uzh"){ + options(mnet_highlight = c("#a3adb7", "#dc6027")) + } else if(theme == "ethz"){ + options(mnet_highlight = c("#6F6F6F", "#0028a5")) + } else if(theme == "crisp"){ + options(mnet_highlight = c("#FFFFFA", "#101314")) + } else if(theme == "neon"){ + options(mnet_highlight = c("#5aeafd", "#54fe4b")) + } else if(theme == "rainbow"){ + options(mnet_highlight = c('#1965B0', '#DC050C')) + } else { + options(mnet_highlight = c("#4576B5", "#D83127")) + } +} + +set_background_theme <- function(theme){ + if(theme == "neon"){ + options(mnet_background = "#070f23") + } else { + options(mnet_background = "#FFFFFF") + } +} + +set_categorical_theme <- function(theme){ + if(theme == "iheid"){ + options(mnet_cat = c("#006564","#0094D8","#622550", + "#268D2B","#3E2682","#820C2B", + "#008F92","#006EAA","#A8086E")) + } else if(theme == "rainbow"){ + options(mnet_cat = c('#E8ECFB', '#D9CCE3', '#D1BBD7', + '#CAACCB', '#BA8DB4', '#AE76A3', + '#AA6F9E', '#994F88', '#882E72', + '#1965B0', '#437DBF', '#5289C7', + '#6195CF', '#7BAFDE', + '#4EB265', '#90C987', '#CAE0AB', + '#F7F056', '#F7CB45', '#F6C141', + '#F4A736', '#F1932D', '#EE8026', + '#E8601C', '#E65518', '#DC050C', + '#A5170E', '#72190E', '#42150A')) + } else { + options(mnet_cat = c("#1B9E77","#4575b4","#d73027", + "#66A61E","#E6AB02","#D95F02","#7570B3", + "#A6761D","#E7298A","#666666")) + } +} + + + #' @rdname map_themes #' @export theme_iheid <- function(base_size = 12, base_family = "serif") { @@ -480,3 +538,4 @@ palette_gen <- function(palette, direction = 1) { } } } + diff --git a/R/mark_nodes.R b/R/mark_nodes.R index 2d1b47e7..1e15ab34 100644 --- a/R/mark_nodes.R +++ b/R/mark_nodes.R @@ -37,6 +37,19 @@ node_is_isolate <- function(.data){ make_node_mark(out, .data) } +#' @rdname mark_nodes +#' @export +node_is_pendant <- function(.data){ + if(missing(.data)) {expect_nodes(); .data <- .G()} + mat <- as_matrix(.data) + if(is_twomode(.data)){ + out <- c(rowSums(mat)==1, colSums(mat)==1) + } else { + out <- rowSums(mat)==1 & colSums(mat)==1 + } + make_node_mark(out, .data) +} + #' @rdname mark_nodes #' @importFrom igraph largest_ivs #' @references @@ -156,6 +169,16 @@ node_is_mentor <- function(.data, elites = 0.1){ make_node_mark(out, .data) } +#' @rdname mark_nodes +#' @inheritParams manip_scope +#' @export +node_is_neighbor <- function(.data, node){ + if(missing(.data)) {expect_nodes(); .data <- .G()} + .data <- as_igraph(.data) + out <- igraph::V(.data) %in% igraph::neighbors(.data, v = node) + make_node_mark(out, .data) +} + # Diffusion properties #### #' Marking nodes based on diffusion properties diff --git a/R/mark_ties.R b/R/mark_ties.R index d95f2597..81861c7f 100644 --- a/R/mark_ties.R +++ b/R/mark_ties.R @@ -138,7 +138,6 @@ tie_is_triangular <- function(.data){ .triangle_ties <- function(.data){ out <- t(matrix(igraph::triangles(as_igraph(.data)), nrow = 3)) - # out <- as.data.frame(out) out <- rbind(out[,c(1,2)],out[,c(2,3)],out[,c(3,1)], out[,c(1,3)],out[,c(3,2)],out[,c(2,1)]) out @@ -248,6 +247,67 @@ tie_is_forbidden <- function(.data){ make_tie_mark(out, .data) } +#' @rdname mark_triangles +#' @examples +#' tie_is_imbalanced(ison_marvel_relationships) +#' @export +tie_is_imbalanced <- function(.data){ + if(missing(.data)) {expect_edges(); .data <- .G()} + + # identify_imbalanced_ties <- function(adj_matrix) { + adj_matrix <- as_matrix(.data) + + # Check if the input is a square matrix + if (!is.matrix(adj_matrix) || nrow(adj_matrix) != ncol(adj_matrix)) { + mnet_unavailable("This function only works with undirected one-mode networks.") + } + + # Get the number of nodes + n <- net_nodes(.data) + + # Identify all edges in the upper triangle (non-zero) + edges <- as_edgelist(to_unnamed(.data)) + num_edges <- nrow(edges) + + # Initialize a logical vector to store the result for each edge + is_imbalanced <- logical(num_edges) + + # Loop over each edge to check if it participates in an imbalanced triad + for (e in 1:num_edges) { + i <- unname(unlist(edges[e, 1])) + j <- unname(unlist(edges[e, 2])) + + # Variable to track if the current edge is part of any imbalanced triad + imbalanced_found <- FALSE + + # Check all possible third nodes k to form a triad (i, j, k) + for (k in setdiff(1:n, c(i, j))) { + # Get the ties for the triad (i, j, k) + a <- adj_matrix[i, j] + b <- adj_matrix[j, k] + c <- adj_matrix[i, k] + + # Check if the triad is complete (no zeros) + if (b != 0 && c != 0) { + # Count the number of positive ties in the triad + positive_count <- sum(c(a, b, c) > 0) + + # Determine if the triad is imbalanced + if (positive_count == 2 || positive_count == 0) { + # Mark as imbalanced and exit loop for this edge + imbalanced_found <- TRUE + break + } + } + } + + # Store the result for the current edge + is_imbalanced[e] <- imbalanced_found + } + + make_tie_mark(is_imbalanced, .data) +} + # Selection properties #### #' Marking ties for selection based on measures diff --git a/R/measure_attributes.R b/R/measure_attributes.R index 26908ce3..595d367a 100644 --- a/R/measure_attributes.R +++ b/R/measure_attributes.R @@ -21,7 +21,7 @@ NULL #' @rdname measure_attributes #' @examples -#' node_attribute(ison_lotr, "Race") +#' node_attribute(fict_lotr, "Race") #' @export node_attribute <- function(.data, attribute){ out <- igraph::vertex_attr(as_igraph(.data), attribute) diff --git a/R/measure_centrality.R b/R/measure_centrality.R index 85a6c5c7..1627b5cc 100644 --- a/R/measure_centrality.R +++ b/R/measure_centrality.R @@ -745,6 +745,30 @@ node_distance <- function(.data, from, to, normalized = TRUE){ make_node_measure(out, .data) } +#' @rdname measure_central_close +#' @section Closeness vitality centrality: +#' The closeness vitality of a node is the change in the sum of all distances +#' in a network, also known as the Wiener Index, when that node is removed. +#' Note that the closeness vitality may be negative infinity if +#' removing that node would disconnect the network. +#' @references +#' Koschuetzki, Dirk, Katharina Lehmann, Leon Peeters, Stefan Richter, +#' Dagmar Tenfelde-Podehl, and Oliver Zlotowski. 2005. +#' "Centrality Indices", in +#' Brandes, Ulrik, and Thomas Erlebach (eds.). +#' _Network Analysis: Methodological Foundations_. +#' Springer: Berlin, pp. 16-61. +#' @export +node_vitality <- function(.data, normalized = TRUE){ + if(missing(.data)) {expect_nodes(); .data <- .G()} + .data <- as_igraph(.data) + out <- vapply(mnet_progress_nodes(.data), function(x){ + sum(igraph::distances(.data)) - sum(igraph::distances(delete_nodes(.data, x))) + }, FUN.VALUE = numeric(1)) + if(normalized) out <- out/max(out) + make_node_measure(out, .data) +} + #' @rdname measure_central_close #' @examples #' (ec <- tie_closeness(ison_adolescents)) @@ -891,6 +915,8 @@ NULL #' and \eqn{\lambda} is a constant representing the principal eigenvalue. #' Rather than performing this iteration, #' most routines solve the eigenvector equation \eqn{Ax = \lambda x}. +#' Note that since `{igraph}` v2.1.1, +#' the values will always be rescaled so that the maximum is 1. #' @param scale Logical scalar, whether to rescale the vector so the maximum score is 1. #' @details #' We use `{igraph}` routines behind the scenes here for consistency and because they are often faster. @@ -905,35 +931,34 @@ NULL #' node_eigenvector(ison_southern_women) #' @return A numeric vector giving the eigenvector centrality measure of each node. #' @export -node_eigenvector <- function(.data, normalized = TRUE, scale = FALSE){ +node_eigenvector <- function(.data, normalized = TRUE, scale = TRUE){ if(missing(.data)) {expect_nodes(); .data <- .G()} weights <- `if`(manynet::is_weighted(.data), manynet::tie_weights(.data), NA) graph <- manynet::as_igraph(.data) + if(!normalized) mnet_info("This function always returns a normalized value now.") + if(!scale) mnet_info("This function always returns a scaled value now.") + if(!manynet::is_connected(.data)) - warning("Unconnected networks will only allow nodes from one component have non-zero eigenvector scores.") + cli::cli_alert_warning("Unconnected networks will only allow nodes from one component to have non-zero eigenvector scores.") # Do the calculations if (!manynet::is_twomode(graph)){ out <- igraph::eigen_centrality(graph = graph, - directed = manynet::is_directed(graph), scale = scale, + directed = manynet::is_directed(graph), options = igraph::arpack_defaults())$vector - if (normalized) out <- out / sqrt(1/2) - if(scale) out <- out / max(out) } else { eigen1 <- manynet::to_mode1(graph) eigen1 <- igraph::eigen_centrality(graph = eigen1, - directed = manynet::is_directed(eigen1), scale = scale, + directed = manynet::is_directed(eigen1), options = igraph::arpack_defaults())$vector eigen2 <- manynet::to_mode2(graph) eigen2 <- igraph::eigen_centrality(graph = eigen2, - directed = manynet::is_directed(eigen2), scale = scale, + directed = manynet::is_directed(eigen2), options = igraph::arpack_defaults())$vector out <- c(eigen1, eigen2) - if (normalized) out <- out / sqrt(1/2) - if(scale) out <- out / max(out) } out <- make_node_measure(out, .data) out diff --git a/R/measure_cohesion.R b/R/measure_cohesion.R index 175e01f0..0ec88936 100644 --- a/R/measure_cohesion.R +++ b/R/measure_cohesion.R @@ -45,8 +45,8 @@ net_density <- function(.data) { #' please use `manynet::to_undirected()` first. #' @importFrom igraph components #' @examples -#' net_components(ison_friends) -#' net_components(to_undirected(ison_friends)) +#' net_components(fict_thrones) +#' net_components(to_undirected(fict_thrones)) #' @export net_components <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} diff --git a/R/measure_features.R b/R/measure_features.R index 0e3c46e2..b07fcd9c 100644 --- a/R/measure_features.R +++ b/R/measure_features.R @@ -110,8 +110,11 @@ net_richclub <- function(.data){ net_factions <- function(.data, membership = NULL){ if(missing(.data)) {expect_nodes(); .data <- .G()} - if(is.null(membership)) + if(is.null(membership)){ + mnet_info("No membership vector assigned.", + "Partitioning the network using {.fn node_in_partition}.") membership <- node_in_partition(.data) + } out <- stats::cor(c(manynet::as_matrix(.data)), c(manynet::as_matrix(manynet::create_components(.data, membership = membership)))) @@ -135,8 +138,12 @@ net_factions <- function(.data, #' can miss small clusters that 'hide' inside larger clusters. #' In the extreme case, this can be where they are only connected #' to the rest of the network through a single tie. +#' To help manage this problem, a `resolution` parameter is added. +#' Please see the argument definition for more details. #' @param resolution A proportion indicating the resolution scale. -#' By default 1. +#' By default 1, which returns the original definition of modularity. +#' The higher this parameter, the more smaller communities will be privileged. +#' The lower this parameter, the fewer larger communities are likely to be found. #' @examples #' net_modularity(ison_adolescents, #' node_in_partition(ison_adolescents)) diff --git a/R/measure_properties.R b/R/measure_properties.R index 73eb3cfe..d33b14f3 100644 --- a/R/measure_properties.R +++ b/R/measure_properties.R @@ -95,7 +95,7 @@ net_dims.network <- function(.data){ #' @rdname measure_properties #' @importFrom igraph vertex_attr_names #' @examples -#' net_node_attributes(ison_lotr) +#' net_node_attributes(fict_lotr) #' @export net_node_attributes <- function(.data){ igraph::vertex_attr_names(as_igraph(.data)) diff --git a/R/member_community.R b/R/member_community.R index 691ed248..a57f4d3e 100644 --- a/R/member_community.R +++ b/R/member_community.R @@ -6,6 +6,9 @@ #' These functions offer algorithms for partitioning #' networks into sets of communities: #' +#' - `node_in_community()` runs either optimal or, for larger networks, +#' finds the algorithm that maximises modularity and returns that membership +#' vector. #' - `node_in_optimal()` is a problem-solving algorithm that seeks to maximise #' modularity over all possible partitions. #' - `node_in_partition()` is a greedy, iterative, deterministic @@ -29,6 +32,56 @@ #' @family memberships NULL +#' @rdname member_community_non +#' @section Community: +#' This function runs through all available community detection algorithms +#' for a given network type, finds the algorithm that returns the +#' largest modularity score, and returns the corresponding membership +#' partition. +#' Where feasible (a small enough network), the optimal problem solving +#' technique is used to ensure the maximal modularity partition. +#' @export +node_in_community <- function(.data){ + if(net_nodes(.data)<100){ + # don't use node_in_betweenness because slow and poorer quality to optimal + mnet_success("{.fn node_in_optimal} available and", + "will return the highest modularity partition.") + node_in_optimal(.data) + } else { + poss_algs <- c("node_in_infomap", + "node_in_spinglass", + "node_in_fluid", + "node_in_louvain", + "node_in_leiden", + "node_in_greedy", + "node_in_eigen", + "node_in_walktrap") + if(!manynet::is_connected(.data)){ + notforconnected <- c("node_in_spinglass", + "node_in_fluid") + mnet_info("Excluding {.fn {notforconnected}} because network unconnected.") + poss_algs <- setdiff(poss_algs, notforconnected) + } + if(manynet::is_directed(.data)){ + notfordirected <- c("node_in_louvain", + "node_in_leiden", + "node_in_eigen") + mnet_info("Excluding {.fn {notfordirected}} because network directed.") + poss_algs <- setdiff(poss_algs, notfordirected) + } + mnet_info("Considering each of {.fn {poss_algs}}.") + candidates <- lapply(mnet_progress_along(poss_algs), function(comm){ + memb <- get(poss_algs[comm])(.data) + mod <- net_modularity(.data, memb) + list(memb, mod) + }) + mods <- unlist(sapply(candidates, "[", 2)) + maxmod <- which.max(mods) + mnet_success("{.fn {poss_algs[maxmod]}} returns the highest modularity ({round(mods[maxmod],3)}).") + candidates[[maxmod]][[1]] + } +} + #' @rdname member_community_non #' @section Optimal: #' The general idea is to calculate the modularity of all possible partitions, @@ -45,6 +98,9 @@ NULL #' @export node_in_optimal <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} + if(net_nodes(.data)>100) + cli::cli_alert_danger(paste("This algorithm may take some time", + "or even run out of memory on such a large network.")) out <- igraph::cluster_optimal(manynet::as_igraph(.data) )$membership make_node_member(out, .data) @@ -67,7 +123,7 @@ node_in_partition <- function(.data){ n <- net_nodes(.data) group_size <- ifelse(n %% 2 == 0, n/2, (n+1)/2) - # count internal and external costs of each vertex + # count internal and external costs of each node g <- as_matrix(to_multilevel(.data)) g1 <- g[1:group_size, 1:group_size] g2 <- g[(group_size+1):n, (group_size+1):n] @@ -79,14 +135,14 @@ node_in_partition <- function(.data){ g1.intcosts <- rowSums(g1) g1.extcosts <- rowSums(intergroup) - # count edge costs of each vertex + # count edge costs of each nodes g1.net <- g1.extcosts - g1.intcosts g2.net <- g2.extcosts - g2.intcosts g1.net <- sort(g1.net, decreasing = TRUE) g2.net <- sort(g2.net, decreasing = TRUE) - # swap pairs of vertices (one from each group) that give a positive sum of net edge costs + # swap pairs of nodes (one from each group) that give a positive sum of net tie costs if(length(g1.net)!=length(g2.net)) { g2.net <- c(g2.net,0) } else {g2.net} @@ -168,11 +224,16 @@ node_in_infomap <- function(.data, times = 50){ #' @export node_in_spinglass <- function(.data, max_k = 200, resolution = 1){ if(missing(.data)) {expect_nodes(); .data <- .G()} - out <- igraph::cluster_spinglass(manynet::as_igraph(.data), - spins = max_k, gamma = resolution, - implementation = ifelse(manynet::is_signed(.data), "neg", "orig") - )$membership - make_node_member(out, .data) + if(!igraph::is_connected(.data)) # note manynet::is_connected will return false + mnet_unavailable("This algorithm only works for connected networks.", + "We suggest using `to_giant()`", + "to select the largest component.") else { + out <- igraph::cluster_spinglass(manynet::as_igraph(.data), + spins = max_k, gamma = resolution, + implementation = ifelse(manynet::is_signed(.data), "neg", "orig") + )$membership + make_node_member(out, .data) + } } #' @rdname member_community_non @@ -195,13 +256,29 @@ node_in_spinglass <- function(.data, max_k = 200, resolution = 1){ node_in_fluid <- function(.data) { if(missing(.data)) {expect_nodes(); .data <- .G()} .data <- as_igraph(.data) - mods <- vapply(seq.int(net_nodes(.data)), function(x) - igraph::modularity(.data, membership = igraph::membership( - igraph::cluster_fluid_communities(.data, x))), - FUN.VALUE = numeric(1)) - out <- igraph::membership(igraph::cluster_fluid_communities( - .data, no.of.communities = which.max(mods))) - make_node_member(out, .data) + if (!igraph::is_connected(.data)) { + mnet_unavailable("This algorithm only works for connected networks.", + "We suggest using `to_giant()`", + "to select the largest component.") + } else { + if(is_complex(.data)){ + mnet_info("This algorithm only works for simple networks.", + "Converting to simplex.") + .data <- to_simplex(.data) + } + if(is_directed(.data)){ + mnet_info("This algorithm only works for undirected networks.", + "Converting to undirected") + .data <- to_undirected(.data) + } + mods <- vapply(seq_nodes(.data), function(x) + igraph::modularity(.data, membership = igraph::membership( + igraph::cluster_fluid_communities(.data, x))), + FUN.VALUE = numeric(1)) + out <- igraph::membership(igraph::cluster_fluid_communities( + .data, no.of.communities = which.max(mods))) + make_node_member(out, .data) + } } #' @rdname member_community_non @@ -222,6 +299,11 @@ node_in_fluid <- function(.data) { #' @export node_in_louvain <- function(.data, resolution = 1){ if(missing(.data)) {expect_nodes(); .data <- .G()} + if(is_directed(.data)){ + mnet_info("This algorithm only works for undirected networks.", + "Converting to undirected") + .data <- to_undirected(.data) + } out <- igraph::cluster_louvain(manynet::as_igraph(.data), resolution = resolution )$membership @@ -243,6 +325,8 @@ node_in_louvain <- function(.data, resolution = 1){ #' \eqn{n_i} is the node weight of node _i_, #' and \eqn{\delta(\sigma_i, \sigma_j) = 1} if and only if #' _i_ and _j_ are in the same communities and 0 otherwise. +#' Compared to the Louvain method, the Leiden algorithm additionally +#' tries to avoid unconnected communities. #' @references #' ## On Leiden community detection #' Traag, Vincent A., Ludo Waltman, and Nees Jan van Eck. 2019. @@ -254,6 +338,11 @@ node_in_louvain <- function(.data, resolution = 1){ #' @export node_in_leiden <- function(.data, resolution = 1){ if(missing(.data)) {expect_nodes(); .data <- .G()} + if(is_directed(.data)){ + mnet_info("This algorithm only works for undirected networks.", + "Converting to undirected") + .data <- to_undirected(.data) + } if(is_weighted(.data)){ # Traag resolution default n <- net_nodes(.data) resolution <- sum(tie_weights(.data))/(n*(n - 1)/2) @@ -314,6 +403,9 @@ NULL #' @export node_in_betweenness <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} + if(net_nodes(.data)>100) + cli::cli_alert_danger(paste("This algorithm may take some time", + "or even run out of memory on such a large network.")) clust <- suppressWarnings(igraph::cluster_edge_betweenness( manynet::as_igraph(.data))) out <- clust$membership @@ -373,6 +465,11 @@ node_in_greedy <- function(.data){ #' @export node_in_eigen <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} + if(is_directed(.data)){ + mnet_info("This algorithm only works for undirected networks.", + "Converting to undirected") + .data <- to_undirected(.data) + } clust <- igraph::cluster_leading_eigen(as_igraph(.data)) out <- clust$membership make_node_member(out, .data) @@ -411,3 +508,27 @@ node_in_walktrap <- function(.data, times = 50){ out } +# #' @rdname member_community_hier +# #' @section Ensemble: +# #' Ensemble-based community detection runs community detection +# #' algorithms over multilayer or multiplex networks. +# #' @references +# #' ## On ensemble-based community detection +# #' Tagarelli, Andrea, Alessia Amelio, and Francesco Gullo. 2017. +# #' "Ensemble-based Community Detection in Multilayer Networks". +# #' _Data Mining and Knowledge Discovery_, 31: 1506-1543. +# #' \doi{10.1007/s10618-017-0528-8} +# #' @examples +# #' node_in_ensemble(ison_adolescents) +# #' @export +# node_in_ensemble <- function(.data, linkage_constraint = TRUE){ +# if(missing(.data)) {expect_nodes(); .data <- .G()} +# clust <- igraph::cluster_walktrap(manynet::as_igraph(.data)) +# out <- clust$membership +# make_node_member(out, .data) +# out <- make_node_member(out, .data) +# attr(out, "hc") <- stats::as.hclust(clust, +# use.modularity = igraph::is_connected(.data)) +# attr(out, "k") <- max(clust$membership) +# out +# } diff --git a/R/member_components.R b/R/member_components.R index f5cacebe..f4eea507 100644 --- a/R/member_components.R +++ b/R/member_components.R @@ -34,10 +34,10 @@ NULL #' @rdname member_components #' @importFrom igraph components -#' @examples -#' ison_monks %>% to_uniplex("esteem") %>% -#' mutate_nodes(comp = node_in_component()) %>% -#' graphr(node_color = "comp") +# #' @examples +# #' ison_monks %>% to_uniplex("esteem") %>% +# #' mutate_nodes(comp = node_in_component()) %>% +# #' graphr(node_color = "comp") #' @export node_in_component <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} diff --git a/R/member_equivalence.R b/R/member_equivalence.R index 943e27e7..2d91af9e 100644 --- a/R/member_equivalence.R +++ b/R/member_equivalence.R @@ -51,7 +51,7 @@ NULL #' @export node_in_equivalence <- function(.data, census, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor", "cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L){ @@ -59,7 +59,9 @@ node_in_equivalence <- function(.data, census, hc <- switch(match.arg(cluster), hierarchical = cluster_hierarchical(census, match.arg(distance)), - concor = cluster_concor(.data, census)) + concor = cluster_concor(.data, census), + cosine = cluster_cosine(census, + match.arg(distance))) if(!is.numeric(k)) k <- switch(match.arg(k), @@ -84,7 +86,7 @@ node_in_equivalence <- function(.data, census, #' @export node_in_structural <- function(.data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor","cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L){ @@ -109,14 +111,20 @@ node_in_structural <- function(.data, #' @export node_in_regular <- function(.data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor","cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L){ if(missing(.data)) {expect_nodes(); .data <- .G()} if(is_twomode(.data)){ - mat <- as.matrix(node_by_quad(.data)) + mnet_info("Since this is a two-mode network,", + "using {.fn node_by_tetrad} to", + "profile nodes' embedding in local structures.") + mat <- as.matrix(node_by_tetrad(.data)) } else { + mnet_info("Since this is a one-mode network,", + "using {.fn node_by_triad} to", + "profile nodes' embedding in local structures.") mat <- node_by_triad(.data) } if(any(colSums(mat) == 0)) mat <- mat[,-which(colSums(mat) == 0)] @@ -130,15 +138,15 @@ node_in_regular <- function(.data, #' if(require("sna", quietly = TRUE)){ #' (nae <- node_in_automorphic(ison_southern_women, #' k = "elbow")) -#' } #' if(require("ggdendro", quietly = TRUE)){ #' plot(nae) #' } #' } +#' } #' @export node_in_automorphic <- function(.data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor","cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L){ diff --git a/R/model_cluster.R b/R/model_cluster.R index b1bf174a..6bb40402 100644 --- a/R/model_cluster.R +++ b/R/model_cluster.R @@ -26,26 +26,36 @@ cluster_hierarchical <- function(census, distance){ hc } +#' @rdname model_cluster +#' @export +cluster_cosine <- function(census, distance){ + cosines <- manynet::to_cosine(census) + dissimilarity <- 1 - cosines + distances <- stats::dist(dissimilarity, method = distance) + hc <- stats::hclust(distances) + hc$distances <- distances + hc +} + # cluster_concor(ison_adolescents) # cluster_concor(ison_southern_women) # https://github.com/bwlewis/hclust_in_R/blob/master/hc.R #' @rdname model_cluster #' @section CONCOR: -#' -#' First a matrix of Pearson correlation coefficients between each pair of nodes -#' profiles in the given census is created. -#' Then, again, we find the correlations of this square, symmetric matrix, -#' and continue to do this iteratively until each entry is either `1` or `-1`. -#' These values are used to split the data into two partitions, -#' with members either holding the values `1` or `-1`. -#' This procedure from census to convergence is then repeated within each block, -#' allowing further partitions to be found. -#' Unlike UCINET, partitions are continued until there are single members in -#' each partition. -#' Then a distance matrix is constructed from records of in which partition phase -#' nodes were separated, -#' and this is given to `stats::hclust()` so that dendrograms etc can be returned. +#' First a matrix of Pearson correlation coefficients between each pair of nodes +#' profiles in the given census is created. +#' Then, again, we find the correlations of this square, symmetric matrix, +#' and continue to do this iteratively until each entry is either `1` or `-1`. +#' These values are used to split the data into two partitions, +#' with members either holding the values `1` or `-1`. +#' This procedure from census to convergence is then repeated within each block, +#' allowing further partitions to be found. +#' Unlike UCINET, partitions are continued until there are single members in +#' each partition. +#' Then a distance matrix is constructed from records of in which partition phase +#' nodes were separated, +#' and this is given to `stats::hclust()` so that dendrograms etc can be returned. #' @importFrom stats complete.cases #' @references #' ## On CONCOR clustering @@ -132,4 +142,3 @@ cluster_concor <- function(.data, census){ hc$distances <- distances hc } - diff --git a/R/motif_census.R b/R/motif_census.R index 357b5732..1bb1327b 100644 --- a/R/motif_census.R +++ b/R/motif_census.R @@ -11,7 +11,7 @@ #' For multiplex networks, the various types of ties are bound together. #' - `node_by_triad()` returns a census of the triad configurations #' nodes are embedded in. -#' - `node_by_quad()` returns a census of nodes' positions +#' - `node_by_tetrad()` returns a census of nodes' positions #' in motifs of four nodes. #' - `node_by_path()` returns the shortest path lengths #' of each node to every other node in the network. @@ -152,44 +152,46 @@ node_by_triad <- function(.data){ # #' | X4 | K4 # #' # #' See also [this list of graph classes](https://www.graphclasses.org/smallgraphs.html#nodes4). -# #' @importFrom tidygraph %E>% -# #' @references -# #' Ortmann, Mark, and Ulrik Brandes. 2017. -# #' “Efficient Orbit-Aware Triad and Quad Census in Directed and Undirected Graphs.” -# #' \emph{Applied Network Science} 2(1):13. -# #' \doi{10.1007/s41109-017-0027-2}. -# #' @examples -# #' node_by_quad(ison_southern_women) -# #' @export -# node_by_quad <- function(.data){ -# if(missing(.data)) {expect_nodes(); .data <- .G()} -# thisRequires("oaqc") -# graph <- .data %>% manynet::as_tidygraph() %E>% -# as.data.frame() -# if(ncol(graph)>2) graph <- graph[,1:2] -# out <- oaqc::oaqc(graph)[[1]] -# out <- out[-1,] -# rownames(out) <- manynet::node_names(.data) -# colnames(out) <- c("E4", # co-K4 -# "I41","I40", # co-diamond -# "H4", # co-C4 -# "L42","L41","L40", # co-paw -# "D42","D40", # co-claw -# "U42","U41", # P4 -# "Y43","Y41", # claw -# "P43","P42","P41", # paw -# "04", # C4 -# "Z42","Z43", # diamond -# "X4") # K4 -# if(manynet::is_twomode(.data)) out <- out[,-c(8,9,14,15,16,18,19,20)] -# make_node_motif(out, .data) -# } #' @rdname motif_node +#' @section Tetrad census: +#' The nodal tetrad census counts the number of four-node configurations +#' that each node is embedded in. +#' The function returns a matrix with a special naming convention: +#' - E4 (aka co-K4): This is an empty set of four nodes; no ties +#' - I4 (aka co-diamond): This is a set of four nodes with just one tie +#' - H4 (aka co-C4): This set of four nodes includes two non-adjacent ties +#' - L4 (aka co-paw): This set of four nodes includes two adjacent ties +#' - D4 (aka co-claw): This set of four nodes includes three adjacent ties, +#' in the form of a triangle with one isolate +#' - U4 (aka P4, four-actor line): This set of four nodes includes three ties +#' arranged in a line +#' - Y4 (aka claw): This set of four nodes includes three ties all adjacent +#' to a single node +#' - P4 (aka paw, kite): This set of four nodes includes four ties arranged +#' as a triangle with an extra tie hanging off of one of the nodes +#' - C4 (aka bifan): This is a symmetric box or 4-cycle or set of shared choices +#' - Z4 (aka diamond): This resembles C4 but with an extra tie cutting across the box +#' - X4 (aka K4): This resembles C4 but with two extra ties cutting across the box; +#' a realisation of all possible ties +#' +#' Graphs of these motifs can be shown using +#' `plot(node_by_tetrad(ison_southern_women))`. +#' @references +#' ## On the tetrad census +#' Ortmann, Mark, and Ulrik Brandes. 2017. +#' “Efficient Orbit-Aware Triad and Quad Census in Directed and Undirected Graphs.” +#' \emph{Applied Network Science} 2(1):13. +#' \doi{10.1007/s41109-017-0027-2}. +#' +#' McMillan, Cassie, and Diane Felmlee. 2020. +#' "Beyond Dyads and Triads: A Comparison of Tetrads in Twenty Social Networks". +#' _Social Psychology Quarterly_ 83(4): 383-404. +#' \doi{10.1177/0190272520944151} #' @examples -#' node_by_quad(ison_southern_women) +#' node_by_tetrad(ison_southern_women) #' @export -node_by_quad <- function(.data){ +node_by_tetrad <- function(.data){ cmbs <- utils::combn(1:net_nodes(.data), 4) mat <- as_matrix(to_onemode(.data)) dd <- apply(cmbs, 2, function(x) c(sum(mat[x,x]), @@ -284,14 +286,17 @@ node_by_path <- function(.data){ #' Motifs at the network level #' #' @description -#' These functions include ways to take a census of the positions of nodes +#' These functions include ways to take a census of the graphlets #' in a network: #' #' - `net_by_dyad()` returns a census of dyad motifs in a network. #' - `net_by_triad()` returns a census of triad motifs in a network. +#' - `net_by_tetrad()` returns a census of tetrad motifs in a network. #' - `net_by_mixed()` returns a census of triad motifs that span #' a one-mode and a two-mode network. #' +#' See also \href{https://www.graphclasses.org/smallgraphs.html}{graph classes}. +#' #' @name motif_net #' @family motifs #' @inheritParams motif_node @@ -349,10 +354,43 @@ net_by_triad <- function(.data) { } #' @rdname motif_net +#' @section Tetrad census: +#' The tetrad census counts the number of four-node configurations in the network. +#' The function returns a matrix with a special naming convention: +#' - E4 (aka co-K4): This is an empty set of four nodes; no ties +#' - I4 (aka co-diamond): This is a set of four nodes with just one tie +#' - H4 (aka co-C4): This set of four nodes includes two non-adjacent ties +#' - L4 (aka co-paw): This set of four nodes includes two adjacent ties +#' - D4 (aka co-claw): This set of four nodes includes three adjacent ties, +#' in the form of a triangle with one isolate +#' - U4 (aka P4, four-actor line): This set of four nodes includes three ties +#' arranged in a line +#' - Y4 (aka claw): This set of four nodes includes three ties all adjacent +#' to a single node +#' - P4 (aka paw, kite): This set of four nodes includes four ties arranged +#' as a triangle with an extra tie hanging off of one of the nodes +#' - C4 (aka bifan): This is a symmetric box or 4-cycle or set of shared choices +#' - Z4 (aka diamond): This resembles C4 but with an extra tie cutting across the box +#' - X4 (aka K4): This resembles C4 but with two extra ties cutting across the box; +#' a realisation of all possible ties +#' +#' Graphs of these motifs can be shown using +#' `plot(net_by_tetrad(ison_southern_women))`. +#' @references +#' ## On the tetrad census +#' Ortmann, Mark, and Ulrik Brandes. 2017. +#' “Efficient Orbit-Aware Triad and Quad Census in Directed and Undirected Graphs.” +#' \emph{Applied Network Science} 2(1):13. +#' \doi{10.1007/s41109-017-0027-2}. +#' +#' McMillan, Cassie, and Diane Felmlee. 2020. +#' "Beyond Dyads and Triads: A Comparison of Tetrads in Twenty Social Networks". +#' _Social Psychology Quarterly_ 83(4): 383-404. +#' \doi{10.1177/0190272520944151} #' @examples -#' net_by_quad(ison_southern_women) +#' net_by_tetrad(ison_southern_women) #' @export -net_by_quad <- function(.data){ +net_by_tetrad <- function(.data){ if(missing(.data)) {expect_nodes(); .data <- .G()} cmbs <- utils::combn(1:net_nodes(.data), 4) mat <- as_matrix(to_onemode(.data)) @@ -391,7 +429,6 @@ net_by_quad <- function(.data){ out <- c(E4 = E4, I4 = I4, H4 = H4, L4 = L4, D4 = D4, U4 = U4, Y4 = Y4, P4 = P4, C4 = C4, Z4 = Z4, X4 = X4) - make_network_motif(out, .data) } diff --git a/R/zzz.R b/R/zzz.R index 6b19fb17..6624b965 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -5,8 +5,9 @@ if (!interactive()) return() options(manynet_verbosity = getOption("manynet_verbosity", "verbose")) - # options(manynet_theme = getOption("manynet_theme", "default")) + options(manynet_theme = getOption("manynet_theme", "default")) options(cli.theme = manynet_console_theme()) + options(cli.progress_clear = TRUE) # pkgs <- as.data.frame(utils::available.packages(utils::contrib.url(getOption("repos")))) # @@ -49,22 +50,45 @@ } -mnet_progress_step <- function(...){ +mnet_progress_step <- function(..., .envir = parent.frame()){ if(getOption("manynet_verbosity", default = "quiet")!="quiet") - cli::cli_progress_step(...) + cli::cli_progress_step(..., .envir = .envir) } -mnet_info <- function(...){ +mnet_progress_along <- function(..., .envir = parent.frame()){ if(getOption("manynet_verbosity", default = "quiet")!="quiet") - cli::cli_alert_info(...) + cli::cli_progress_along(..., .envir = .envir) } -mnet_unavailable <- function(...){ +mnet_progress_seq <- function(..., .envir = parent.frame()){ + if(getOption("manynet_verbosity", default = "quiet")!="quiet") + cli::cli_progress_along(seq.int(...), .envir = .envir, + total = ..., clear = TRUE) +} + +mnet_progress_nodes <- function(..., .envir = parent.frame()){ + if(getOption("manynet_verbosity", default = "quiet")!="quiet") + cli::cli_progress_along(seq.int(net_nodes(...)), .envir = .envir, + total = ..., clear = TRUE) +} + +mnet_info <- function(..., .envir = parent.frame()){ + if(getOption("manynet_verbosity", default = "quiet")!="quiet") + cli::cli_alert_info(paste(...), .envir = .envir) +} + +mnet_success <- function(..., .envir = parent.frame()){ + if(getOption("manynet_verbosity", default = "quiet")!="quiet") + cli::cli_alert_success(paste(...), .envir = .envir) +} + +mnet_unavailable <- function(..., .envir = parent.frame()){ if(getOption("manynet_verbosity", default = "quiet")!="quiet") cli::cli_abort(paste(..., "If you are interested in this feature,", "please vote for it or raise it as an issue at", - "{.url https://github.com/stocnet/manynet/issues}.")) + "{.url https://github.com/stocnet/manynet/issues}."), + .envir = .envir) } manynet_console_theme <- function(){ diff --git a/cran-comments.md b/cran-comments.md index 143846df..a6c532ca 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -9,6 +9,5 @@ 0 errors | 0 warnings | 0 notes -* Re errors on CRAN, this version fixes errors on Linux versions for which the {oaqc} package is not available -* Re previous submission, this version fixes a DOI and avoids an issue with {igraph} -* Fixed errors occurring in tests and examples when suggested packages excluded \ No newline at end of file +* Attempted to fix non ASCII strings warning +* Changes to avoid reverse dependency issues for igraph \ No newline at end of file diff --git a/data/fict_friends.rda b/data/fict_friends.rda new file mode 100644 index 00000000..b213707f Binary files /dev/null and b/data/fict_friends.rda differ diff --git a/data/fict_greys.rda b/data/fict_greys.rda new file mode 100644 index 00000000..5175c491 Binary files /dev/null and b/data/fict_greys.rda differ diff --git a/data/fict_lotr.rda b/data/fict_lotr.rda new file mode 100644 index 00000000..8c3afd4f Binary files /dev/null and b/data/fict_lotr.rda differ diff --git a/data/fict_potter.rda b/data/fict_potter.rda new file mode 100644 index 00000000..aa80136e Binary files /dev/null and b/data/fict_potter.rda differ diff --git a/data/fict_thrones.rda b/data/fict_thrones.rda new file mode 100644 index 00000000..aeead9d0 Binary files /dev/null and b/data/fict_thrones.rda differ diff --git a/data/irps_blogs.rda b/data/irps_blogs.rda new file mode 100644 index 00000000..236d0b5e Binary files /dev/null and b/data/irps_blogs.rda differ diff --git a/data/irps_books.rda b/data/irps_books.rda new file mode 100644 index 00000000..a57ea3c5 Binary files /dev/null and b/data/irps_books.rda differ diff --git a/data/irps_usgeo.rda b/data/irps_usgeo.rda new file mode 100644 index 00000000..f53472e4 Binary files /dev/null and b/data/irps_usgeo.rda differ diff --git a/data/irps_wwi.rda b/data/irps_wwi.rda new file mode 100644 index 00000000..814c3354 Binary files /dev/null and b/data/irps_wwi.rda differ diff --git a/data/ison_blogs.rda b/data/ison_blogs.rda deleted file mode 100644 index 903c17a8..00000000 Binary files a/data/ison_blogs.rda and /dev/null differ diff --git a/data/ison_books.rda b/data/ison_books.rda deleted file mode 100644 index 46114b4f..00000000 Binary files a/data/ison_books.rda and /dev/null differ diff --git a/data/ison_friends.rda b/data/ison_friends.rda deleted file mode 100644 index 879c4c66..00000000 Binary files a/data/ison_friends.rda and /dev/null differ diff --git a/data/ison_greys.rda b/data/ison_greys.rda deleted file mode 100644 index 1dd4ec16..00000000 Binary files a/data/ison_greys.rda and /dev/null differ diff --git a/data/ison_lotr.rda b/data/ison_lotr.rda deleted file mode 100644 index 345ea282..00000000 Binary files a/data/ison_lotr.rda and /dev/null differ diff --git a/data/ison_potter.rda b/data/ison_potter.rda deleted file mode 100644 index b5aa1dc8..00000000 Binary files a/data/ison_potter.rda and /dev/null differ diff --git a/data/ison_thrones.rda b/data/ison_thrones.rda deleted file mode 100644 index a743ef7a..00000000 Binary files a/data/ison_thrones.rda and /dev/null differ diff --git a/data/ison_usstates.rda b/data/ison_usstates.rda deleted file mode 100644 index 7b5ae284..00000000 Binary files a/data/ison_usstates.rda and /dev/null differ diff --git a/inst/tutorials/tutorial1/data.Rmd b/inst/tutorials/tutorial1/data.Rmd index 1582e537..5816b5cb 100644 --- a/inst/tutorials/tutorial1/data.Rmd +++ b/inst/tutorials/tutorial1/data.Rmd @@ -633,7 +633,7 @@ mean(as_matrix(s_women)) ``` ```{r womenweightsq, purl=FALSE} -question("2.438849 is...", +question("2.316547 is...", answer("the average frequency of events shared by women who shared any events.", correct = TRUE), answer("the average frequency of events shared by women."), diff --git a/inst/tutorials/tutorial4/community.Rmd b/inst/tutorials/tutorial4/community.Rmd index 5d55db3e..5d84ecc9 100644 --- a/inst/tutorials/tutorial4/community.Rmd +++ b/inst/tutorials/tutorial4/community.Rmd @@ -15,6 +15,7 @@ library(learnr) library(patchwork) library(manynet) knitr::opts_chunk$set(echo = FALSE) +clear_glossary() friends <- to_uniplex(ison_algebra, "friends") social <- to_uniplex(ison_algebra, "social") @@ -24,6 +25,23 @@ tasks <- to_uniplex(ison_algebra, "tasks") ## Setting up +In the last tutorial, we looked at network centrality and centralisation. +Nodal centrality is often thought to be an expression of structural inequality. +But nodes don't always seek to differentiate themselves in a network. +Sometimes they are interested in being part of a group. +In this tutorial, we're going to consider various ways in which 'groupness' +might be examined. + +gif of man not knowing how to study + + + + + + + + + The data we're going to use here, "ison_algebra", is included in the `{manynet}` package. Do you remember how to call the data? Can you find out some more information about it? @@ -168,7 +186,8 @@ and $|N|$ and $|M|$ are the number of nodes in the first and second mode respect question("Which equation is used for measuring density for a directed network:", answer("A", correct = TRUE, - message = learnr::random_praise()), + message = 'gif of a thumbs up' +), answer("B", message = "This is the equation for an undirected network."), answer("C", @@ -177,7 +196,9 @@ question("Which equation is used for measuring density for a directed network:", ) ``` - +One can calculate the density of the network using the number of nodes +and the number of ties using the functions `net_nodes()` and `net_ties()`, +respectively: ```{r dens-explicit, exercise=TRUE, exercise.setup = "separatingnets", purl = FALSE} @@ -188,7 +209,8 @@ question("Which equation is used for measuring density for a directed network:", net_ties(tasks)/(net_nodes(tasks)*(net_nodes(tasks)-1)) ``` -but we can also just use the `{manynet}` function... +but we can also just use the `{manynet}` function for calculating the density, +which always uses the equation appropriate for the type of network... ```{r dens, exercise=TRUE, exercise.setup = "separatingnets", purl = FALSE} @@ -208,7 +230,7 @@ question("Is this network's density high or low in absolute terms?", message = "The closer the value is to 1, the more dense the network and the more cohesive the network is as a whole."), answer("Low", correct = TRUE, - message = "The closer the value is to 0, the sparser the network and the less cohesive the network is as a whole. But this is still quite typical density for a relatively small, social network like this one."), + message = 'The closer the value is to 0, the sparser the network and the less cohesive the network is as a whole. But this is still quite typical density for a relatively small, social network like this one.

gif of i knew it'), allow_retry = TRUE ) ``` @@ -218,7 +240,23 @@ the network as a whole. ## Closure -Next let's calculate _reciprocity_ in the task network. +In this section we're going to move from generalised measures of cohesion, +like density, to more localised measures of cohesion. +These are not only measures of cohesion though, +but are also often associated with certain mechanisms of closure. +Closure involves ties being more likely because other ties are present. +There are two common examples of this in the literature: +`gloss("reciprocity")`, where a directed tie is often likely to prompt a reciprocating tie, +and `gloss("transitivity")`, where a directed two-path is likely to be shortened +by an additional arc connecting the first and third nodes on that path. + +gif of ah ha gotcha + +### Reciprocity + +First, let's calculate +`r gloss("reciprocity")` +in the task network. While one could do this by hand, it's more efficient to do this using the `{manynet}` package. Can you guess the correct name of the function? @@ -247,7 +285,11 @@ and yet node 16 is both the sender and receiver of most of the task activity. So our reciprocity measure has taught us something about this network that might not have been obvious visually. -And let's calculate _transitivity_ in the task network. +### Transitivity + +And let's calculate +`r gloss("transitivity")` +in the task network. Again, can you guess the correct name of this function? ```{r trans, exercise=TRUE, exercise.setup = "separatingnets", purl = FALSE} @@ -262,11 +304,12 @@ net_transitivity(tasks) ```{r trans-interp, echo=FALSE, purl = FALSE} question("What can we say about task closure in this network? Choose all that apply.", answer("Transitivity for the task network is 0.568", - correct = TRUE), + correct = TRUE, + message = 'gif of cool cool cool'), answer("Transitivity for the task network is -0.568", message = "Transivitity must be between 0 and 1."), answer("Transitivity is quite low in this network", - message = "Transitivity is usually around 0.3 in most social networks."), + message = "Transitivity is often around 0.3 in most social networks."), answer("Transitivity is quite high in this network", correct = TRUE), answer("Transitivity is likely higher in the task network than the friendship network", @@ -276,13 +319,158 @@ question("What can we say about task closure in this network? Choose all that ap ) ``` +## Projection + +### A two-mode network + +The next dataset, 'ison_southern_women', is also available in `{manynet}`. +Let's load and graph the data. + +```{r setup-women, exercise=TRUE, exercise.setup = "data", purl = FALSE} + +``` + +```{r setup-women-hint-1, purl = FALSE} +# let's load the data and analyze it +data("ison_southern_women") +ison_southern_women +``` + +```{r setup-women-hint-2, purl = FALSE} +graphr(ison_southern_women, node_color = "type") +graphr(ison_southern_women, "railway", node_color = "type") +``` + +```{r setup-women-solution} +data("ison_southern_women") +ison_southern_women +graphr(ison_southern_women, node_color = "type") +``` + +### Project two-mode network into two one-mode networks + +Now what if we are only interested in one part of the network? +For that, we can obtain a 'projection' of the two-mode network. +There are two ways of doing this. +The hard way... + +```{r hardway, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} + +``` + +```{r hardway-solution} +twomode_matrix <- as_matrix(ison_southern_women) +women_matrix <- twomode_matrix %*% t(twomode_matrix) +event_matrix <- t(twomode_matrix) %*% twomode_matrix +``` + +Or the easy way: + +```{r easyway, exercise=TRUE, exercise.setup = "setup-women"} +# women-graph +# to_mode1(): Results in a weighted one-mode object that retains the row nodes from +# a two-mode object, and weights the ties between them on the basis of their joint +# ties to nodes in the second mode (columns) + +women_graph <- to_mode1(ison_southern_women) +graphr(women_graph) + +# note that projection `to_mode1` involves keeping one type of nodes +# this is different from to_uniplex above, which keeps one type of ties in the network + +# event-graph +# to_mode2(): Results in a weighted one-mode object that retains the column nodes from +# a two-mode object, and weights the ties between them on the basis of their joint ties +# to nodes in the first mode (rows) + +event_graph <- to_mode2(ison_southern_women) +graphr(event_graph) +``` + +`{manynet}` also includes several other options for how to construct the projection. +The default ("count") might be interpreted as indicating the degree of +opportunity between nodes that comes from sharing ties to the other mode. +"jaccard" divides this count by the number of nodes in the other mode that +to which either of the nodes are tied. +It can thus be interpreted as opportunity weighted by participation. +"rand" instead counts both shared ties and shared absences, +and can thus be interpreted as the degree of behavioural mirroring between the +nodes. +Lastly, "pearson" (Pearson's coefficient) and "yule" (Yule's Q) produce +correlations in ties for valued and binary data respectively. + +```{r otherway, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} + +``` + +```{r otherway-solution} +to_mode2(ison_southern_women, similarity = "jaccard") +to_mode2(ison_southern_women, similarity = "rand") +to_mode2(ison_southern_women, similarity = "pearson") +to_mode2(ison_southern_women, similarity = "yule") +``` + +Let's return to the question of closure. +First try one of the closure measures we have already treated that gives us +a sense of shared partners for one-mode networks. +Then compare this with `net_equivalency()`, which can be used on the original +two-mode network. + +```{r twomode-cohesion, exercise=TRUE, exercise.setup = "easyway", purl = FALSE} + +``` + +```{r twomode-cohesion-hint-1, purl = FALSE} +# net_transitivity(): Calculate transitivity in a network + +net_transitivity(women_graph) +net_transitivity(event_graph) +``` + +```{r twomode-cohesion-hint-2, purl = FALSE} +# net_equivalency(): Calculate equivalence or reinforcement in a (usually two-mode) network + +net_equivalency(ison_southern_women) +``` + +```{r twomode-cohesion-solution} +net_transitivity(women_graph) +net_transitivity(event_graph) +net_equivalency(ison_southern_women) +``` + +```{r equil-interp, echo=FALSE, purl = FALSE} +question("What do we learn from this? Choose all that apply.", + answer("Transitivity in the women projection is very high.", + correct = TRUE), + answer("Transitivity in the event projection is very high.", + correct = TRUE), + answer("Equivalence for the two-mode Southern Women dataset is moderate.", + correct = TRUE, + message = 'gif of you just wrinkled my brain'), + answer("Transitivity will often be very high in projected networks.", + correct = TRUE), + answer("Projection obscures which women are members of which events and vice versa.", + correct = TRUE), + # random_answer_order = TRUE, + allow_retry = TRUE +) +``` + +Try to explain in no more than a paragraph why projection can lead to misleading transitivity measures and what some consequences of this might be. + + + ## Components Now let's look at the friendship network, 'friends'. -We're interested here in how many _components_ there are. +We're interested here in how many +`r gloss("components", "component")` +there are. By default, the `net_components()` function will return the number of _strong_ components for directed networks. -For _weak_ components, you will need to first make the network undirected. +For _weak_ components, you will need to first make the network +`r gloss("undirected")`. Remember the difference between weak and strong components? ```{r weak-strong, echo = FALSE, purl = FALSE} @@ -327,7 +515,7 @@ question("How many components are there?", message = "There are 3 _weak_ components.", correct = TRUE), answer("4", - message = "There are 4 _strong_ components.", + message = 'There are 4 _strong_ components. gif of two thumbs up', correct = TRUE), answer("5", message = "There are fewer than 5 components."), @@ -382,6 +570,113 @@ question("Why is there a difference between the weak and strong components resul ) ``` +## Factions + +Components offer a precise way of understanding groups in a network. +However, they can also ignore some 'groupiness' that is obvious to even a +cursory examination of the graph. +The `irps_blogs` network concerns the url links between political blogs +in the 2004 election. +It is a big network (you can check below). +In our experience, it can take a few seconds + +```{r blogsize, exercise = TRUE} +# This is a large network +net_nodes(irps_blogs) +# Let's concentrate on just a sample of 490 +blogs <- delete_nodes(irps_blogs, sample(1:1490, 1000)) +graphr(blogs) +``` + +But are they all actually linked? +Even among the smaller sample, there seems to be a number of isolates. +We can calculate the number of isolates by simply summing `node_is_isolate()`. + +```{r blogisolates, exercise = TRUE, exercise.setup = "blogsize"} +sum(node_is_isolate(blogs)) +``` + +Since there are many isolates, there will be many components, +even if we look at weak components and not just strong components. + +```{r blogcomp, exercise = TRUE, exercise.setup = "blogsize"} +net_components(blogs) +net_components(to_undirected(blogs)) +``` + +### Giant component + +So, it looks like most of the (weak) components are due to isolates! +How do we concentrate on the main component of this network? +Well, the main/largest component in a network is called the +`r gloss("giant component", "giant")`. + +```{r blogtogiant, exercise=TRUE, warning=FALSE, fig.width=9, exercise.setup = "blogsize"} +blogs <- blogs %>% to_giant() +sum(node_is_isolate(blogs)) +graphr(blogs) +``` + +Finally, we have a single 'giant' component to examine. +However, now we have a different kind of challenge: +everything is one big hairball. +And yet, if we think about what we might expect of the structure of a network +of political blogs, we might not think it is so undifferentiated. +We might hypothesise that, despite the _graphical_ presentation of a hairball, +there is actually a reasonable partition of the network into two factions. + +### Finding a partition + +To find a partition in a network, we use the `node_in_partition()` function. +All `node_in_*()` functions return a string vector the length of the number +of nodes in the network. +It is a string vector because this is how a categorical result is obtained. +We can assign the result of this function to the nodes in the network +(because it is the length of the nodes in the network), +and graph the network using this result. + +```{r bloggraph, exercise=TRUE, exercise.setup = "blogtogiant", warning=FALSE, fig.width=9} +blogs %>% mutate_nodes(part = node_in_partition()) %>% + graphr(node_color = "part") +``` + +We see from this graph that indeed there seems to be an obvious separation +between the left and right 'hemispheres' of the network. + +## Modularity + +But what is the 'fit' of this assignment of the blog nodes into two partitions? +The most common measure of the fit of a community assignment in a network is +modularity. + +```{r blogmod, exercise=TRUE, exercise.setup = "blogtogiant"} +net_modularity(blogs, membership = node_in_partition(blogs)) +``` + +Remember that modularity ranges between 1 and -1. +How can we interpret this result? + +While the partition algorithm is useful for deriving a partition of the network +into the number of factions assigned, +it is still an algorithm that tries to maximise modularity. +Other times we might instead have an empirically collected grouping, +and we are keen to see how 'modular' the network is around this attribute. +This only works on categorical attributes, of course, +but is otherwise quite flexible. + +```{r blogmodassign, exercise=TRUE, exercise.setup = "blogtogiant", warning=FALSE, fig.width=9} +graphr(blogs, node_color = "Leaning") +net_modularity(blogs, membership = node_attribute(blogs, "Leaning")) +``` + +gif of Chevy Chase saying plot twist + +How interesting. +Perhaps the partitioning algorithm is not the algorithm that maximises +modularity after all... +Perhaps we need to look further and see whether there is another solution here +that returns an even greater modularity criterion. + ## Communities Ok, the friendship network has 3-4 components, but how many 'groups' are there? @@ -647,132 +942,28 @@ question("What is the difference between communities and components?", allow_retry = TRUE) ``` -## Projection - -### A two-mode network - -The next dataset, 'ison_southern_women', is also available in `{manynet}`. -Let's load and graph the data. - -```{r setup-women, exercise=TRUE, exercise.setup = "data", purl = FALSE} - -``` - -```{r setup-women-hint-1, purl = FALSE} -# let's load the data and analyze it -data("ison_southern_women") -ison_southern_women -``` - -```{r setup-women-hint-2, purl = FALSE} -graphr(ison_southern_women, node_color = "type") -graphr(ison_southern_women, "railway", node_color = "type") -``` - -```{r setup-women-solution} -data("ison_southern_women") -ison_southern_women -graphr(ison_southern_women, node_color = "type") -``` - -### Project two-mode network into two one-mode networks - -Now what if we are only interested in one part of the network? -For that, we can obtain a 'projection' of the two-mode network. -There are two ways of doing this. -The hard way... - -```{r hardway, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} - -``` - -```{r hardway-solution} -twomode_matrix <- as_matrix(ison_southern_women) -women_matrix <- twomode_matrix %*% t(twomode_matrix) -event_matrix <- t(twomode_matrix) %*% twomode_matrix -``` - -Or the easy way: - -```{r easyway, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} - -``` - -```{r easyway-hint-1, purl = FALSE} -# women-graph -# to_mode1(): Results in a weighted one-mode object that retains the row nodes from -# a two-mode object, and weights the ties between them on the basis of their joint -# ties to nodes in the second mode (columns) - -women_graph <- to_mode1(ison_southern_women) -graphr(women_graph) +## Free play -# note that projection `to_mode1` involves keeping one type of nodes -# this is different from to_uniplex above, which keeps one type of ties in the network -``` +gif of two dancing -```{r easyway-hint-2, purl = FALSE} -# event-graph -# to_mode2(): Results in a weighted one-mode object that retains the column nodes from -# a two-mode object, and weights the ties between them on the basis of their joint ties -# to nodes in the first mode (rows) +We've looked here at the `irps_blogs` dataset. +Now have a go at the `irps_books` dataset. +What is the density? Does it make sense to investigate reciprocity, +transitivity, or equivalence? How can we interpret the results? +How many components in the network? Is there a strong factional structure? +Which community detection algorithm returns the highest modularity score, +or corresponds best to what is in the data or what you see in the graph? -event_graph <- to_mode2(ison_southern_women) -graphr(event_graph) +```{r freeplay, exercise = TRUE, fig.width=9} +irps_books ``` -```{r easyway-solution} -women_graph <- to_mode1(ison_southern_women) -graphr(women_graph) -event_graph <- to_mode2(ison_southern_women) -graphr(event_graph) -``` + -`{manynet}` also includes several other options for how to construct the projection. -Please see the help file for more details. - -```{r otherway, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} - -``` - -```{r otherway-solution} -graphr(to_mode2(ison_southern_women, similarity = "jaccard")) + ggtitle("Jaccard") + -graphr(to_mode2(ison_southern_women, similarity = "rand")) + ggtitle("Rand") + -graphr(to_mode2(ison_southern_women, similarity = "pearson")) + ggtitle("Pearson") + -graphr(to_mode2(ison_southern_women, similarity = "yule")) + ggtitle("Yule's Q") -``` - -Which women/events 'bind' which events/women? -Let's return to the question of cohesion. - -```{r twomode-cohesion, exercise=TRUE, exercise.setup = "setup-women", purl = FALSE} - -``` - -```{r twomode-cohesion-hint-1, purl = FALSE} -# net_equivalency(): Calculate equivalence or reinforcement in a (usually two-mode) network - -net_equivalency(ison_southern_women) -``` - -```{r twomode-cohesion-hint-2, purl = FALSE} -# net_transitivity(): Calculate transitivity in a network - -net_transitivity(women_graph) -net_transitivity(event_graph) -``` - -```{r twomode-cohesion-solution} -net_equivalency(ison_southern_women) -net_transitivity(women_graph) -net_transitivity(event_graph) -``` +## Glossary -What do we learn from this? +gif of annie raising her hand -## Task/Unit Test +Here are some of the terms that we have covered in this module: -1. Produce a plot comparing 3 community detection procedures used here on a -(women) projection of the 'ison_southern_women' dataset. Identify which you prefer, and explain why. -2. Explain in no more than a paragraph why projection can lead to misleading transitivity measures. -3. Explain in no more than a paragraph how structural balance might lead to group identity. +`r print_glossary()` diff --git a/inst/tutorials/tutorial4/community.html b/inst/tutorials/tutorial4/community.html index 65156ab7..14a3665a 100644 --- a/inst/tutorials/tutorial4/community.html +++ b/inst/tutorials/tutorial4/community.html @@ -112,6 +112,17 @@

Setting up

+

In the last tutorial, we looked at network centrality and +centralisation. Nodal centrality is often thought to be an expression of +structural inequality. But nodes don’t always seek to differentiate +themselves in a network. Sometimes they are interested in being part of +a group. In this tutorial, we’re going to consider various ways in which +‘groupness’ might be examined.

+

gif of man not knowing how to study

+ + + +

The data we’re going to use here, “ison_algebra”, is included in the {manynet} package. Do you remember how to call the data? Can you find out some more information about it?

@@ -273,6 +284,9 @@

Density

+

One can calculate the density of the network using the number of +nodes and the number of ties using the functions +net_nodes() and net_ties(), respectively:

@@ -285,7 +299,9 @@

Density

# calculating network density manually according to equation
 net_ties(tasks)/(net_nodes(tasks)*(net_nodes(tasks)-1))
-

but we can also just use the {manynet} function…

+

but we can also just use the {manynet} function for +calculating the density, which always uses the equation appropriate for +the type of network…

@@ -313,10 +329,24 @@

Density

Closure

-

Next let’s calculate reciprocity in the task network. While -one could do this by hand, it’s more efficient to do this using the -{manynet} package. Can you guess the correct name of the -function?

+

In this section we’re going to move from generalised measures of +cohesion, like density, to more localised measures of cohesion. These +are not only measures of cohesion though, but are also often associated +with certain mechanisms of closure. Closure involves ties being more +likely because other ties are present. There are two common examples of +this in the literature: gloss("reciprocity"), where a +directed tie is often likely to prompt a reciprocating tie, and +gloss("transitivity"), where a directed two-path is likely +to be shortened by an additional arc connecting the first and third +nodes on that path.

+

gif of ah ha gotcha

+
+

Reciprocity

+

First, let’s calculate + +reciprocity in the task network. While one could do this +by hand, it’s more efficient to do this using the {manynet} +package. Can you guess the correct name of the function?

@@ -343,8 +373,13 @@

Closure

node 16 is both the sender and receiver of most of the task activity. So our reciprocity measure has taught us something about this network that might not have been obvious visually.

-

And let’s calculate transitivity in the task network. Again, -can you guess the correct name of this function?

+
+
+

Transitivity

+

And let’s calculate + +transitivity in the task network. Again, can you guess the +correct name of this function?

@@ -365,14 +400,166 @@

Closure

+
+
+

Projection

+
+

A two-mode network

+

The next dataset, ‘ison_southern_women’, is also available in +{manynet}. Let’s load and graph the data.

+
+ +
+
+
# let's load the data and analyze it
+data("ison_southern_women")
+ison_southern_women
+
+
+
graphr(ison_southern_women, node_color = "type")
+graphr(ison_southern_women, "railway", node_color = "type")
+
+
+
data("ison_southern_women")
+ison_southern_women
+graphr(ison_southern_women, node_color = "type")
+
+
+
+

Project two-mode network into two one-mode networks

+

Now what if we are only interested in one part of the network? For +that, we can obtain a ‘projection’ of the two-mode network. There are +two ways of doing this. The hard way…

+
+ +
+
+
twomode_matrix <- as_matrix(ison_southern_women)
+women_matrix <- twomode_matrix %*% t(twomode_matrix)
+event_matrix <- t(twomode_matrix) %*% twomode_matrix
+
+

Or the easy way:

+
+
# women-graph
+# to_mode1(): Results in a weighted one-mode object that retains the row nodes from
+# a two-mode object, and weights the ties between them on the basis of their joint
+# ties to nodes in the second mode (columns)
+
+women_graph <- to_mode1(ison_southern_women)
+graphr(women_graph)
+
+# note that projection `to_mode1` involves keeping one type of nodes
+# this is different from to_uniplex above, which keeps one type of ties in the network
+
+# event-graph
+# to_mode2(): Results in a weighted one-mode object that retains the column nodes from
+# a two-mode object, and weights the ties between them on the basis of their joint ties
+# to nodes in the first mode (rows)
+
+event_graph <- to_mode2(ison_southern_women)
+graphr(event_graph)
+ +
+

{manynet} also includes several other options for how to +construct the projection. The default (“count”) might be interpreted as +indicating the degree of opportunity between nodes that comes from +sharing ties to the other mode. “jaccard” divides this count by the +number of nodes in the other mode that to which either of the nodes are +tied. It can thus be interpreted as opportunity weighted by +participation. “rand” instead counts both shared ties and shared +absences, and can thus be interpreted as the degree of behavioural +mirroring between the nodes. Lastly, “pearson” (Pearson’s coefficient) +and “yule” (Yule’s Q) produce correlations in ties for valued and binary +data respectively.

+
+ +
+
+
to_mode2(ison_southern_women, similarity = "jaccard")
+to_mode2(ison_southern_women, similarity = "rand")
+to_mode2(ison_southern_women, similarity = "pearson")
+to_mode2(ison_southern_women, similarity = "yule")
+
+

Let’s return to the question of closure. First try one of the closure +measures we have already treated that gives us a sense of shared +partners for one-mode networks. Then compare this with +net_equivalency(), which can be used on the original +two-mode network.

+
+ +
+
+
# net_transitivity(): Calculate transitivity in a network
+
+net_transitivity(women_graph)
+net_transitivity(event_graph)
+
+
+
# net_equivalency(): Calculate equivalence or reinforcement in a (usually two-mode) network
+
+net_equivalency(ison_southern_women)
+
+
+
net_transitivity(women_graph)
+net_transitivity(event_graph)
+net_equivalency(ison_southern_women)
+
+
+
+
+
+
+ +
+
+

Try to explain in no more than a paragraph why projection can lead to +misleading transitivity measures and what some consequences of this +might be.

+ +
+

Components

Now let’s look at the friendship network, ‘friends’. We’re interested -here in how many components there are. By default, the +here in how many + +components there are. By default, the net_components() function will return the number of strong components for directed networks. For weak -components, you will need to first make the network undirected. Remember -the difference between weak and strong components?

+components, you will need to first make the network + +undirected . Remember the difference between weak and +strong components?

@@ -464,6 +651,117 @@

Components

+
+

Factions

+

Components offer a precise way of understanding groups in a network. +However, they can also ignore some ‘groupiness’ that is obvious to even +a cursory examination of the graph. The irps_blogs network +concerns the url links between political blogs in the 2004 election. It +is a big network (you can check below). In our experience, it can take a +few seconds

+
+
# This is a large network
+net_nodes(irps_blogs)
+# Let's concentrate on just a sample of 490
+blogs <- delete_nodes(irps_blogs, sample(1:1490, 1000))
+graphr(blogs)
+ +
+

But are they all actually linked? Even among the smaller sample, +there seems to be a number of isolates. We can calculate the number of +isolates by simply summing node_is_isolate().

+
+
sum(node_is_isolate(blogs))
+ +
+

Since there are many isolates, there will be many components, even if +we look at weak components and not just strong components.

+
+
net_components(blogs)
+net_components(to_undirected(blogs))
+ +
+
+

Giant component

+

So, it looks like most of the (weak) components are due to isolates! +How do we concentrate on the main component of this network? Well, the +main/largest component in a network is called the + +giant component .

+
+
blogs <- blogs %>% to_giant()
+sum(node_is_isolate(blogs))
+graphr(blogs)
+ +
+

Finally, we have a single ‘giant’ component to examine. However, now +we have a different kind of challenge: everything is one big hairball. +And yet, if we think about what we might expect of the structure of a +network of political blogs, we might not think it is so +undifferentiated. We might hypothesise that, despite the +graphical presentation of a hairball, there is actually a +reasonable partition of the network into two factions.

+
+
+

Finding a partition

+

To find a partition in a network, we use the +node_in_partition() function. All node_in_*() +functions return a string vector the length of the number of nodes in +the network. It is a string vector because this is how a categorical +result is obtained. We can assign the result of this function to the +nodes in the network (because it is the length of the nodes in the +network), and graph the network using this result.

+
+
blogs %>% mutate_nodes(part = node_in_partition()) %>% 
+  graphr(node_color = "part")
+ +
+

We see from this graph that indeed there seems to be an obvious +separation between the left and right ‘hemispheres’ of the network.

+
+
+
+

Modularity

+

But what is the ‘fit’ of this assignment of the blog nodes into two +partitions? The most common measure of the fit of a community assignment +in a network is modularity.

+
+
net_modularity(blogs, membership = node_in_partition(blogs))
+ +
+

Remember that modularity ranges between 1 and -1. How can we +interpret this result?

+

While the partition algorithm is useful for deriving a partition of +the network into the number of factions assigned, it is still an +algorithm that tries to maximise modularity. Other times we might +instead have an empirically collected grouping, and we are keen to see +how ‘modular’ the network is around this attribute. This only works on +categorical attributes, of course, but is otherwise quite flexible.

+
+
graphr(blogs, node_color = "Leaning")
+net_modularity(blogs, membership = node_attribute(blogs, "Leaning"))
+ +
+

gif of Chevy Chase saying plot twist

+

How interesting. Perhaps the partitioning algorithm is not the +algorithm that maximises modularity after all… Perhaps we need to look +further and see whether there is another solution here that returns an +even greater modularity criterion.

+

Communities

Ok, the friendship network has 3-4 components, but how many ‘groups’ @@ -746,203 +1044,114 @@

Fast Greedy

-
-

Projection

-
-

A two-mode network

-

The next dataset, ‘ison_southern_women’, is also available in -{manynet}. Let’s load and graph the data.

-
- -
-
-
# let's load the data and analyze it
-data("ison_southern_women")
-ison_southern_women
-
-
-
graphr(ison_southern_women, node_color = "type")
-graphr(ison_southern_women, "railway", node_color = "type")
-
-
-
data("ison_southern_women")
-ison_southern_women
-graphr(ison_southern_women, node_color = "type")
-
-
-
-

Project two-mode network into two one-mode networks

-

Now what if we are only interested in one part of the network? For -that, we can obtain a ‘projection’ of the two-mode network. There are -two ways of doing this. The hard way…

-
- -
-
-
twomode_matrix <- as_matrix(ison_southern_women)
-women_matrix <- twomode_matrix %*% t(twomode_matrix)
-event_matrix <- t(twomode_matrix) %*% twomode_matrix
-
-

Or the easy way:

-
+

Free play

+

gif of two dancing

+

We’ve looked here at the irps_blogs dataset. Now have a +go at the irps_books dataset. What is the density? Does it +make sense to investigate reciprocity, transitivity, or equivalence? How +can we interpret the results? How many components in the network? Is +there a strong factional structure? Which community detection algorithm +returns the highest modularity score, or corresponds best to what is in +the data or what you see in the graph?

+
+
irps_books
-
-
# women-graph
-# to_mode1(): Results in a weighted one-mode object that retains the row nodes from
-# a two-mode object, and weights the ties between them on the basis of their joint
-# ties to nodes in the second mode (columns)
+
+
+
+

Glossary

+

gif of annie raising her hand

+

Here are some of the terms that we have covered in this module:

+
+
+Component +
+
+A component is a connected subgraph not part of a larger connected +subgraph. +
+
+Giant +
+
+The giant component is the component that includes the most nodes in the +network. +
+
+Reciprocity +
+
+A measure of how often nodes in a directed network are mutually linked. +
+
+Transitivity +
+
+Triadic closure is where if the connections A-B and A-C exist among +three nodes, there is a tendency for B-C also to be formed. +
+
+Undirected +
+
+An undirected network is one in which tie direction is undefined. +
+
+

+ -

-
-
graphr(to_mode2(ison_southern_women, similarity = "jaccard")) + ggtitle("Jaccard") +
-graphr(to_mode2(ison_southern_women, similarity = "rand")) + ggtitle("Rand") +
-graphr(to_mode2(ison_southern_women, similarity = "pearson")) + ggtitle("Pearson") +
-graphr(to_mode2(ison_southern_women, similarity = "yule")) + ggtitle("Yule's Q")
-
-

Which women/events ‘bind’ which events/women? Let’s return to the -question of cohesion.

-
- -
-
-
# net_equivalency(): Calculate equivalence or reinforcement in a (usually two-mode) network
-
-net_equivalency(ison_southern_women)
-
-
-
# net_transitivity(): Calculate transitivity in a network
-
-net_transitivity(women_graph)
-net_transitivity(event_graph)
-
-
-
net_equivalency(ison_southern_women)
-net_transitivity(women_graph)
-net_transitivity(event_graph)
-
-

What do we learn from this?

-
-
-
-

Task/Unit Test

-
    -
  1. Produce a plot comparing 3 community detection procedures used here -on a (women) projection of the ‘ison_southern_women’ dataset. Identify -which you prefer, and explain why.
  2. -
  3. Explain in no more than a paragraph why projection can lead to -misleading transitivity measures.
  4. -
  5. Explain in no more than a paragraph how structural balance might -lead to group identity. - +friends <- to_uniplex(ison_algebra, "friends") +social <- to_uniplex(ison_algebra, "social") +tasks <- to_uniplex(ison_algebra, "tasks") + + + - - - - + - + + - - + - + + - - + - + + - - + - + + - - + - + + - - + - + + - - + - + + - - + - + + - - + - + + - - + - - - - - - + - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + @@ -1584,17 +2415,18 @@

    Task/Unit Test

    - - - - - - - - - - - - - - - - - - - - -
  6. -
+

diff --git a/inst/tutorials/tutorial5/position.Rmd b/inst/tutorials/tutorial5/position.Rmd index cef5f349..c4f8e53a 100644 --- a/inst/tutorials/tutorial5/position.Rmd +++ b/inst/tutorials/tutorial5/position.Rmd @@ -23,6 +23,8 @@ tasks <- to_uniplex(ison_algebra, "tasks") ## Setting up +gif of rick and morty characters hanging out with themselves + For this session, we're going to use the "ison_algebra" dataset included in the `{manynet}` package. Do you remember how to call the data? Can you find out some more information about it via its help file? @@ -77,24 +79,18 @@ ____ <- to_uniplex(ison_algebra, _____) ``` ```{r separatingnets-hint-4, purl = FALSE} -# Now, let's compare the each attribute's graph, side-by-side by using "+" -# Note: using "/" after each graph will order them vertically; however, it might not be best way -# See for example: -gfriend <- graphr(friends) + ggtitle("Friendship") -gfriend + gsocial + gtask +graphr(friends) + ggtitle("Friendship") ``` ```{r separatingnets-solution} friends <- to_uniplex(ison_algebra, "friends") -gfriend <- graphr(friends) + ggtitle("Friendship") +graphr(friends) + ggtitle("Friendship") social <- to_uniplex(ison_algebra, "social") -gsocial <- graphr(social) + ggtitle("Social") +graphr(social) + ggtitle("Social") tasks <- to_uniplex(ison_algebra, "tasks") -gtask <- graphr(tasks) + ggtitle("Task") - -gfriend + gsocial + gtask +graphr(tasks) + ggtitle("Task") ``` Note also that these are weighted networks. @@ -120,18 +116,21 @@ question("If we interpret ties with higher weights as strong ties, and lesser we Our first question for this network, is where innovation and creative ideas might be expected to appear. +There are a number of theories that associate innovation or novelty with +structural position. ```{r structinnov-qa, echo=FALSE, purl = FALSE} question("Which network concepts are associated with innovation?", answer("Structural holes", correct = TRUE, - message = learnr::random_praise()), + message = "Being positioned in a structural hole is said to be a brokerage position that brings with it information arbitrage possibilities."), answer("Structural folds", - correct = TRUE), + correct = TRUE, + message = "Being positioned in a structural fold, with in-group membership in multiple groups, can provide not only information arbitrage possibilities, but also the standing in the target group to introduce novelty successfully."), answer("Structural balance", message = learnr::random_encouragement()), answer("Structural equivalence", - message = learnr::random_encouragement()), + message = 'gif of a morty assassinating another morty'), answer("Structuralism", message = learnr::random_encouragement()), random_answer_order = TRUE, @@ -227,6 +226,8 @@ about where innovation might occur within this network? ## Structural Equivalence +gif of rick multiplying + Next we might ask ourselves what (other) roles there are in the network? We want to know who plays what role in this algebra class. Let us begin with structural equivalence. @@ -491,6 +492,8 @@ but here it essentially just reports nodes' identity. ## Blockmodelling +gif of mortys in a block parade + ### Summarising profiles Ok, so now we have a result from establishing nodes' membership in structurally equivalent classes. @@ -506,6 +509,8 @@ While this plot adds the structurally equivalent classes information to our earl it doesn't really help us understand how the classes relate. That is, we might be less interested in how the individuals in the different classes relate, and more interested in how the different classes relate in aggregate. +gif of mortys learning about roles + One option that can be useful for characterising what the profile of ties (partners) is for each position/equivalence class is to use `summary()`. @@ -535,7 +540,7 @@ it takes a bit to look through what varies between the different classes as 'blocked'. But only four rows (the four structurally equivalent classes, according to the default). -Another way to do this is to plot the blockmodel as a whole. +Another way to do this is to plot the `gloss("blockmodel")` as a whole. Passing the `plot()` function an adjacency/incidence matrix along with a membership vector allows the matrix to be sorted and framed (without the membership vector, just the adjacency/incidence matrix is plotted): @@ -558,11 +563,11 @@ plot(as_matrix(alge), membership = node_in_structural(alge)) # plot the blockmodel for the friends, tasks, and social networks separately -plot(as_matrix(friends), - membership = node_in_structural(alge)) + -plot(as_matrix(tasks), - membership = node_in_structural(alge)) + -plot(as_matrix(social), +plot(as_matrix(to_uniplex(alge, "friends")), + membership = node_in_structural(alge)) +plot(as_matrix(to_uniplex(alge, "tasks")), + membership = node_in_structural(alge)) +plot(as_matrix(to_uniplex(alge, "social")), membership = node_in_structural(alge)) ``` @@ -572,17 +577,17 @@ This can help us interpret the general relationships between classes. For example, when we plot the friends, tasks, and social networks using the structural equivalence results, we might characterise them like so: -- The first group work together only in reciprocal pairs on tasks, -preferring to approach the nerd but also those of the other two roles. -While they hang out with each other socially quite a bit, friendship from groups 2 and 3 are preferred. -- The second group also work together only in reciprocal pairs, -preferring to work collaboratively with group 1 or also the nerd. -They also tend to count those from group 1 as friends, -and hang out with everyone else but themselves. -- The third group will work with either some in group 1 and 3, or 2, -but again prefer the nerd for task advice. -They are pretty good friends with each other though, -and pretty happy to socialise with everyone. +- The first group (of 6) are a bit of a mix: there seem to be two popular friends, +one that strongly reciprocates and the other that nominates no friendships but +seems to nominate others in the group as social contacts instead. +The first group rely heavily on the nerd for advice. +- The second group (of 5) seem to be strongly reciprocal in friendship and +social together, lightly advise each other but mostly go to the nerd for advice. +- The third group (of 4) are also strongly reciprocal in friendship, +but also sometimes nominate some in groups one and two as friends too. +There is at least a pair that often hang out together socially, +but this group do not hang out with the nerd much nor ask them for advice +as much as members of the other groups. - The nerd is a loner, no friends, but everyone hangs out with them for task advice. @@ -590,7 +595,7 @@ but everyone hangs out with them for task advice. Lastly, we can consider how _classes_ of nodes relate to one another in a blockmodel. Let's use the 4-cluster solution on the valued network (though binary is possible too) -to create a _reduced graph_. +to create a `r gloss("reduced graph","reduced")`. A reduced graph is a transformation of a network such that the nodes are no longer the individual nodes but the groups of one or more nodes as a class, and the ties between these blocked nodes can represent the sum or average tie between these classes. @@ -605,3 +610,22 @@ bm <- bm %>% as_tidygraph %>% mutate(name = c("Freaks", "Squares", "Nerds", "Geek")) graphr(bm) ``` + +## Free play + +Now try to find the regularly equivalent classes in the `ison_lawfirm` dataset. +As this is a multiplex network, you can make this a uniplex network first. + +```{r freeplay, exercise = TRUE} + +``` + +An extension can be to also explore automorphically equivalent classes. + +## Glossary + +Here are some of the terms that we have covered in this module: + +`r print_glossary()` + + diff --git a/inst/tutorials/tutorial5/position.html b/inst/tutorials/tutorial5/position.html index 53dfb3ba..21b41596 100644 --- a/inst/tutorials/tutorial5/position.html +++ b/inst/tutorials/tutorial5/position.html @@ -112,6 +112,7 @@

Setting up

+

gif of rick and morty characters hanging out with themselves

For this session, we’re going to use the “ison_algebra” dataset included in the {manynet} package. Do you remember how to call the data? Can you find out some more information about it via its @@ -173,26 +174,20 @@

Separating multiplex networks

data-label="separatingnets-hint-4" data-completion="1" data-diagnostics="1" data-startover="1" data-lines="0" data-pipe="|>"> -
# Now, let's compare the each attribute's graph, side-by-side by using "+"
-# Note: using "/" after each graph will order them vertically; however, it might not be best way
-# See for example:
-gfriend <- graphr(friends) + ggtitle("Friendship")
-gfriend + gsocial + gtask
+
graphr(friends) + ggtitle("Friendship")
friends <- to_uniplex(ison_algebra, "friends")
-gfriend <- graphr(friends) + ggtitle("Friendship")
+graphr(friends) + ggtitle("Friendship")
 
 social <- to_uniplex(ison_algebra, "social")
-gsocial <- graphr(social) + ggtitle("Social")
+graphr(social) + ggtitle("Social")
 
 tasks <- to_uniplex(ison_algebra, "tasks")
-gtask <- graphr(tasks) + ggtitle("Task")
-
-gfriend + gsocial + gtask
+graphr(tasks) + ggtitle("Task")

Note also that these are weighted networks. graphr() automatically recognises these different weights and plots them.

@@ -209,7 +204,8 @@

Separating multiplex networks

Structural Holes

Our first question for this network, is where innovation and creative -ideas might be expected to appear.

+ideas might be expected to appear. There are a number of theories that +associate innovation or novelty with structural position.

@@ -302,6 +298,7 @@

Measuring structural holes

Structural Equivalence

+

gif of rick multiplying

Next we might ask ourselves what (other) roles there are in the network? We want to know who plays what role in this algebra class. Let us begin with structural equivalence.

@@ -572,6 +569,7 @@

Step three: identifying the number of clusters

Blockmodelling

+

gif of mortys in a block parade

Summarising profiles

Ok, so now we have a result from establishing nodes’ membership in @@ -590,6 +588,7 @@

Summarising profiles

classes relate. That is, we might be less interested in how the individuals in the different classes relate, and more interested in how the different classes relate in aggregate.

+

gif of mortys learning about roles

One option that can be useful for characterising what the profile of ties (partners) is for each position/equivalence class is to use summary(). It summarises some census result by a partition @@ -620,11 +619,11 @@

Summarising profiles

takes a bit to look through what varies between the different classes as ‘blocked’. But only four rows (the four structurally equivalent classes, according to the default).

-

Another way to do this is to plot the blockmodel as a whole. Passing -the plot() function an adjacency/incidence matrix along -with a membership vector allows the matrix to be sorted and framed -(without the membership vector, just the adjacency/incidence matrix is -plotted):

+

Another way to do this is to plot the +gloss("blockmodel") as a whole. Passing the +plot() function an adjacency/incidence matrix along with a +membership vector allows the matrix to be sorted and framed (without the +membership vector, just the adjacency/incidence matrix is plotted):

@@ -647,11 +646,11 @@

Summarising profiles

membership = node_in_structural(alge)) # plot the blockmodel for the friends, tasks, and social networks separately -plot(as_matrix(friends), - membership = node_in_structural(alge)) + -plot(as_matrix(tasks), - membership = node_in_structural(alge)) + -plot(as_matrix(social), +plot(as_matrix(to_uniplex(alge, "friends")), + membership = node_in_structural(alge)) +plot(as_matrix(to_uniplex(alge, "tasks")), + membership = node_in_structural(alge)) +plot(as_matrix(to_uniplex(alge, "social")), membership = node_in_structural(alge))

By passing the membership argument our structural equivalence @@ -661,18 +660,19 @@

Summarising profiles

tasks, and social networks using the structural equivalence results, we might characterise them like so:

    -
  • The first group work together only in reciprocal pairs on tasks, -preferring to approach the nerd but also those of the other two roles. -While they hang out with each other socially quite a bit, friendship -from groups 2 and 3 are preferred.
  • -
  • The second group also work together only in reciprocal pairs, -preferring to work collaboratively with group 1 or also the nerd. They -also tend to count those from group 1 as friends, and hang out with -everyone else but themselves.
  • -
  • The third group will work with either some in group 1 and 3, or 2, -but again prefer the nerd for task advice. They are pretty good friends -with each other though, and pretty happy to socialise with -everyone.
  • +
  • The first group (of 6) are a bit of a mix: there seem to be two +popular friends, one that strongly reciprocates and the other that +nominates no friendships but seems to nominate others in the group as +social contacts instead. The first group rely heavily on the nerd for +advice.
  • +
  • The second group (of 5) seem to be strongly reciprocal in friendship +and social together, lightly advise each other but mostly go to the nerd +for advice.
  • +
  • The third group (of 4) are also strongly reciprocal in friendship, +but also sometimes nominate some in groups one and two as friends too. +There is at least a pair that often hang out together socially, but this +group do not hang out with the nerd much nor ask them for advice as much +as members of the other groups.
  • The nerd is a loner, no friends, but everyone hangs out with them for task advice.
@@ -682,14 +682,16 @@

Summarising profiles

Reduced graphs

Lastly, we can consider how classes of nodes relate to one another in a blockmodel. Let’s use the 4-cluster solution on the valued -network (though binary is possible too) to create a reduced -graph. A reduced graph is a transformation of a network such that -the nodes are no longer the individual nodes but the groups of one or -more nodes as a class, and the ties between these blocked nodes can -represent the sum or average tie between these classes. Of course, this -means that there can be self-ties or loops, because even if the original -network was simple (not complex), any within-class ties will end up -becoming loops and thus the network will be complex.

+network (though binary is possible too) to create a + +reduced graph . A reduced graph is a transformation of a +network such that the nodes are no longer the individual nodes but the +groups of one or more nodes as a class, and the ties between these +blocked nodes can represent the sum or average tie between these +classes. Of course, this means that there can be self-ties or loops, +because even if the original network was simple (not complex), any +within-class ties will end up becoming loops and thus the network will +be complex.

@@ -700,6 +702,32 @@

Reduced graphs

graphr(bm)
+
+
+

Free play

+

Now try to find the regularly equivalent classes in the +ison_lawfirm dataset. As this is a multiplex network, you +can make this a uniplex network first.

+
+ +
+

An extension can be to also explore automorphically equivalent +classes.

+
+
+

Glossary

+

Here are some of the terms that we have covered in this module:

+
+
+Reduced +
+
+A reduced graph is a representation of the ties within and between +blocks in the network. +
+

@@ -859,28 +886,29 @@

Reduced graphs

@@ -1025,17 +1053,17 @@

Reduced graphs

@@ -1240,11 +1268,11 @@

Reduced graphs

@@ -1527,9 +1555,9 @@

Reduced graphs

error_check = NULL, check = NULL, solution = structure(c("# plot the blockmodel for the whole network", "plot(as_matrix(alge),", " membership = node_in_structural(alge))", "", "# plot the blockmodel for the friends, tasks, and social networks separately", - "plot(as_matrix(friends),", " membership = node_in_structural(alge)) +", - "plot(as_matrix(tasks),", " membership = node_in_structural(alge)) +", - "plot(as_matrix(social),", " membership = node_in_structural(alge))" + "plot(as_matrix(to_uniplex(alge, \"friends\")),", " membership = node_in_structural(alge))", + "plot(as_matrix(to_uniplex(alge, \"tasks\")),", " membership = node_in_structural(alge))", + "plot(as_matrix(to_uniplex(alge, \"social\")),", " membership = node_in_structural(alge))" ), chunk_opts = list(label = "block-solution")), tests = NULL, options = list(eval = FALSE, echo = TRUE, results = "markup", tidy = FALSE, tidy.opts = NULL, collapse = FALSE, prompt = FALSE, @@ -1602,15 +1630,55 @@

Reduced graphs

engine = "r", version = "4"), class = c("r", "tutorial_exercise" ))) + + + + +

diff --git a/inst/tutorials/tutorial6/topology.Rmd b/inst/tutorials/tutorial6/topology.Rmd index 74e5f09b..e8139daa 100644 --- a/inst/tutorials/tutorial6/topology.Rmd +++ b/inst/tutorials/tutorial6/topology.Rmd @@ -145,7 +145,7 @@ Try varying the `width` argument to see the result. #### Lattices -Lattices reflect highly clustered networks +`r gloss("Lattices","lattice")` reflect highly clustered networks where there is a high likelihood that interaction partners also interact. They are used to show how clustering facilitates or limits diffusion or makes pockets of behaviour stable. @@ -394,7 +394,7 @@ Color the nodes by Gender, Office, Practice, and School. Any you might think correlate with core status? ```{r gnet, exercise=TRUE, purl = FALSE, fig.width=9} -lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex("friends") +lawfirm <- ison_lawfirm |> to_uniplex("friends") |> to_undirected() ``` ```{r gnet-solution} @@ -491,7 +491,7 @@ question("There a statistically significant association between the core assignm answer("practice.", message = learnr::random_encouragement()), answer("none of the above variables.", correct = TRUE, - message = learnr::random_praise()), + message = "That's right. The p-value for office is close, but no cigar."), allow_retry = TRUE ) ``` @@ -607,7 +607,7 @@ question("The higher the minimum number of nodes to remove...", ### Identifying cutpoints But which are these nodes? Is there more than one? -Nodes that endanger fragmentation of the network are called cutpoints. +Nodes that endanger fragmentation of the network are called `r gloss("cutpoints","cutpoint")`. Find and use a function to identify which, if any, of the nodes in the `ison_adolescents` network are cutpoints. @@ -635,6 +635,7 @@ ison_adolescents |> mutate(cut = node_is_cutpoint(ison_adolescents)) |> ### Identifying bridges Let's do something similar now, but with respect to ties rather than nodes. +Here we are interested in identifying which ties are `r gloss("bridges","bridge")`. ```{r tieside, exercise = TRUE, purl=FALSE} @@ -660,3 +661,17 @@ ison_adolescents |> mutate_ties(coh = tie_cohesion(ison_adolescents)) |> ``` Where would you target your efforts if you wanted to fragment this network? + +## Free play + +```{r freeplay, exercise = TRUE} + +``` + +## Glossary + +Here are some of the terms that we have covered in this module: + +`r print_glossary()` + + diff --git a/inst/tutorials/tutorial6/topology.html b/inst/tutorials/tutorial6/topology.html index 6fb1e563..2abf1f04 100644 --- a/inst/tutorials/tutorial6/topology.html +++ b/inst/tutorials/tutorial6/topology.html @@ -212,10 +212,11 @@

Trees

Lattices

-

Lattices reflect highly clustered networks where there is a high -likelihood that interaction partners also interact. They are used to -show how clustering facilitates or limits diffusion or makes pockets of -behaviour stable.

+

+Lattices reflect highly clustered networks where there is +a high likelihood that interaction partners also interact. They are used +to show how clustering facilitates or limits diffusion or makes pockets +of behaviour stable.

@@ -461,7 +462,7 @@

Core-periphery assignment

-
lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex("friends")
+
lawfirm <- ison_lawfirm |> to_uniplex("friends") |> to_undirected()
How cohesive is the network?

Identifying cutpoints

But which are these nodes? Is there more than one? Nodes that -endanger fragmentation of the network are called cutpoints. Find and use -a function to identify which, if any, of the nodes in the -ison_adolescents network are cutpoints.

+endanger fragmentation of the network are called + +cutpoints . Find and use a function to identify which, if +any, of the nodes in the ison_adolescents network are +cutpoints.

@@ -680,7 +683,9 @@

Identifying cutpoints

Identifying bridges

Let’s do something similar now, but with respect to ties rather than -nodes.

+nodes. Here we are interested in identifying which ties are + +bridges .

@@ -708,7 +713,42 @@

Identifying bridges

graphr(edge_size = "coh")

Where would you target your efforts if you wanted to fragment this -network? +network?

+
+
+
+

Free play

+
+ +
+
+
+

Glossary

+

Here are some of the terms that we have covered in this module:

+
+
+Bridge +
+
+A bridge is a tie whose deletion increases the number of components. +
+
+Cutpoint +
+
+A cutpoint or articulation point is a node whose deletion increases the +number of components. +
+
+Lattice +
+
+A network that can be drawn as a regular tiling. +
+
+

@@ -1454,11 +1494,11 @@

Identifying bridges

@@ -1561,7 +1601,7 @@

Identifying bridges

" \"Beau travail!\",", " \"Bravo!\",", " \"Super!\"),", " encouragement = c(\"Bon effort\"))" ), chunk_opts = list(label = "setup", include = FALSE)), setup = NULL, - chunks = list(list(label = "gnet", code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", + chunks = list(list(label = "gnet", code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", opts = list(label = "\"gnet\"", exercise = "TRUE", purl = "FALSE", fig.width = "9"), engine = "r")), code_check = NULL, error_check = NULL, check = NULL, solution = structure(c("lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", @@ -1586,7 +1626,7 @@

Identifying bridges

aniopts = "controls,loop", warning = TRUE, error = FALSE, message = TRUE, render = NULL, ref.label = NULL, child = NULL, engine = "r", split = FALSE, include = TRUE, purl = FALSE, - max.print = 1000, label = "gnet", exercise = TRUE, code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", + max.print = 1000, label = "gnet", exercise = TRUE, code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", out.width.px = 864, out.height.px = 384, params.src = "gnet, exercise=TRUE, purl = FALSE, fig.width=9", fig.num = 0, exercise.df_print = "paged", exercise.checker = "NULL"), engine = "r", version = "4"), class = c("r", "tutorial_exercise" @@ -1622,8 +1662,8 @@

Identifying bridges

"learnr::random_phrases_add(language = \"en\", ", " praise = c(\"C'est génial!\",", " \"Beau travail!\",", " \"Bravo!\",", " \"Super!\"),", " encouragement = c(\"Bon effort\"))" -), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", - chunks = list(list(label = "gnet", code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", +), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", + chunks = list(list(label = "gnet", code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", opts = list(label = "\"gnet\"", exercise = "TRUE", purl = "FALSE", fig.width = "9"), engine = "r"), list(label = "nodecore", code = "", opts = list(label = "\"nodecore\"", exercise = "TRUE", @@ -1684,8 +1724,8 @@

Identifying bridges

"learnr::random_phrases_add(language = \"en\", ", " praise = c(\"C'est génial!\",", " \"Beau travail!\",", " \"Bravo!\",", " \"Super!\"),", " encouragement = c(\"Bon effort\"))" -), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", - chunks = list(list(label = "gnet", code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", +), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", + chunks = list(list(label = "gnet", code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", opts = list(label = "\"gnet\"", exercise = "TRUE", purl = "FALSE", fig.width = "9"), engine = "r"), list(label = "netcore", code = "", opts = list(label = "\"netcore\"", exercise = "TRUE", @@ -1718,30 +1758,30 @@

Identifying bridges

@@ -1784,8 +1824,8 @@

Identifying bridges

"learnr::random_phrases_add(language = \"en\", ", " praise = c(\"C'est génial!\",", " \"Beau travail!\",", " \"Bravo!\",", " \"Super!\"),", " encouragement = c(\"Bon effort\"))" -), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", - chunks = list(list(label = "gnet", code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", +), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", + chunks = list(list(label = "gnet", code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", opts = list(label = "\"gnet\"", exercise = "TRUE", purl = "FALSE", fig.width = "9"), engine = "r"), list(label = "chisq", code = "chisq.test(as.factor(node_is_core(lawfirm)), \n as.factor(node_attribute(lawfirm, \"gender\")))", @@ -1825,26 +1865,26 @@

Identifying bridges

@@ -1887,8 +1927,8 @@

Identifying bridges

"learnr::random_phrases_add(language = \"en\", ", " praise = c(\"C'est génial!\",", " \"Beau travail!\",", " \"Bravo!\",", " \"Super!\"),", " encouragement = c(\"Bon effort\"))" -), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", - chunks = list(list(label = "gnet", code = "lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex(\"friends\")", +), chunk_opts = list(label = "setup", include = FALSE)), setup = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", + chunks = list(list(label = "gnet", code = "lawfirm <- ison_lawfirm |> to_uniplex(\"friends\") |> to_undirected()", opts = list(label = "\"gnet\"", exercise = "TRUE", purl = "FALSE", fig.width = "9"), engine = "r"), list(label = "nodecoren", code = "lawfirm %>% \n mutate(ncn = node_coreness()) %>% \n graphr(node_color = \"ncn\")", @@ -1922,13 +1962,13 @@

Identifying bridges

@@ -1945,22 +1985,22 @@

Identifying bridges

@@ -2034,18 +2074,18 @@

Identifying bridges

@@ -2120,19 +2160,19 @@

Identifying bridges

@@ -2405,19 +2445,74 @@

Identifying bridges

engine = "r", version = "4"), class = c("r", "tutorial_exercise" ))) + + + + +

-
diff --git a/man/defunct.Rd b/man/defunct.Rd index ac016ecf..58d1567b 100644 --- a/man/defunct.Rd +++ b/man/defunct.Rd @@ -87,6 +87,9 @@ \alias{network_brokerage_census} \alias{node_brokering} \alias{node_core} +\alias{node_by_quad} +\alias{net_by_quad} +\alias{layout_tbl_graph_quad} \title{Functions that have been renamed, superseded, or are no longer working} \usage{ pkg_data(pkg = "manynet") @@ -286,6 +289,12 @@ network_brokerage_census(.data, membership, standardized = FALSE) node_brokering(.data, membership) node_core(.data) + +node_by_quad(.data) + +net_by_quad(.data) + +layout_tbl_graph_quad(.data, circular = FALSE, times = 1000) } \description{ \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} @@ -470,5 +479,11 @@ wherever possible and update your scripts accordingly. \item \code{node_core()}: Deprecated on 2024-06-21. +\item \code{node_by_quad()}: Deprecated on 2024-10-10. + +\item \code{net_by_quad()}: Deprecated on 2024-10-10. + +\item \code{layout_tbl_graph_quad()}: Deprecated on 2024-10-10. + }} \keyword{internal} diff --git a/man/depth_first_recursive_search.Rd b/man/depth_first_recursive_search.Rd new file mode 100644 index 00000000..9642a068 --- /dev/null +++ b/man/depth_first_recursive_search.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/map_layouts.R +\name{depth_first_recursive_search} +\alias{depth_first_recursive_search} +\title{Layouts for snapping layouts to a grid} +\usage{ +depth_first_recursive_search(layout) +} +\description{ +The function uses approximate pattern matching +to redistribute coarse layouts on square grid points, while +preserving the topological relationships among the nodes (see Inoue et al. 2012). +} +\references{ +Inoue, Kentaro, Shinichi Shimozono, Hideaki Yoshida, and Hiroyuki Kurata. 2012. +“Application of Approximate Pattern Matching in Two Dimensional Spaces to Grid Layout for Biochemical Network Maps” edited by J. Bourdon. +\emph{PLoS ONE} 7(6):e37739. +\doi{https://doi.org/10.1371/journal.pone.0037739}. +} +\keyword{internal} diff --git a/man/ison_friends.Rd b/man/fict_friends.Rd similarity index 60% rename from man/ison_friends.Rd rename to man/fict_friends.Rd index 433db7a3..2c0eb7b1 100644 --- a/man/ison_friends.Rd +++ b/man/fict_friends.Rd @@ -1,12 +1,13 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_friends} -\alias{ison_friends} -\title{One-mode Friends character connections (McNulty, 2020)} +\name{fict_friends} +\alias{fict_friends} +\title{One-mode undirected Friends character scene co-appearances (McNulty, 2020)} \format{ -\if{html}{\out{
}}\preformatted{#> # A longitudinal, labelled, weighted, directed network of 650 nodes and 3959 -#> arcs +\if{html}{\out{
}}\preformatted{#> # Friends network +#> # A labelled, weighted, undirected network of 650 characters and 2976 scene +#> co-appearance ties #> # A tibble: 650 x 1 #> name #> @@ -17,26 +18,26 @@ #> 5 Aunt Iris #> 6 Aunt Lillian #> # i 644 more rows -#> # A tibble: 3,959 x 4 -#> from to wave weight -#> -#> 1 1 44 1 1 -#> 2 2 14 1 1 -#> 3 2 44 1 1 -#> 4 2 58 1 2 -#> 5 2 72 1 1 -#> 6 2 75 1 1 -#> # i 3,953 more rows +#> # A tibble: 2,976 x 3 +#> from to weight +#> +#> 1 8 9 3 +#> 2 4 10 1 +#> 3 8 12 1 +#> 4 9 12 1 +#> 5 2 14 1 +#> 6 3 14 1 +#> # i 2,970 more rows }\if{html}{\out{
}} } \usage{ -data(ison_friends) +data(fict_friends) } \description{ One-mode network collected by \href{https://github.com/keithmcnulty/friends_analysis/}{McNulty (2020)} on the connections between the Friends TV series characters from Seasons 1 to 10. -The \code{ison_friends} is a directed network +The \code{fict_friends} is an undirected network containing connections between characters organised by season number, which is reflected in the tie attribute 'wave'. The network contains 650 nodes @@ -44,9 +45,6 @@ Each tie represents the connection between a character pair (appear in the same and the 'weight' of the tie is the number of scenes the character pair appears in together. For all networks, characters are named (eg. Phoebe, Ross, Rachel). } -\details{ -The data contains both networks but each may be used separately. -} \references{ McNulty, K. (2020). \emph{Network analysis of Friends scripts.}. diff --git a/man/ison_greys.Rd b/man/fict_greys.Rd similarity index 91% rename from man/ison_greys.Rd rename to man/fict_greys.Rd index daebb17d..ecdccfa5 100644 --- a/man/ison_greys.Rd +++ b/man/fict_greys.Rd @@ -1,11 +1,12 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_greys} -\alias{ison_greys} +\name{fict_greys} +\alias{fict_greys} \title{One-mode undirected network of characters hook-ups on Grey's Anatomy TV show} \format{ -\if{html}{\out{
}}\preformatted{#> # A labelled, undirected network of 53 nodes and 56 ties +\if{html}{\out{
}}\preformatted{#> # Grey's Anatomy +#> # A labelled, undirected network of 53 characters and 56 hook-up ties #> # A tibble: 53 x 7 #> name sex race birthyear position season sign #> @@ -29,7 +30,7 @@ }\if{html}{\out{
}} } \usage{ -data(ison_greys) +data(fict_greys) } \description{ Grey's Anatomy is an American medical drama television series running on ABC since 2005. diff --git a/man/ison_lotr.Rd b/man/fict_lotr.Rd similarity index 79% rename from man/ison_lotr.Rd rename to man/fict_lotr.Rd index f3cfc898..e6f7d501 100644 --- a/man/ison_lotr.Rd +++ b/man/fict_lotr.Rd @@ -1,11 +1,13 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_lotr} -\alias{ison_lotr} +\name{fict_lotr} +\alias{fict_lotr} \title{One-mode network of Lord of the Rings character interactions} \format{ -\if{html}{\out{
}}\preformatted{#> # A labelled, complex, undirected network of 36 nodes and 66 ties +\if{html}{\out{
}}\preformatted{#> # Lord of the Rings +#> # A labelled, complex, undirected network of 36 characters and 66 interaction +#> ties #> # A tibble: 36 x 2 #> name Race #> @@ -29,7 +31,7 @@ }\if{html}{\out{
}} } \usage{ -data(ison_lotr) +data(fict_lotr) } \description{ A network of 36 Lord of the Rings book characters and 66 interactional relationships. diff --git a/man/fict_potter.Rd b/man/fict_potter.Rd new file mode 100644 index 00000000..295612f8 --- /dev/null +++ b/man/fict_potter.Rd @@ -0,0 +1,54 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/data_ison.R +\docType{data} +\name{fict_potter} +\alias{fict_potter} +\title{Six complex one-mode support data in Harry Potter books (Bossaert and Meidert 2013)} +\format{ +\if{html}{\out{
}}\preformatted{#> # Harry Potter +#> # A longitudinal, labelled, complex, directed network of 64 students and 544 +#> support arcs +#> # A tibble: 64 x 4 +#> name schoolyear gender house +#> +#> 1 Adrian Pucey 1989 male Slytherin +#> 2 Alicia Spinnet 1989 female Gryffindor +#> 3 Angelina Johnson 1989 female Gryffindor +#> 4 Anthony Goldstein 1991 male Ravenclaw +#> 5 Blaise Zabini 1991 male Slytherin +#> 6 C. Warrington 1989 male Slytherin +#> # i 58 more rows +#> # A tibble: 544 x 3 +#> from to wave +#> +#> 1 2 2 2 +#> 2 2 2 3 +#> 3 2 2 5 +#> 4 2 3 2 +#> 5 2 3 3 +#> 6 2 3 5 +#> # i 538 more rows +}\if{html}{\out{
}} +} +\usage{ +data(fict_potter) +} +\description{ +Goele Bossaert and Nadine Meidert coded peer support ties among 64 characters +in the Harry Potter books. +Each author coded four of seven books using NVivo, +with the seventh book coded by both and serving to assess inter-rater reliability. +The first six books concentrated on adolescent interactions, +were studied in their paper, and are made available here. +The peer support ties mean voluntary emotional, instrumental, or informational support, +or praise from one living, adolescent character to another within the book's pages. +In addition, nodal attributes name, schoolyear (which doubles as their age), +gender, and their house assigned by the sorting hat are included. +} +\references{ +Bossaert, Goele and Nadine Meidert (2013). +"'We are only as strong as we are united, as weak as we are divided'. A dynamic analysis of the peer support networks in the Harry Potter books." +\emph{Open Journal of Applied Sciences}, 3(2): 174-185. +\doi{10.4236/ojapps.2013.32024} +} +\keyword{datasets} diff --git a/man/fict_thrones.Rd b/man/fict_thrones.Rd new file mode 100644 index 00000000..5c2ec085 --- /dev/null +++ b/man/fict_thrones.Rd @@ -0,0 +1,54 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/data_ison.R +\docType{data} +\name{fict_thrones} +\alias{fict_thrones} +\title{One-mode Game of Thrones kinship (Glander 2017)} +\format{ +\if{html}{\out{
}}\preformatted{#> # Game of Thrones Kinship +#> # A labelled, multiplex, directed network of 208 characters and 404 kinship +#> arcs +#> # A tibble: 208 x 10 +#> name culture house popularity Gender title birth death noble married +#> +#> 1 Alys Arryn House~ 0.0803 female "" NA NA FALSE TRUE +#> 2 Elys Waynwood House~ 0.0702 female "Ser" NA NA TRUE TRUE +#> 3 Jasper Arryn House~ 0.0435 male "Eyr~ NA NA TRUE FALSE +#> 4 Jeyne Royce House~ 0 female NA NA NA NA +#> 5 Jon Arryn Valemen House~ 0.836 male "Eyr~ 217 298 TRUE TRUE +#> 6 Lysa Arryn House~ 0 female "Lad~ 266 300 TRUE TRUE +#> # i 202 more rows +#> # A tibble: 404 x 3 +#> from to type +#> +#> 1 1 2 spouse +#> 2 2 1 spouse +#> 3 3 1 parent +#> 4 3 5 parent +#> 5 4 5 spouse +#> 6 5 4 spouse +#> # i 398 more rows +}\if{html}{\out{
}} +} +\usage{ +data(fict_thrones) +} +\description{ +The original dataset was put together by Erin Pierce and Ben Kahle for an +assignment for a course on Bayesian statistics. +The data included information on when characters died in the Song of Ice +and Fire books, +and some predictive factors such as whether they were nobles, married, etc. +Shirin Glander extended this data set on character deaths in the TV series +Game of Thrones with the kinship relationships between the characters, +by scraping "A Wiki of Ice and Fire" and adding missing information by hand. +There is certainly more that can be done here. +} +\references{ +Pierce, Erin, and Ben Kahle. 2015. +"\href{http://allendowney.blogspot.com/2015/03/bayesian-survival-analysis-for-game-of.html}{Bayesian Survival Analysis in A Song of Ice and Fire}". + +Glander, Shirin. 2017. +"\href{https://datascienceplus.com/network-analysis-of-game-of-thrones/}{Network analysis of Game of Thrones}". +} +\keyword{datasets} diff --git a/man/glossary.Rd b/man/glossary.Rd new file mode 100644 index 00000000..5ef9edd1 --- /dev/null +++ b/man/glossary.Rd @@ -0,0 +1,24 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/manynet-tutorials.R +\name{glossary} +\alias{glossary} +\alias{gloss} +\alias{print_glossary} +\alias{clear_glossary} +\title{Adding network glossary items} +\usage{ +gloss(text, ref = NULL) + +print_glossary() + +clear_glossary() +} +\arguments{ +\item{text}{The text to appear.} + +\item{ref}{The name of the glossary item to index. +If NULL, then the function will search the glossary for 'text' instead.} +} +\description{ +This function adds a glossary item, useful in tutorials. +} diff --git a/man/ison_blogs.Rd b/man/irps_blogs.Rd similarity index 77% rename from man/ison_blogs.Rd rename to man/irps_blogs.Rd index 304f30a6..50818c63 100644 --- a/man/ison_blogs.Rd +++ b/man/irps_blogs.Rd @@ -1,11 +1,11 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_blogs} -\alias{ison_blogs} +\name{irps_blogs} +\alias{irps_blogs} \title{One-mode directed network of links between US political blogs (Adamic and Glance 2005)} \format{ -\if{html}{\out{
}}\preformatted{#> # A labelled, complex, directed network of 1490 nodes and 19090 arcs +\if{html}{\out{
}}\preformatted{#> # A labelled, complex, directed network of 1490 blogs and 19090 link arcs #> # A tibble: 1,490 x 3 #> name Leaning Source #> @@ -29,11 +29,12 @@ }\if{html}{\out{
}} } \usage{ -data(ison_blogs) +data(irps_blogs) } \description{ This network consists of the blogosphere around the time of the 2004 US presidential election until February 2005. +The 2004 election was the first in which blogging played a significant role. Ties were constructed from a crawl of the front page of each blog. Political leaning is indicated as "Liberal" (or left leaning) or @@ -42,8 +43,9 @@ Some blogs were labelled manually, based on incoming and outgoing links and posts. } \references{ -Adamic, Lada A., and Natalie Glance. 2005. -"The political blogosphere and the 2004 US Election", -\emph{Proceedings of the WWW-2005 Workshop on the Weblogging Ecosystem}. +Adamic, Lada, and Natalie Glance. 2005. +"The political blogosphere and the 2004 US Election: Divided they blog". +\emph{LinkKDD '05: Proceedings of the 3rd international workshop on Link discovery}, 36-43. +\doi{10.1145/1134271.1134277} } \keyword{datasets} diff --git a/man/ison_books.Rd b/man/irps_books.Rd similarity index 96% rename from man/ison_books.Rd rename to man/irps_books.Rd index 43bead64..53f08943 100644 --- a/man/ison_books.Rd +++ b/man/irps_books.Rd @@ -1,8 +1,8 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_books} -\alias{ison_books} +\name{irps_books} +\alias{irps_books} \title{One-mode undirected network of co-purchased books about US politics on Amazon} \format{ \if{html}{\out{
}}\preformatted{#> # A labelled, undirected network of 105 nodes and 441 ties @@ -29,7 +29,7 @@ }\if{html}{\out{
}} } \usage{ -data(ison_books) +data(irps_books) } \description{ This network consists of books about US politics sold by Amazon.com. diff --git a/man/ison_usstates.Rd b/man/irps_usgeo.Rd similarity index 86% rename from man/ison_usstates.Rd rename to man/irps_usgeo.Rd index bb42e747..666aee10 100644 --- a/man/ison_usstates.Rd +++ b/man/irps_usgeo.Rd @@ -1,11 +1,12 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/data_ison.R \docType{data} -\name{ison_usstates} -\alias{ison_usstates} +\name{irps_usgeo} +\alias{irps_usgeo} \title{One-mode undirected network of US state contiguity (Meghanathan 2017)} \format{ -\if{html}{\out{
}}\preformatted{#> # A labelled, undirected network of 50 nodes and 107 ties +\if{html}{\out{
}}\preformatted{#> # US State Contiguity +#> # A labelled, undirected network of 50 states and 107 contiguity ties #> # A tibble: 50 x 3 #> name capitol population #> @@ -29,7 +30,7 @@ }\if{html}{\out{
}} } \usage{ -data(ison_usstates) +data(irps_usgeo) } \description{ This network is of contiguity between US states. diff --git a/man/irps_wwi.Rd b/man/irps_wwi.Rd new file mode 100644 index 00000000..75bd6bd8 --- /dev/null +++ b/man/irps_wwi.Rd @@ -0,0 +1,58 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/data_ison.R +\docType{data} +\name{irps_wwi} +\alias{irps_wwi} +\title{One-mode signed network of relationships between European major powers (Antal et al. 2006)} +\format{ +\if{html}{\out{
}}\preformatted{#> # World War I Protagonists +#> # A dynamic, labelled, signed, undirected network of 6 European major powers +#> and 20 relationship ties +#> # A tibble: 6 x 1 +#> name +#> +#> 1 GBR +#> 2 FRA +#> 3 RUS +#> 4 AUH +#> 5 DEU +#> 6 ITA +#> # A tibble: 20 x 5 +#> from to sign begin end +#> +#> 1 1 2 -1 1872 1904 +#> 2 1 3 -1 1872 1907 +#> 3 1 4 -1 1872 1918 +#> 4 2 3 -1 1872 1890 +#> 5 2 4 -1 1872 1918 +#> 6 2 5 -1 1872 1918 +#> # i 14 more rows +}\if{html}{\out{
}} +} +\usage{ +data(irps_wwi) +} +\description{ +This network records the evolution of the major relationship changes +between the protagonists of World War I (WWI) from 1872 to 1907. +It is incomplete both in terms of (eventual) parties to the war as well +as some other relations, but gives a good overview of the main alliances +and enmities. + +The data series begins with the Three Emperors' League (1872, revived in 1881) +between Germany, Austria-Hungary, and Russia. +The Triple Alliance in 1882 joined Germany, Austria-Hungary, and Italy into +a bloc that lasted until WWI. +A bilateral alliance between Germany and Russia lapsed in 1890, +and a French-Russian alliance developed between 1891-1894. +The Entente Cordiale thawed and then fostered relations between Great Britain +and France in 1904, and a British-Russian agreement in 1907 bound +Great Britain, France, and Russia into the Triple Entente. +} +\references{ +Antal, Tibor, Pavel Krapivsky, and Sidney Redner. 2006. +"Social balance on networks: The dynamics of friendship and enmity". +\emph{Physica D} 224: 130-136. +\doi{10.1016/j.physd.2006.09.028} +} +\keyword{datasets} diff --git a/man/ison_potter.Rd b/man/ison_potter.Rd deleted file mode 100644 index e67885de..00000000 --- a/man/ison_potter.Rd +++ /dev/null @@ -1,168 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/data_ison.R -\docType{data} -\name{ison_potter} -\alias{ison_potter} -\title{Six complex one-mode support data in Harry Potter books (Bossaert and Meidert 2013)} -\format{ -\if{html}{\out{
}}\preformatted{#> $book1 -#> # A labelled, complex, directed network of 64 nodes and 47 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 47 x 2 -#> from to -#> -#> 1 11 11 -#> 2 11 25 -#> 3 11 26 -#> 4 11 44 -#> 5 11 56 -#> 6 11 58 -#> # i 41 more rows -#> -#> $book2 -#> # A labelled, complex, directed network of 64 nodes and 110 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 110 x 2 -#> from to -#> -#> 1 2 2 -#> 2 2 3 -#> 3 2 19 -#> 4 2 20 -#> 5 2 25 -#> 6 2 26 -#> # i 104 more rows -#> -#> $book3 -#> # A labelled, complex, directed network of 64 nodes and 104 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 104 x 2 -#> from to -#> -#> 1 2 2 -#> 2 2 3 -#> 3 2 19 -#> 4 2 20 -#> 5 2 25 -#> 6 2 26 -#> # i 98 more rows -#> -#> $book4 -#> # A labelled, complex, directed network of 64 nodes and 49 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 49 x 2 -#> from to -#> -#> 1 7 7 -#> 2 7 8 -#> 3 7 25 -#> 4 8 8 -#> 5 8 25 -#> 6 9 9 -#> # i 43 more rows -#> -#> $book5 -#> # A labelled, complex, directed network of 64 nodes and 160 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 160 x 2 -#> from to -#> -#> 1 2 2 -#> 2 2 3 -#> 3 2 19 -#> 4 2 20 -#> 5 2 25 -#> 6 2 29 -#> # i 154 more rows -#> -#> $book6 -#> # A labelled, complex, directed network of 64 nodes and 74 arcs -#> # A tibble: 64 x 4 -#> name schoolyear gender house -#> -#> 1 Adrian Pucey 1989 male Slytherin -#> 2 Alicia Spinnet 1989 female Gryffindor -#> 3 Angelina Johnson 1989 female Gryffindor -#> 4 Anthony Goldstein 1991 male Ravenclaw -#> 5 Blaise Zabini 1991 male Slytherin -#> 6 C. Warrington 1989 male Slytherin -#> # i 58 more rows -#> # A tibble: 74 x 2 -#> from to -#> -#> 1 11 11 -#> 2 11 25 -#> 3 11 56 -#> 4 11 58 -#> 5 12 12 -#> 6 14 14 -#> # i 68 more rows -}\if{html}{\out{
}} -} -\usage{ -data(ison_potter) -} -\description{ -Goele Bossaert and Nadine Meidert coded peer support ties among 64 characters -in the Harry Potter books. -Each author coded four of seven books using NVivo, -with the seventh book coded by both and serving to assess inter-rater reliability. -The first six books concentrated on adolescent interactions, -were studied in their paper, and are made available here. -The peer support ties mean voluntary emotional, instrumental, or informational support, -or praise from one living, adolescent character to another within the book's pages. -In addition, nodal attributes name, schoolyear (which doubles as their age), -gender, and their house assigned by the sorting hat are included. -} -\references{ -Bossaert, Goele and Nadine Meidert (2013). -"'We are only as strong as we are united, as weak as we are divided'. A dynamic analysis of the peer support networks in the Harry Potter books." -\emph{Open Journal of Applied Sciences}, 3(2): 174-185. -\doi{10.4236/ojapps.2013.32024} -} -\keyword{datasets} diff --git a/man/ison_thrones.Rd b/man/ison_thrones.Rd deleted file mode 100644 index f87cea49..00000000 --- a/man/ison_thrones.Rd +++ /dev/null @@ -1,45 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/data_ison.R -\docType{data} -\name{ison_thrones} -\alias{ison_thrones} -\title{One-mode Game of Thrones kinship (Glander 2017)} -\format{ -\if{html}{\out{
}}\preformatted{#> # Game of Thrones Kinship -#> # A labelled, multiplex, directed network of 208 characters and 404 kinship -#> arcs -#> # A tibble: 208 x 8 -#> name male culture house popularity house2 color shape -#> -#> 1 Alys Arryn 0 House Arryn 0.0803 circ~ -#> 2 Elys Waynwood 0 House Waynwood 0.0702 circ~ -#> 3 Jasper Arryn 1 House Arryn 0.0435 squa~ -#> 4 Jeyne Royce 0 House Royce 0 circ~ -#> 5 Jon Arryn 1 Valemen House Arryn 0.836 squa~ -#> 6 Lysa Arryn 0 House Tully 0 House Tully #F781~ circ~ -#> # i 202 more rows -#> # A tibble: 404 x 5 -#> from to type color lty -#> > -#> 1 6 7 mother #7570B3 solid -#> 2 3 1 father #1B9E77 solid -#> 3 3 5 father #1B9E77 solid -#> 4 5 7 father #1B9E77 solid -#> 5 10 23 mother #7570B3 solid -#> 6 10 12 mother #7570B3 solid -#> # i 398 more rows -}\if{html}{\out{
}} -} -\usage{ -data(ison_thrones) -} -\description{ -Shirin Glander extended a data set on character deaths in the TV series Game of Thrones -with the kinship relationships between the characters, by scraping "A Wiki of Ice and Fire" -and adding missing information by hand. -} -\references{ -Glander, Shirin (2017). -"\href{https://datascienceplus.com/network-analysis-of-game-of-thrones/}{Network analysis of Game of Thrones}". -} -\keyword{datasets} diff --git a/man/manip_as.Rd b/man/manip_as.Rd index bb96a3b5..0e393381 100644 --- a/man/manip_as.Rd +++ b/man/manip_as.Rd @@ -2,6 +2,7 @@ % Please edit documentation in R/manip_as.R \name{manip_as} \alias{manip_as} +\alias{as_nodelist} \alias{as_edgelist} \alias{as_matrix} \alias{as_igraph} @@ -13,6 +14,8 @@ \alias{as_diffnet} \title{Modifying network classes} \usage{ +as_nodelist(.data) + as_edgelist(.data, twomode = FALSE) as_matrix(.data, twomode = NULL) @@ -133,12 +136,14 @@ as_network(test) \seealso{ Other modifications: \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_correlation.Rd b/man/manip_correlation.Rd index 5219aabd..0f90a160 100644 --- a/man/manip_correlation.Rd +++ b/man/manip_correlation.Rd @@ -3,9 +3,12 @@ \name{manip_correlation} \alias{manip_correlation} \alias{to_correlation} +\alias{to_cosine} \title{Node correlation} \usage{ to_correlation(.data, method = NULL) + +to_cosine(.data) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -40,12 +43,14 @@ This function runs in \eqn{O(mn^2)} complexity. \seealso{ Other modifications: \code{\link{manip_as}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_deformat.Rd b/man/manip_deformat.Rd new file mode 100644 index 00000000..3c614a69 --- /dev/null +++ b/man/manip_deformat.Rd @@ -0,0 +1,107 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/manip_format.R +\name{manip_deformat} +\alias{manip_deformat} +\alias{to_unnamed} +\alias{to_undirected} +\alias{to_unweighted} +\alias{to_unsigned} +\alias{to_simplex} +\alias{to_uniplex} +\title{Modifying network formats} +\usage{ +to_unnamed(.data) + +to_undirected(.data) + +to_unweighted(.data, threshold = 1) + +to_unsigned(.data, keep = c("positive", "negative")) + +to_simplex(.data) + +to_uniplex(.data, tie) +} +\arguments{ +\item{.data}{An object of a manynet-consistent class: +\itemize{ +\item matrix (adjacency or incidence) from \code{{base}} R +\item edgelist, a data frame from \code{{base}} R or tibble from \code{{tibble}} +\item igraph, from the \code{{igraph}} package +\item network, from the \code{{network}} package +\item tbl_graph, from the \code{{tidygraph}} package +}} + +\item{threshold}{For a matrix, the threshold to binarise/dichotomise at.} + +\item{keep}{In the case of a signed network, whether to retain +the "positive" or "negative" ties.} + +\item{tie}{Character string naming a tie attribute to retain from a graph.} +} +\value{ +All \code{to_} functions return an object of the same class as that provided. +So passing it an igraph object will return an igraph object +and passing it a network object will return a network object, +with certain modifications as outlined for each function. +} +\description{ +These functions reformat manynet-consistent data. +\itemize{ +\item \code{to_unnamed()} reformats labelled network data to unlabelled network data. +\item \code{to_undirected()} reformats directed network data to an undirected network, +so that any pair of nodes with at least one directed edge will be +connected by an undirected edge in the new network. +This is equivalent to the "collapse" mode in \code{{igraph}}.. +\item \code{to_unweighted()} reformats weighted network data to unweighted network +data, with all tie weights removed. +\item \code{to_unsigned()} reformats signed network data to unsigned network data +keeping just the "positive" or "negative" ties. +\item \code{to_simplex()} reformats complex network data, containing loops, to simplex network data, without any loops. +\item \code{to_uniplex()} reformats multiplex network data to a single type of tie. +} + +If the format condition is not met, +for example \code{to_undirected()} is used on a network that is already undirected, +the network data is returned unaltered. +No warning is given so that these functions can be used to ensure conformance. + +Unlike the \verb{as_*()} group of functions, +these functions always return the same class as they are given, +only transforming these objects' properties. +} +\details{ +Not all functions have methods available for all object classes. +Below are the currently implemented S3 methods:\tabular{lrrrrr}{ + \tab data.frame \tab igraph \tab matrix \tab network \tab tbl_graph \cr + to_simplex \tab 0 \tab 1 \tab 1 \tab 0 \tab 1 \cr + to_undirected \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_uniplex \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_unnamed \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_unsigned \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_unweighted \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr +} +} +\examples{ +as_tidygraph(create_filled(5)) \%>\% + mutate_ties(type = sample(c("friend", "enemy"), 10, replace = TRUE)) \%>\% + to_uniplex("friend") +} +\seealso{ +Other modifications: +\code{\link{manip_as}}, +\code{\link{manip_correlation}}, +\code{\link{manip_from}}, +\code{\link{manip_levels}}, +\code{\link{manip_miss}}, +\code{\link{manip_nodes}}, +\code{\link{manip_paths}}, +\code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, +\code{\link{manip_project}}, +\code{\link{manip_reformat}}, +\code{\link{manip_scope}}, +\code{\link{manip_split}}, +\code{\link{manip_ties}} +} +\concept{modifications} diff --git a/man/manip_from.Rd b/man/manip_from.Rd index 04f4252c..25183e70 100644 --- a/man/manip_from.Rd +++ b/man/manip_from.Rd @@ -66,11 +66,13 @@ ison_adolescents \%>\% Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_levels.Rd b/man/manip_levels.Rd index 6c594c0c..bd610122 100644 --- a/man/manip_levels.Rd +++ b/man/manip_levels.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/manip_reformat.R +% Please edit documentation in R/manip_format.R \name{manip_levels} \alias{manip_levels} \alias{to_onemode} @@ -63,11 +63,13 @@ Below are the currently implemented S3 methods:\tabular{lrrrr}{ Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_miss.Rd b/man/manip_miss.Rd index 7c1fd16b..e319ff2d 100644 --- a/man/manip_miss.Rd +++ b/man/manip_miss.Rd @@ -53,11 +53,13 @@ Krause, Robert, Mark Huisman, Christian Steglich, and Tom A.B. Snijders. 2020. Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_nodes.Rd b/man/manip_nodes.Rd index 7283d1a5..1542e15a 100644 --- a/man/manip_nodes.Rd +++ b/man/manip_nodes.Rd @@ -105,11 +105,13 @@ Below are the currently implemented S3 methods:\tabular{lrrr}{ Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_paths.Rd b/man/manip_paths.Rd index 8c47be1c..afc49984 100644 --- a/man/manip_paths.Rd +++ b/man/manip_paths.Rd @@ -149,11 +149,13 @@ Prim, R.C. 1957. Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_permutation.Rd b/man/manip_permutation.Rd index ea0e81e9..0578c343 100644 --- a/man/manip_permutation.Rd +++ b/man/manip_permutation.Rd @@ -34,11 +34,13 @@ graphr(to_permuted(ison_adolescents), node_size = 4) Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_preformat.Rd b/man/manip_preformat.Rd new file mode 100644 index 00000000..1be6b03a --- /dev/null +++ b/man/manip_preformat.Rd @@ -0,0 +1,92 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/manip_format.R +\name{manip_preformat} +\alias{manip_preformat} +\alias{to_named} +\alias{to_signed} +\alias{to_weighted} +\title{Modifying network formats} +\usage{ +to_named(.data, names = NULL) + +to_signed(.data, mark = NULL) + +to_weighted(.data, measure = NULL) +} +\arguments{ +\item{.data}{An object of a manynet-consistent class: +\itemize{ +\item matrix (adjacency or incidence) from \code{{base}} R +\item edgelist, a data frame from \code{{base}} R or tibble from \code{{tibble}} +\item igraph, from the \code{{igraph}} package +\item network, from the \code{{network}} package +\item tbl_graph, from the \code{{tidygraph}} package +}} + +\item{names}{Character vector of the node names. NULL by default.} + +\item{mark}{A mark (logical vector) the length of the ties in the network.} + +\item{measure}{A numeric vector (measure) that will be added as the tie +weights to the network. +If this is NULL, then the tie weights will be drawn from a +Poisson distribution with \eqn{\lambda = 4}.} +} +\value{ +All \code{to_} functions return an object of the same class as that provided. +So passing it an igraph object will return an igraph object +and passing it a network object will return a network object, +with certain modifications as outlined for each function. +} +\description{ +These functions add some format to manynet-consistent data. +\itemize{ +\item \code{to_directed()} reformats undirected network data to a directed network. +\item \code{to_redirected()} reformats the direction of directed network data, flipping any existing direction. +\item \code{to_reciprocated()} reformats directed network data such that every directed tie is reciprocated. +\item \code{to_acyclic()} reformats network data to an acyclic graph. +\item \code{to_named()} reformats unlabelled network data to labelled network data +from a vector of names or random baby names. +\item \code{to_signed()} reformats unsigned network data to signed network data +with signs from a mark vector or at random. +} + +If the format condition is not met, +for example \code{to_undirected()} is used on a network that is already undirected, +the network data is returned unaltered. +No warning is given so that these functions can be used to ensure conformance. + +Unlike the \verb{as_*()} group of functions, +these functions always return the same class as they are given, +only transforming these objects' properties. +} +\details{ +Not all functions have methods available for all object classes. +Below are the currently implemented S3 methods:\tabular{lrrrrr}{ + \tab data.frame \tab igraph \tab matrix \tab network \tab tbl_graph \cr + to_acyclic \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_directed \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_named \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_reciprocated \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_redirected \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_simplex \tab 0 \tab 1 \tab 1 \tab 0 \tab 1 \cr +} +} +\seealso{ +Other modifications: +\code{\link{manip_as}}, +\code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, +\code{\link{manip_from}}, +\code{\link{manip_levels}}, +\code{\link{manip_miss}}, +\code{\link{manip_nodes}}, +\code{\link{manip_paths}}, +\code{\link{manip_permutation}}, +\code{\link{manip_project}}, +\code{\link{manip_reformat}}, +\code{\link{manip_scope}}, +\code{\link{manip_split}}, +\code{\link{manip_ties}} +} +\concept{modifications} diff --git a/man/manip_project.Rd b/man/manip_project.Rd index ccba3a71..75462284 100644 --- a/man/manip_project.Rd +++ b/man/manip_project.Rd @@ -5,7 +5,6 @@ \alias{to_mode1} \alias{to_mode2} \alias{to_ties} -\alias{to_galois} \title{Modifying networks projection} \usage{ to_mode1(.data, similarity = c("count", "jaccard", "rand", "pearson", "yule")) @@ -13,8 +12,6 @@ to_mode1(.data, similarity = c("count", "jaccard", "rand", "pearson", "yule")) to_mode2(.data, similarity = c("count", "jaccard", "rand", "pearson", "yule")) to_ties(.data) - -to_galois(.data) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -58,7 +55,6 @@ of the first node set's (e.g. rows) joint affiliations to nodes in the second no \item \code{to_mode2()} projects a two-mode network to a one-mode network of the second node set's (e.g. columns) joint affiliations to nodes in the first node set (rows). \item \code{to_ties()} projects a network to one where the ties become nodes and incident nodes become their ties. -\item \code{to_galois()} projects a network to its Galois derivation. } } \details{ @@ -70,11 +66,6 @@ Below are the currently implemented S3 methods:\tabular{lrrrrr}{ to_ties \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr } } -\section{Galois lattices}{ - -Note that the output from \code{to_galois()} is very busy at the moment. -} - \examples{ to_mode1(ison_southern_women) to_mode2(ison_southern_women) @@ -87,12 +78,14 @@ to_ties(ison_adolescents) Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, \code{\link{manip_split}}, diff --git a/man/manip_reformat.Rd b/man/manip_reformat.Rd index fa6ecde2..464f1716 100644 --- a/man/manip_reformat.Rd +++ b/man/manip_reformat.Rd @@ -1,44 +1,23 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/manip_reformat.R +% Please edit documentation in R/manip_format.R \name{manip_reformat} \alias{manip_reformat} -\alias{to_uniplex} -\alias{to_undirected} -\alias{to_directed} -\alias{to_redirected} -\alias{to_reciprocated} \alias{to_acyclic} -\alias{to_unweighted} -\alias{to_unsigned} -\alias{to_unnamed} -\alias{to_named} -\alias{to_simplex} \alias{to_anti} +\alias{to_redirected} +\alias{to_reciprocated} +\alias{to_directed} \title{Modifying network formats} \usage{ -to_uniplex(.data, tie) - -to_undirected(.data) +to_acyclic(.data) -to_directed(.data) +to_anti(.data) to_redirected(.data) to_reciprocated(.data) -to_acyclic(.data) - -to_unweighted(.data, threshold = 1) - -to_unsigned(.data, keep = c("positive", "negative")) - -to_unnamed(.data) - -to_named(.data, names = NULL) - -to_simplex(.data) - -to_anti(.data) +to_directed(.data) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -49,15 +28,6 @@ to_anti(.data) \item network, from the \code{{network}} package \item tbl_graph, from the \code{{tidygraph}} package }} - -\item{tie}{Character string naming a tie attribute to retain from a graph.} - -\item{threshold}{For a matrix, the threshold to binarise/dichotomise at.} - -\item{keep}{In the case of a signed network, whether to retain -the "positive" or "negative" ties.} - -\item{names}{Character vector of the node names. NULL by default.} } \value{ All \code{to_} functions return an object of the same class as that provided. @@ -68,26 +38,13 @@ with certain modifications as outlined for each function. \description{ These functions reformat manynet-consistent data. \itemize{ -\item \code{to_uniplex()} reformats multiplex network data to a single type of tie. -\item \code{to_undirected()} reformats directed network data to an undirected network. -\item \code{to_directed()} reformats undirected network data to a directed network. -\item \code{to_redirected()} reformats the direction of directed network data, flipping any existing direction. -\item \code{to_reciprocated()} reformats directed network data such that every directed tie is reciprocated. \item \code{to_acyclic()} reformats network data to an acyclic graph. -\item \code{to_unweighted()} reformats weighted network data to unweighted network data. -\item \code{to_unsigned()} reformats signed network data to unsigned network data. -\item \code{to_unnamed()} reformats labelled network data to unlabelled network data. -\item \code{to_named()} reformats unlabelled network data to labelled network data. -\item \code{to_simplex()} reformats complex network data, containing loops, to simplex network data, without any loops. \item \code{to_anti()} reformats network data into its complement, where only ties \emph{not} present in the original network are included in the new network. +\item \code{to_redirected()} reformats the direction of directed network data, flipping any existing direction. +\item \code{to_reciprocated()} reformats directed network data such that every directed tie is reciprocated. } -If the format condition is not met, -for example \code{to_undirected()} is used on a network that is already undirected, -the network data is returned unaltered. -No warning is given so that these functions can be used to ensure conformance. - Unlike the \verb{as_*()} group of functions, these functions always return the same class as they are given, only transforming these objects' properties. @@ -97,47 +54,21 @@ Not all functions have methods available for all object classes. Below are the currently implemented S3 methods:\tabular{lrrrrr}{ \tab data.frame \tab igraph \tab matrix \tab network \tab tbl_graph \cr to_acyclic \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_directed \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_named \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr + to_anti \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr to_reciprocated \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr to_redirected \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_simplex \tab 0 \tab 1 \tab 1 \tab 0 \tab 1 \cr - to_undirected \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_uniplex \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_unnamed \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_unsigned \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr - to_unweighted \tab 1 \tab 1 \tab 1 \tab 1 \tab 1 \cr } } \section{Functions}{ \itemize{ -\item \code{to_undirected()}: Returns an object that has any edge direction removed, -so that any pair of nodes with at least one directed edge will be -connected by an undirected edge in the new network. -This is equivalent to the "collapse" mode in \code{{igraph}}. - \item \code{to_redirected()}: Returns an object that has any edge direction transposed, or flipped, so that senders become receivers and receivers become senders. This essentially has no effect on undirected networks or reciprocated ties. \item \code{to_reciprocated()}: Returns an object where all ties are reciprocated. -\item \code{to_unweighted()}: Returns an object that has all edge weights removed. - -\item \code{to_unsigned()}: Returns a network with either just the "positive" ties -or just the "negative" ties - -\item \code{to_unnamed()}: Returns an object with all vertex names removed - -\item \code{to_named()}: Returns an object that has random vertex names added - -\item \code{to_simplex()}: Returns an object that has all loops or self-ties removed - }} \examples{ -as_tidygraph(create_filled(5)) \%>\% - mutate_ties(type = sample(c("friend", "enemy"), 10, replace = TRUE)) \%>\% - to_uniplex("friend") to_anti(ison_southern_women) #graphr(to_anti(ison_southern_women)) } @@ -145,12 +76,14 @@ to_anti(ison_southern_women) Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_scope}}, \code{\link{manip_split}}, diff --git a/man/manip_scope.Rd b/man/manip_scope.Rd index 626c7f8d..0d6d461d 100644 --- a/man/manip_scope.Rd +++ b/man/manip_scope.Rd @@ -97,12 +97,14 @@ ison_adolescents \%>\% Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_split}}, diff --git a/man/manip_split.Rd b/man/manip_split.Rd index bcdd967d..fd664890 100644 --- a/man/manip_split.Rd +++ b/man/manip_split.Rd @@ -108,12 +108,14 @@ ison_adolescents \%>\% Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/manip_ties.Rd b/man/manip_ties.Rd index 3727947f..531efcc0 100644 --- a/man/manip_ties.Rd +++ b/man/manip_ties.Rd @@ -91,12 +91,14 @@ delete_ties(ison_adolescents, "Alice|Sue") Other modifications: \code{\link{manip_as}}, \code{\link{manip_correlation}}, +\code{\link{manip_deformat}}, \code{\link{manip_from}}, \code{\link{manip_levels}}, \code{\link{manip_miss}}, \code{\link{manip_nodes}}, \code{\link{manip_paths}}, \code{\link{manip_permutation}}, +\code{\link{manip_preformat}}, \code{\link{manip_project}}, \code{\link{manip_reformat}}, \code{\link{manip_scope}}, diff --git a/man/map_graphr.Rd b/man/map_graphr.Rd index 6aeb3c3b..474f3d4b 100644 --- a/man/map_graphr.Rd +++ b/man/map_graphr.Rd @@ -15,6 +15,7 @@ graphr( node_group, edge_color, edge_size, + snap = FALSE, ..., node_colour, edge_colour @@ -86,6 +87,8 @@ it is recommended to calculate all edge-related statistics prior to using this function. Edges can also be sized by declaring a numeric size or vector instead.} +\item{snap}{Logical scalar, whether the layout should be snapped to a grid.} + \item{...}{Extra arguments to pass on to the layout algorithm, if necessary.} } \value{ @@ -122,7 +125,7 @@ try \code{run_tute("Visualisation")}. \examples{ graphr(ison_adolescents) ison_adolescents \%>\% - mutate(color = rep(c("extrovert", "introvert"), times = 4), + mutate(color = rep(c("introvert","extrovert"), times = 4), size = ifelse(node_is_cutpoint(ison_adolescents), 6, 3)) \%>\% mutate_ties(ecolor = rep(c("friends", "acquaintances"), times = 5)) \%>\% graphr(node_color = "color", node_size = "size", diff --git a/man/map_layout_configuration.Rd b/man/map_layout_configuration.Rd index c4e1b17e..8f8e0f33 100644 --- a/man/map_layout_configuration.Rd +++ b/man/map_layout_configuration.Rd @@ -3,15 +3,24 @@ \name{map_layout_configuration} \alias{map_layout_configuration} \alias{layout_tbl_graph_configuration} +\alias{layout_tbl_graph_dyad} \alias{layout_tbl_graph_triad} -\alias{layout_tbl_graph_quad} +\alias{layout_tbl_graph_tetrad} +\alias{layout_tbl_graph_pentad} +\alias{layout_tbl_graph_hexad} \title{Layout algorithms based on configurational positions} \usage{ layout_tbl_graph_configuration(.data, circular = FALSE, times = 1000) +layout_tbl_graph_dyad(.data, circular = FALSE, times = 1000) + layout_tbl_graph_triad(.data, circular = FALSE, times = 1000) -layout_tbl_graph_quad(.data, circular = FALSE, times = 1000) +layout_tbl_graph_tetrad(.data, circular = FALSE, times = 1000) + +layout_tbl_graph_pentad(.data, circular = FALSE, times = 1000) + +layout_tbl_graph_hexad(.data, circular = FALSE, times = 1000) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -30,7 +39,7 @@ Only possible for some layouts. Defaults to FALSE.} } \description{ Configurational layouts locate nodes at symmetric coordinates -to help illustrate the particular layouts. +to help illustrate particular configurations. Currently "triad" and "quad" layouts are available. The "configuration" layout will choose the appropriate configurational layout automatically. diff --git a/man/mark_nodes.Rd b/man/mark_nodes.Rd index ab598dfc..36e9c5ab 100644 --- a/man/mark_nodes.Rd +++ b/man/mark_nodes.Rd @@ -3,14 +3,18 @@ \name{mark_nodes} \alias{mark_nodes} \alias{node_is_isolate} +\alias{node_is_pendant} \alias{node_is_independent} \alias{node_is_cutpoint} \alias{node_is_fold} \alias{node_is_mentor} +\alias{node_is_neighbor} \title{Marking nodes based on structural properties} \usage{ node_is_isolate(.data) +node_is_pendant(.data) + node_is_independent(.data) node_is_cutpoint(.data) @@ -18,6 +22,8 @@ node_is_cutpoint(.data) node_is_fold(.data) node_is_mentor(.data, elites = 0.1) + +node_is_neighbor(.data, node) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -42,6 +48,8 @@ for example because they are an isolate, a tie to themselves (a loop) will be created instead. Note that this is a different default behaviour than that described in Valente and Davis (1999).} + +\item{node}{Name or index of node.} } \description{ These functions return logical vectors the length of the diff --git a/man/mark_triangles.Rd b/man/mark_triangles.Rd index f108b042..aeb301cb 100644 --- a/man/mark_triangles.Rd +++ b/man/mark_triangles.Rd @@ -8,6 +8,7 @@ \alias{tie_is_cyclical} \alias{tie_is_simmelian} \alias{tie_is_forbidden} +\alias{tie_is_imbalanced} \title{Marking ties based on structural properties} \usage{ tie_is_triangular(.data) @@ -21,6 +22,8 @@ tie_is_cyclical(.data) tie_is_simmelian(.data) tie_is_forbidden(.data) + +tie_is_imbalanced(.data) } \arguments{ \item{.data}{An object of a manynet-consistent class: @@ -66,6 +69,7 @@ ison_monks \%>\% to_uniplex("like") \%>\% generate_random(8, directed = TRUE) \%>\% mutate_ties(forbid = tie_is_forbidden()) \%>\% graphr(edge_color = "forbid") +tie_is_imbalanced(ison_marvel_relationships) } \seealso{ Other marks: diff --git a/man/measure_attributes.Rd b/man/measure_attributes.Rd index 2b731318..7ae9f694 100644 --- a/man/measure_attributes.Rd +++ b/man/measure_attributes.Rd @@ -50,7 +50,7 @@ These functions are also often used as helpers within other functions. as the number of nodes or ties in the network, respectively. } \examples{ -node_attribute(ison_lotr, "Race") +node_attribute(fict_lotr, "Race") node_names(ison_southern_women) node_is_mode(ison_southern_women) tie_attribute(ison_algebra, "task_tie") diff --git a/man/measure_central_close.Rd b/man/measure_central_close.Rd index 8c1af71e..ac2a6e3a 100644 --- a/man/measure_central_close.Rd +++ b/man/measure_central_close.Rd @@ -8,6 +8,7 @@ \alias{node_information} \alias{node_eccentricity} \alias{node_distance} +\alias{node_vitality} \alias{tie_closeness} \alias{net_closeness} \alias{net_reach} @@ -26,6 +27,8 @@ node_eccentricity(.data, normalized = TRUE) node_distance(.data, from, to, normalized = TRUE) +node_vitality(.data, normalized = TRUE) + tie_closeness(.data, normalized = TRUE) net_closeness(.data, normalized = TRUE, direction = c("all", "out", "in")) @@ -161,6 +164,14 @@ where the distance from \eqn{i} to \eqn{j} is \eqn{\infty} if unconnected. As such it is only well defined for connected networks. } +\section{Closeness vitality centrality}{ + +The closeness vitality of a node is the change in the sum of all distances +in a network, also known as the Wiener Index, when that node is removed. +Note that the closeness vitality may be negative infinity if +removing that node would disconnect the network. +} + \examples{ node_closeness(ison_southern_women) node_reach(ison_adolescents) @@ -223,6 +234,13 @@ Hage, Per, and Frank Harary. 1995. \emph{Social Networks}, 17(1): 57-63. \doi{10.1016/0378-8733(94)00248-9} } + +Koschuetzki, Dirk, Katharina Lehmann, Leon Peeters, Stefan Richter, +Dagmar Tenfelde-Podehl, and Oliver Zlotowski. 2005. +"Centrality Indices", in +Brandes, Ulrik, and Thomas Erlebach (eds.). +\emph{Network Analysis: Methodological Foundations}. +Springer: Berlin, pp. 16-61. } \seealso{ Other centrality: diff --git a/man/measure_central_eigen.Rd b/man/measure_central_eigen.Rd index 31e836dc..a78cc7b3 100644 --- a/man/measure_central_eigen.Rd +++ b/man/measure_central_eigen.Rd @@ -12,7 +12,7 @@ \alias{net_eigenvector} \title{Measures of eigenvector-like centrality and centralisation} \usage{ -node_eigenvector(.data, normalized = TRUE, scale = FALSE) +node_eigenvector(.data, normalized = TRUE, scale = TRUE) node_power(.data, normalized = TRUE, scale = FALSE, exponent = 1) @@ -100,6 +100,8 @@ where \eqn{a_{i,j} = 1} if \eqn{i} is linked to \eqn{j} and 0 otherwise, and \eqn{\lambda} is a constant representing the principal eigenvalue. Rather than performing this iteration, most routines solve the eigenvector equation \eqn{Ax = \lambda x}. +Note that since \code{{igraph}} v2.1.1, +the values will always be rescaled so that the maximum is 1. } \section{Power or beta (or Bonacich) centrality}{ diff --git a/man/measure_cohesion.Rd b/man/measure_cohesion.Rd index 4419f406..8f670e5e 100644 --- a/man/measure_cohesion.Rd +++ b/man/measure_cohesion.Rd @@ -62,8 +62,8 @@ please use \code{manynet::to_undirected()} first. \examples{ net_density(ison_adolescents) net_density(ison_southern_women) - net_components(ison_friends) - net_components(to_undirected(ison_friends)) + net_components(fict_thrones) + net_components(to_undirected(fict_thrones)) net_cohesion(ison_marvel_relationships) net_cohesion(to_giant(ison_marvel_relationships)) net_adhesion(ison_marvel_relationships) diff --git a/man/measure_features.Rd b/man/measure_features.Rd index cc57d496..f119f997 100644 --- a/man/measure_features.Rd +++ b/man/measure_features.Rd @@ -44,7 +44,9 @@ This can be created by, among other things, any \verb{node_is_*()} function.} \item{membership}{A vector of partition membership.} \item{resolution}{A proportion indicating the resolution scale. -By default 1.} +By default 1, which returns the original definition of modularity. +The higher this parameter, the more smaller communities will be privileged. +The lower this parameter, the fewer larger communities are likely to be found.} \item{method}{There are three small-world measures implemented: \itemize{ @@ -115,6 +117,8 @@ particularly with large networks or depending on the degree of interconnectednes can miss small clusters that 'hide' inside larger clusters. In the extreme case, this can be where they are only connected to the rest of the network through a single tie. +To help manage this problem, a \code{resolution} parameter is added. +Please see the argument definition for more details. } \examples{ diff --git a/man/measure_properties.Rd b/man/measure_properties.Rd index 18f2e109..519a2eab 100644 --- a/man/measure_properties.Rd +++ b/man/measure_properties.Rd @@ -56,7 +56,7 @@ net_nodes(ison_southern_women) net_ties(ison_southern_women) net_dims(ison_southern_women) net_dims(to_mode1(ison_southern_women)) - net_node_attributes(ison_lotr) + net_node_attributes(fict_lotr) net_tie_attributes(ison_algebra) } \seealso{ diff --git a/man/member_community_non.Rd b/man/member_community_non.Rd index 1c29826e..869ffa1e 100644 --- a/man/member_community_non.Rd +++ b/man/member_community_non.Rd @@ -2,6 +2,7 @@ % Please edit documentation in R/member_community.R \name{member_community_non} \alias{member_community_non} +\alias{node_in_community} \alias{node_in_optimal} \alias{node_in_partition} \alias{node_in_infomap} @@ -11,6 +12,8 @@ \alias{node_in_leiden} \title{Non-hierarchical community partitioning algorithms} \usage{ +node_in_community(.data) + node_in_optimal(.data) node_in_partition(.data) @@ -50,6 +53,9 @@ and larger values make missing ties more important.} These functions offer algorithms for partitioning networks into sets of communities: \itemize{ +\item \code{node_in_community()} runs either optimal or, for larger networks, +finds the algorithm that maximises modularity and returns that membership +vector. \item \code{node_in_optimal()} is a problem-solving algorithm that seeks to maximise modularity over all possible partitions. \item \code{node_in_partition()} is a greedy, iterative, deterministic @@ -69,6 +75,16 @@ The different algorithms offer various advantages in terms of computation time, availability on different types of networks, ability to maximise modularity, and their logic or domain of inspiration. } +\section{Community}{ + +This function runs through all available community detection algorithms +for a given network type, finds the algorithm that returns the +largest modularity score, and returns the corresponding membership +partition. +Where feasible (a small enough network), the optimal problem solving +technique is used to ensure the maximal modularity partition. +} + \section{Optimal}{ The general idea is to calculate the modularity of all possible partitions, @@ -130,6 +146,8 @@ where \emph{m} is the total tie weight, \eqn{n_i} is the node weight of node \emph{i}, and \eqn{\delta(\sigma_i, \sigma_j) = 1} if and only if \emph{i} and \emph{j} are in the same communities and 0 otherwise. +Compared to the Louvain method, the Leiden algorithm additionally +tries to avoid unconnected communities. } \examples{ diff --git a/man/member_components.Rd b/man/member_components.Rd index ebec88b7..63ba59b6 100644 --- a/man/member_components.Rd +++ b/man/member_components.Rd @@ -52,11 +52,6 @@ As described in \code{igraph::coreness}, a node's coreness is \emph{k} if it belongs to the \emph{k}-core but not to the (\emph{k}+1)-core. } -\examples{ -ison_monks \%>\% to_uniplex("esteem") \%>\% - mutate_nodes(comp = node_in_component()) \%>\% - graphr(node_color = "comp") -} \seealso{ Other memberships: \code{\link{mark_core}}, diff --git a/man/member_equivalence.Rd b/man/member_equivalence.Rd index db7f3847..efc6af46 100644 --- a/man/member_equivalence.Rd +++ b/man/member_equivalence.Rd @@ -15,7 +15,7 @@ node_in_equivalence( .data, census, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor", "cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L ) @@ -23,7 +23,7 @@ node_in_equivalence( node_in_structural( .data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor", "cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L ) @@ -31,7 +31,7 @@ node_in_structural( node_in_regular( .data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor", "cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L ) @@ -39,7 +39,7 @@ node_in_regular( node_in_automorphic( .data, k = c("silhouette", "elbow", "strict"), - cluster = c("hierarchical", "concor"), + cluster = c("hierarchical", "concor", "cosine"), distance = c("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski"), range = 8L ) @@ -121,12 +121,12 @@ plot(nre) if(require("sna", quietly = TRUE)){ (nae <- node_in_automorphic(ison_southern_women, k = "elbow")) -} if(require("ggdendro", quietly = TRUE)){ plot(nae) } } } +} \seealso{ Other memberships: \code{\link{mark_core}}, diff --git a/man/model_cluster.Rd b/man/model_cluster.Rd index 9689b2ce..1f9efc62 100644 --- a/man/model_cluster.Rd +++ b/man/model_cluster.Rd @@ -3,11 +3,14 @@ \name{model_cluster} \alias{model_cluster} \alias{cluster_hierarchical} +\alias{cluster_cosine} \alias{cluster_concor} \title{Methods for equivalence clustering} \usage{ cluster_hierarchical(census, distance) +cluster_cosine(census, distance) + cluster_concor(.data, census) } \arguments{ @@ -43,7 +46,6 @@ They are exported and listed here to provide more detailed documentation. } \section{CONCOR}{ - First a matrix of Pearson correlation coefficients between each pair of nodes profiles in the given census is created. Then, again, we find the correlations of this square, symmetric matrix, diff --git a/man/motif_net.Rd b/man/motif_net.Rd index aa92a207..65da8000 100644 --- a/man/motif_net.Rd +++ b/man/motif_net.Rd @@ -4,7 +4,7 @@ \alias{motif_net} \alias{net_by_dyad} \alias{net_by_triad} -\alias{net_by_quad} +\alias{net_by_tetrad} \alias{net_by_mixed} \title{Motifs at the network level} \source{ @@ -15,7 +15,7 @@ net_by_dyad(.data) net_by_triad(.data) -net_by_quad(.data) +net_by_tetrad(.data) net_by_mixed(.data, object2) } @@ -32,19 +32,49 @@ net_by_mixed(.data, object2) \item{object2}{A second, two-mode migraph-consistent object.} } \description{ -These functions include ways to take a census of the positions of nodes +These functions include ways to take a census of the graphlets in a network: \itemize{ \item \code{net_by_dyad()} returns a census of dyad motifs in a network. \item \code{net_by_triad()} returns a census of triad motifs in a network. +\item \code{net_by_tetrad()} returns a census of tetrad motifs in a network. \item \code{net_by_mixed()} returns a census of triad motifs that span a one-mode and a two-mode network. } + +See also \href{https://www.graphclasses.org/smallgraphs.html}{graph classes}. +} +\section{Tetrad census}{ + +The tetrad census counts the number of four-node configurations in the network. +The function returns a matrix with a special naming convention: +\itemize{ +\item E4 (aka co-K4): This is an empty set of four nodes; no ties +\item I4 (aka co-diamond): This is a set of four nodes with just one tie +\item H4 (aka co-C4): This set of four nodes includes two non-adjacent ties +\item L4 (aka co-paw): This set of four nodes includes two adjacent ties +\item D4 (aka co-claw): This set of four nodes includes three adjacent ties, +in the form of a triangle with one isolate +\item U4 (aka P4, four-actor line): This set of four nodes includes three ties +arranged in a line +\item Y4 (aka claw): This set of four nodes includes three ties all adjacent +to a single node +\item P4 (aka paw, kite): This set of four nodes includes four ties arranged +as a triangle with an extra tie hanging off of one of the nodes +\item C4 (aka bifan): This is a symmetric box or 4-cycle or set of shared choices +\item Z4 (aka diamond): This resembles C4 but with an extra tie cutting across the box +\item X4 (aka K4): This resembles C4 but with two extra ties cutting across the box; +a realisation of all possible ties +} + +Graphs of these motifs can be shown using +\code{plot(net_by_tetrad(ison_southern_women))}. } + \examples{ net_by_dyad(manynet::ison_algebra) net_by_triad(manynet::ison_adolescents) -net_by_quad(ison_southern_women) +net_by_tetrad(ison_southern_women) marvel_friends <- to_unsigned(ison_marvel_relationships, "positive") (mixed_cen <- net_by_mixed(marvel_friends, ison_marvel_teams)) } @@ -67,6 +97,19 @@ Davis, James A., and Samuel Leinhardt. 1967. “\href{https://files.eric.ed.gov/fulltext/ED024086.pdf}{The Structure of Positive Interpersonal Relations in Small Groups}.” 55. } +\subsection{On the tetrad census}{ + +Ortmann, Mark, and Ulrik Brandes. 2017. +“Efficient Orbit-Aware Triad and Quad Census in Directed and Undirected Graphs.” +\emph{Applied Network Science} 2(1):13. +\doi{10.1007/s41109-017-0027-2}. + +McMillan, Cassie, and Diane Felmlee. 2020. +"Beyond Dyads and Triads: A Comparison of Tetrads in Twenty Social Networks". +\emph{Social Psychology Quarterly} 83(4): 383-404. +\doi{10.1177/0190272520944151} +} + \subsection{On the mixed census}{ Hollway, James, Alessandro Lomi, Francesca Pallotti, and Christoph Stadtfeld. 2017. diff --git a/man/motif_node.Rd b/man/motif_node.Rd index 5eddc5f9..ee47136a 100644 --- a/man/motif_node.Rd +++ b/man/motif_node.Rd @@ -5,7 +5,7 @@ \alias{node_by_tie} \alias{node_by_dyad} \alias{node_by_triad} -\alias{node_by_quad} +\alias{node_by_tetrad} \alias{node_by_path} \title{Motifs at the nodal level} \usage{ @@ -15,7 +15,7 @@ node_by_dyad(.data) node_by_triad(.data) -node_by_quad(.data) +node_by_tetrad(.data) node_by_path(.data) } @@ -38,18 +38,46 @@ For directed networks, out-ties and in-ties are bound together. For multiplex networks, the various types of ties are bound together. \item \code{node_by_triad()} returns a census of the triad configurations nodes are embedded in. -\item \code{node_by_quad()} returns a census of nodes' positions +\item \code{node_by_tetrad()} returns a census of nodes' positions in motifs of four nodes. \item \code{node_by_path()} returns the shortest path lengths of each node to every other node in the network. } } +\section{Tetrad census}{ + +The nodal tetrad census counts the number of four-node configurations +that each node is embedded in. +The function returns a matrix with a special naming convention: +\itemize{ +\item E4 (aka co-K4): This is an empty set of four nodes; no ties +\item I4 (aka co-diamond): This is a set of four nodes with just one tie +\item H4 (aka co-C4): This set of four nodes includes two non-adjacent ties +\item L4 (aka co-paw): This set of four nodes includes two adjacent ties +\item D4 (aka co-claw): This set of four nodes includes three adjacent ties, +in the form of a triangle with one isolate +\item U4 (aka P4, four-actor line): This set of four nodes includes three ties +arranged in a line +\item Y4 (aka claw): This set of four nodes includes three ties all adjacent +to a single node +\item P4 (aka paw, kite): This set of four nodes includes four ties arranged +as a triangle with an extra tie hanging off of one of the nodes +\item C4 (aka bifan): This is a symmetric box or 4-cycle or set of shared choices +\item Z4 (aka diamond): This resembles C4 but with an extra tie cutting across the box +\item X4 (aka K4): This resembles C4 but with two extra ties cutting across the box; +a realisation of all possible ties +} + +Graphs of these motifs can be shown using +\code{plot(node_by_tetrad(ison_southern_women))}. +} + \examples{ task_eg <- to_named(to_uniplex(ison_algebra, "tasks")) (tie_cen <- node_by_tie(task_eg)) node_by_dyad(ison_networkers) (triad_cen <- node_by_triad(task_eg)) -node_by_quad(ison_southern_women) +node_by_tetrad(ison_southern_women) node_by_path(ison_adolescents) node_by_path(ison_southern_women) } @@ -68,6 +96,19 @@ Davis, James A., and Samuel Leinhardt. 1967. “\href{https://files.eric.ed.gov/fulltext/ED024086.pdf}{The Structure of Positive Interpersonal Relations in Small Groups}.” 55. } +\subsection{On the tetrad census}{ + +Ortmann, Mark, and Ulrik Brandes. 2017. +“Efficient Orbit-Aware Triad and Quad Census in Directed and Undirected Graphs.” +\emph{Applied Network Science} 2(1):13. +\doi{10.1007/s41109-017-0027-2}. + +McMillan, Cassie, and Diane Felmlee. 2020. +"Beyond Dyads and Triads: A Comparison of Tetrads in Twenty Social Networks". +\emph{Social Psychology Quarterly} 83(4): 383-404. +\doi{10.1177/0190272520944151} +} + \subsection{On paths}{ Dijkstra, Edsger W. 1959. diff --git a/pkgdown/_pkgdown.yml b/pkgdown/_pkgdown.yml index 55b0b17b..fadfa679 100644 --- a/pkgdown/_pkgdown.yml +++ b/pkgdown/_pkgdown.yml @@ -90,7 +90,9 @@ reference: desc: | Functions for reformatting networks, retaining the same network dimensions. contents: + - manip_preformat - manip_reformat + - manip_deformat - subtitle: "Transforming" desc: | Functions for transforming networks, which may change the network's dimensions. @@ -227,13 +229,22 @@ reference: providing an overview of their properties. contents: - ends_with("_tute") + - glossary - subtitle: "Data" desc: | The package contains a variety of networks useful for pedagogical purposes and used in the course 'Social Networks Theories and Methods' and other workshops. + There are three collections of data: `ison_` include classic datasets used + for introducing network analysis, + `fict_` include some popular fictional datasets, + and `irps_` include some network datasets that demonstrate the application + of social network analysis to International Relations or Political Science + topics. Each page documents the source of the data and its format. References are provided for further reading and citation. contents: - data_overview - starts_with("ison_") + - starts_with("fict_") + - starts_with("irps_") diff --git a/tests/testthat/helper-manynet.R b/tests/testthat/helper-manynet.R index 82a391d3..09beca30 100644 --- a/tests/testthat/helper-manynet.R +++ b/tests/testthat/helper-manynet.R @@ -4,6 +4,23 @@ collect_functions <- function(pattern, package = "manynet"){ getNamespaceExports(package)[grepl(pattern, getNamespaceExports(package))] } +expect_values <- function(object, ref) { + # 1. Capture object and label + # act <- quasi_label(rlang::enquo(object), arg = "object") + act <- list(val = object, label = deparse(substitute(object))) + + # 2. Call expect() + act$n <- unname(unlist(act$val)) + ref <- unname(unlist(ref)) + expect( + act$n == ref, + sprintf("%s has values %i, not values %i.", act$lab, act$n, ref) + ) + + # 3. Invisibly return the value + invisible(act$val) +} + top3 <- function(res, dec = 4){ if(is.numeric(res)){ unname(round(res, dec))[1:3] diff --git a/tests/testthat/test-manip_as.R b/tests/testthat/test-manip_as.R index c769c868..cb993a05 100644 --- a/tests/testthat/test-manip_as.R +++ b/tests/testthat/test-manip_as.R @@ -87,8 +87,7 @@ test_that("conversion of diff_model object works correctly", { skip_on_ci() diff <- play_diffusion(ison_brandes) tidy_diff <- as_tidygraph(diff) - expect_equal(net_nodes(tidy_diff), net_nodes(ison_brandes)) - expect_equal(net_ties(tidy_diff), net_ties(ison_brandes)) - # expect_true(is_twomode(tidy_diff)) - expect_equal(c(net_nodes(tidy_diff)), max(diff$I)) + expect_values(net_nodes(tidy_diff), net_nodes(ison_brandes)) + expect_values(net_ties(tidy_diff), net_ties(ison_brandes)) + expect_values(net_nodes(tidy_diff), max(diff$I)) }) diff --git a/tests/testthat/test-manip_reformat.R b/tests/testthat/test-manip_format.R similarity index 95% rename from tests/testthat/test-manip_reformat.R rename to tests/testthat/test-manip_format.R index ebed5fc5..5b09c36d 100644 --- a/tests/testthat/test-manip_reformat.R +++ b/tests/testthat/test-manip_format.R @@ -86,11 +86,11 @@ test_that("to_onemode works",{ }) test_that("to_simplex works", { - expect_true(is_complex(ison_lotr)) - expect_false(is_complex(to_simplex(ison_lotr))) - expect_false(is_complex(to_simplex(as_igraph(ison_lotr)))) - expect_false(is_complex(to_simplex(as_matrix(ison_lotr)))) - expect_false(is_complex(to_simplex(as_igraph(ison_lotr)))) + expect_true(is_complex(fict_lotr)) + expect_false(is_complex(to_simplex(fict_lotr))) + expect_false(is_complex(to_simplex(as_igraph(fict_lotr)))) + expect_false(is_complex(to_simplex(as_matrix(fict_lotr)))) + expect_false(is_complex(to_simplex(as_igraph(fict_lotr)))) }) test_that("to_unsigned works", { diff --git a/tests/testthat/test-manip_split.R b/tests/testthat/test-manip_split.R index 6be03b08..c4a66312 100644 --- a/tests/testthat/test-manip_split.R +++ b/tests/testthat/test-manip_split.R @@ -50,11 +50,11 @@ test_that("to_waves works for diff_model objects", { skip_on_ci() wave_diff <- play_diffusion(ison_brandes) expect_length(to_waves(wave_diff), length(wave_diff$t)) - expect_equal(net_nodes(to_waves(wave_diff)[[1]]), + expect_values(net_nodes(to_waves(wave_diff)[[1]]), net_nodes(to_waves(wave_diff)[[12]])) - expect_equal(net_ties(to_waves(wave_diff)[[1]]), + expect_values(net_ties(to_waves(wave_diff)[[1]]), net_ties(to_waves(wave_diff)[[12]])) - expect_equal(net_nodes(to_waves(wave_diff)[[1]]), + expect_values(net_nodes(to_waves(wave_diff)[[1]]), net_nodes(ison_brandes)) expect_true(node_attribute(to_waves(wave_diff)[[1]], "Infected")[1]) expect_false(node_attribute(to_waves(wave_diff)[[7]], "Exposed")[1]) diff --git a/tests/testthat/test-manip_transform.R b/tests/testthat/test-manip_transform.R index b7221db0..d2e51003 100644 --- a/tests/testthat/test-manip_transform.R +++ b/tests/testthat/test-manip_transform.R @@ -18,8 +18,8 @@ test_that("matrix projected correctly by rows",{ expect_true(is_weighted(to_mode1(as_edgelist(ison_southern_women)))) expect_true(all(node_names(to_mode1(ison_southern_women)) %in% node_names(ison_southern_women))) expect_true(length(node_names(to_mode1(ison_southern_women))) != length(node_names(ison_southern_women))) - expect_equal(length(node_names(to_mode1(ison_southern_women))), length(rownames(as_matrix(ison_southern_women)))) - expect_equal(net_nodes(to_mode1(ison_southern_women, "count")), net_nodes(to_mode1(ison_southern_women, "jaccard"))) + expect_values(length(node_names(to_mode1(ison_southern_women))), length(rownames(as_matrix(ison_southern_women)))) + expect_values(net_nodes(to_mode1(ison_southern_women, "count")), net_nodes(to_mode1(ison_southern_women, "jaccard"))) expect_true(is_weighted(to_mode1(ison_southern_women, "pearson"))) expect_false(tie_weights(to_mode1(ison_southern_women, "rand"))[3] == tie_weights(to_mode1(ison_southern_women, "count"))[3]) }) @@ -33,15 +33,15 @@ test_that("matrix projected correctly by columns",{ expect_true(is_weighted(to_mode2(as_edgelist(ison_southern_women)))) expect_true(all(node_names(to_mode2(ison_southern_women)) %in% node_names(ison_southern_women))) expect_true(length(node_names(to_mode2(ison_southern_women))) != length(node_names(ison_southern_women))) - expect_equal(length(node_names(to_mode2(ison_southern_women))), length(colnames(as_matrix(ison_southern_women)))) - expect_equal(net_nodes(to_mode2(ison_southern_women, "count")), net_nodes(to_mode2(ison_southern_women, "jaccard"))) + expect_values(length(node_names(to_mode2(ison_southern_women))), length(colnames(as_matrix(ison_southern_women)))) + expect_values(net_nodes(to_mode2(ison_southern_women, "count")), net_nodes(to_mode2(ison_southern_women, "jaccard"))) expect_true(is_weighted(to_mode2(ison_southern_women, "pearson"))) expect_false(tie_weights(to_mode2(ison_southern_women, "rand"))[1] == tie_weights(to_mode2(ison_southern_women, "count"))[1]) }) test_that("to matching works", { sw <- as_edgelist(to_matching(ison_southern_women)) - expect_equal(net_nodes(to_matching(ison_southern_women)), + expect_values(net_nodes(to_matching(ison_southern_women)), net_nodes(ison_southern_women)) expect_true(nrow(sw) == nrow(dplyr::distinct(sw))) }) diff --git a/tests/testthat/test-mark_nodes.R b/tests/testthat/test-mark_nodes.R index 4bc89c57..6057dbba 100644 --- a/tests/testthat/test-mark_nodes.R +++ b/tests/testthat/test-mark_nodes.R @@ -1,12 +1,35 @@ -test_that("node cuts works", { - expect_s3_class(node_is_cutpoint(ison_algebra), "node_mark") +set.seed(1234) + +test_that("node_is_cutpoint", { + expect_true(exists("node_is_cutpoint")) + test_that("returns correct type", { + expect_s3_class(node_is_cutpoint(ison_algebra), "node_mark") + }) expect_length(node_is_cutpoint(ison_southern_women), c(net_nodes(ison_southern_women))) }) -test_that("node isolate works", { - expect_s3_class(node_is_isolate(ison_brandes), "logical") - expect_equal(length(node_is_isolate(ison_brandes)), c(net_nodes(ison_brandes))) +test_that("node_is_isolate", { + f <- node_is_isolate + expect_true(is.function(f)) + test <- f(ison_brandes) + test_that("returns correct values", { + expect_equal(length(test), c(net_nodes(ison_brandes))) + }) + test_that("returns correct type", { + expect_s3_class(test, "logical") + }) +}) + +test_that("node_is_fold", { + expect_true(exists("node_is_fold")) + test <- node_is_fold(create_explicit(A-B, B-C, A-C, C-D, C-E, D-E)) + test_that("returns correct values", { + expect_equal(as.logical(test), c(F,F,T,F,F)) + }) + test_that("returns correct type", { + expect_s3_class(test, "node_mark") + }) }) test_that("node_is_max works", { @@ -36,9 +59,6 @@ test_that("additional node mark functions work", { c("FALSE", "FALSE", "TRUE", "TRUE", "FALSE", "FALSE", "FALSE", "FALSE", "TRUE", "FALSE", "FALSE")) set.seed(1234) - expect_equal(as.character(node_is_fold(create_explicit(A-B, B-C, A-C, C-D, C-E, D-E))), - c("FALSE", "FALSE", "TRUE", "FALSE", "FALSE")) - set.seed(1234) expect_equal(as.character(node_is_mentor(ison_adolescents)), c("FALSE", "TRUE", "TRUE", "FALSE", "FALSE", "FALSE", "FALSE", "FALSE")) set.seed(1234) diff --git a/tests/testthat/test-measure_centrality.R b/tests/testthat/test-measure_centrality.R index e5aceab0..836d3158 100644 --- a/tests/testthat/test-measure_centrality.R +++ b/tests/testthat/test-measure_centrality.R @@ -67,16 +67,15 @@ test_that("two mode betweenness centrality calculated correctly",{ }) test_that("one mode eigenvector centrality calculated correctly",{ - expect_equal(top3(node_eigenvector(ison_adolescents, normalized = FALSE)), c(0.16, 0.491, 0.529), tolerance = 0.001) - expect_equal(top3(node_eigenvector(ison_adolescents, normalized = TRUE)), c(0.227, 0.694, 0.748), tolerance = 0.001) + # expect_equal(top3(node_eigenvector(ison_adolescents, normalized = FALSE)), c(0.16, 0.491, 0.529), tolerance = 0.001) + expect_equal(top3(node_eigenvector(ison_adolescents)), c(0.303, 0.928, 1), tolerance = 0.001) }) test_that("two mode eigenvector centrality calculated correctly",{ - expect_equal(top3(node_eigenvector(test_mat, normalized = FALSE)), c(0.3185, 0.3004, 0.3536)) - expect_equal(top3(node_eigenvector(test_igr, normalized = FALSE)), c(0.3185, 0.3004, 0.3536)) - expect_equal(bot3(node_eigenvector(test_mat, normalized = FALSE)), c(0.2156, 0.1316, 0.1316)) - expect_equal(bot3(node_eigenvector(test_igr, normalized = FALSE)), c(0.2156, 0.1316, 0.1316)) - expect_equal(top3(node_eigenvector(test_igr, normalized = TRUE)), c(0.4505, 0.4248, 0.5000)) + expect_equal(top3(node_eigenvector(test_mat)), c(0.9009, 0.8497, 1)) + expect_equal(bot3(node_eigenvector(test_mat)), c(0.4764, 0.2907, 0.2907)) + expect_equal(top3(node_eigenvector(test_igr)), c(0.9009, 0.8497, 1)) + expect_equal(bot3(node_eigenvector(test_igr)), c(0.4764, 0.2907, 0.2907)) }) test_that("node measure class works", { diff --git a/tests/testthat/test-motif_census.R b/tests/testthat/test-motif_census.R index 26b05bfe..9b142bd4 100644 --- a/tests/testthat/test-motif_census.R +++ b/tests/testthat/test-motif_census.R @@ -33,8 +33,8 @@ test_that("net_triad census works", { expect_error(net_by_triad(ison_southern_women)) }) -test <- node_by_quad(ison_southern_women) -test_that("node quad census works", { +test <- node_by_tetrad(ison_southern_women) +test_that("node tetrad census works", { expect_s3_class(test, "node_motif") expect_equal(test[1,1], 1241) })