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("
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.
+ + + + +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?
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:
# 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…
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.
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?
And let’s calculate transitivity in the task network. Again, -can you guess the correct name of this function?
+And let’s calculate + +transitivity in the task network. Again, can you guess the +correct name of this function?
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")
+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.
+ +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 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))
+
+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.
+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.
+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"))
+
+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.
+Ok, the friendship network has 3-4 components, but how many ‘groups’ @@ -746,203 +1044,114 @@
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")
-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:
-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)
+
+
Here are some of the terms that we have covered in this module:
++ -
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?
-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 @@
# 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.
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.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 @@Ok, so now we have a result from establishing nodes’ membership in @@ -590,6 +588,7 @@
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 @@
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):
By passing the membership argument our structural equivalence @@ -661,18 +660,19 @@
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.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.
+Here are some of the terms that we have covered in this module:
+@@ -859,28 +886,29 @@
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.
lawfirm <- to_undirected(ison_lawfirm) |> to_uniplex("friends")
+lawfirm <- ison_lawfirm |> to_uniplex("friends") |> to_undirected()
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.
ison_adolescents
network are
+cutpoints.
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 .Where would you target your efforts if you wanted to fragment this -network? +network?
+Here are some of the terms that we have covered in this module:
+@@ -1454,11 +1494,11 @@