Browse code

Added maxWidth_nchar_plot to performAllNetworkAnalyses, other small updates

Christian Arnold authored on 05/07/2022 09:20:59
Showing 14 changed files

... ...
@@ -2218,6 +2218,9 @@ addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails
2218 2218
       
2219 2219
     } # end for each TF
2220 2220
     
2221
+    futile.logger::flog.info(paste0("Stored ", nrow(tblFilt.df), " connections with an FDR <= ", maxFDRToStore))
2222
+    
2223
+    
2221 2224
     .printExecutionTime(start2, prefix = "  ")
2222 2225
     
2223 2226
   } # end for each connectionType
... ...
@@ -197,6 +197,7 @@ build_eGRN_graph <- function(GRN, model_TF_gene_nodes_separately = FALSE,
197 197
 #' @inheritParams plotCommunitiesStats
198 198
 #' @inheritParams plotCommunitiesEnrichment
199 199
 #' @inheritParams calculateCommunitiesStats
200
+#' @template maxWidth_nchar_plot
200 201
 #' @export
201 202
 #' @examples 
202 203
 #' # See the Workflow vignette on the GRaNIE website for examples
... ...
@@ -209,6 +210,7 @@ performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"),
209 210
                                       clustering = "louvain",
210 211
                                       communities = seq_len(10), display = "byRank",
211 212
                                       topnGenes = 20, topnTFs = 20,
213
+                                      maxWidth_nchar_plot = 50,
212 214
                                       display_pAdj = FALSE,
213 215
                                       outputFolder = NULL,
214 216
                                       forceRerun = FALSE) {
... ...
@@ -222,7 +224,8 @@ performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"),
222 224
   
223 225
   GRN = calculateGeneralEnrichment(GRN, ontology = ontology, algorithm = algorithm, statistic = statistic, 
224 226
                                    background = background, forceRerun = forceRerun)
225
-  GRN = plotGeneralEnrichment(GRN, outputFolder = outputFolder, display_pAdj = display_pAdj, forceRerun = forceRerun) 
227
+  GRN = plotGeneralEnrichment(GRN, outputFolder = outputFolder, display_pAdj = display_pAdj, 
228
+                              maxWidth_nchar_plot = maxWidth_nchar_plot, forceRerun = forceRerun) 
226 229
   
227 230
   
228 231
   GRN = calculateCommunitiesStats(GRN, clustering = clustering, forceRerun = forceRerun)
... ...
@@ -234,13 +237,15 @@ performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"),
234 237
                                        background = background, forceRerun = forceRerun)
235 238
   
236 239
   GRN = plotCommunitiesEnrichment(GRN, outputFolder = outputFolder, display = display, communities = communities, 
237
-                                  display_pAdj = display_pAdj, forceRerun = forceRerun)
240
+                                  display_pAdj = display_pAdj,  maxWidth_nchar_plot = maxWidth_nchar_plot,
241
+                                  forceRerun = forceRerun)
238 242
   
239 243
   GRN = calculateTFEnrichment(GRN, ontology = ontology, algorithm = algorithm, statistic = statistic,
240 244
                               background = background, pAdjustMethod = "BH",
241 245
                               forceRerun = forceRerun)
242 246
   
243
-  GRN = plotTFEnrichment(GRN, display_pAdj = display_pAdj, outputFolder = outputFolder, forceRerun = forceRerun)
247
+  GRN = plotTFEnrichment(GRN, display_pAdj = display_pAdj, outputFolder = outputFolder, maxWidth_nchar_plot = maxWidth_nchar_plot,
248
+                         forceRerun = forceRerun)
244 249
   
245 250
   
246 251
   .printExecutionTime(start)
... ...
@@ -92,7 +92,7 @@ plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL,
92 92
                        "_RNA.", norm, ".pdf")
93 93
       if (!file.exists(fileCur) | forceRerun) {
94 94
         
95
-        futile.logger::flog.info(paste0("\nPlotting PCA and metadata correlation of ", norm, 
95
+        futile.logger::flog.info(paste0("Plotting PCA and metadata correlation of ", norm, 
96 96
                                         " RNA data for all shared samples to file ", fileCur , 
97 97
                                         "... This may take a few minutes"))
98 98
         
... ...
@@ -2141,7 +2141,7 @@ plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NUL
2141 2141
 #' @param p Numeric. Default 0.05. p-value threshold to determine significance.
2142 2142
 #' @param topn_pvalue Numeric. Default 30. Maximum number of ontology terms that meet the p-value significance threshold to display in the enrichment dot plot
2143 2143
 #' @param display_pAdj \code{TRUE} or \code{FALSE}. Default \code{FALSE}. Is the p-value being displayed in the plots the adjusted p-value? This parameter is relevant for KEGG, Disease Ontology, and Reactome enrichments, and does not affect GO enrichments.
2144
-#' @param maxWidth_nchar_plot Integer (>=10). Default 50. Maximum number of characters for a term before it is truncated.
2144
+#' @template maxWidth_nchar_plot
2145 2145
 #' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results.
2146 2146
 #' @examples 
2147 2147
 #' # See the Workflow vignette on the GRaNIE website for examples
... ...
@@ -2511,7 +2511,7 @@ plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL
2511 2511
 #' @param communities \code{NULL} or numeric vector. Default \code{NULL}. If set to \code{NULL}, the default, all communities enrichments that have been calculated before are plotted. If a numeric vector is specified: Depending on what was specified in the \code{display} parameter, this parameter indicates either the rank or the label of the communities to be plotted. i.e. for \code{communities = c(1,4)}, if \code{display = "byRank"} the results for the first and fourth largest communities are plotted. if \code{display = "byLabel"}, the results for the communities labeled \code{"1"}, and \code{"4"} are plotted. 
2512 2512
 #' @param nSignificant Numeric. Default 3. Threshold to filter out an ontology term with less than \code{nSignificant} overlapping genes. 
2513 2513
 #' @param nID Numeric. Default 10. For the reduced heatmap, number of top terms to select per community.
2514
-#' @param maxWidth_nchar_plot Integer (>=10). Default 50. Maximum number of characters for a term before it is truncated.
2514
+#' @template maxWidth_nchar_plot
2515 2515
 #' @return  The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results.
2516 2516
 #' @examples 
2517 2517
 #' # See the Workflow vignette on the GRaNIE website for examples
... ...
@@ -2693,7 +2693,6 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput =
2693 2693
         dplyr::filter(!is.na(Term)) %>%
2694 2694
         dplyr::select(Term, dplyr::any_of(communities.order)) %>% # reorder the table based on the previously generated custom order
2695 2695
         dplyr::mutate_at(dplyr::vars(!dplyr::contains("Term")), function(x){return(-log10(x))}) %>%
2696
-        # dplyr::mutate(Term_mod = make.names(stringr::str_trunc(as.character(Term), width = maxWidth_nchar_plot, side = "right"), unique = TRUE)) %>%
2697 2696
         tibble::column_to_rownames("Term") %>%
2698 2697
         as.matrix()
2699 2698
       
... ...
@@ -3289,7 +3288,7 @@ plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL
3289 3288
 #' @param maxRowsToPlot Numeric. Default 500. Refers to the maximum number of connections to be plotted.
3290 3289
 #' @param graph Character. Default \code{TF-gene}. One of: \code{TF-gene}, \code{TF-peak-gene}. Whether to plot a graph with links from TFs to peaks to gene, or the graph with the inferred TF to gene connections.
3291 3290
 #' @param colorby Character. Default \code{type}. One of \code{type}, code \code{community}. Color the vertices by either type (TF/peak/gene) or community. See \code{\link{calculateCommunitiesStats}}
3292
-#' @param layered Boolean. Default \code{FALSE}. Display the network in a layered format where each layer corresponds to a node type (TF/peak/gene).
3291
+#' @param layout Character. Dfault \code{fr}. One of \code{star}, \code{fr}, \code{sugiyama}, \code{kk}, \code{lgl}, \code{graphopt}, \code{mds}, \code{sphere}
3293 3292
 #' @param vertice_color_TFs Named list. Default \code{list(h = 10, c = 85, l = c(25, 95))}. The list must specify the color in hcl format (hue, chroma, luminence). See the \code{colorspace} package for more details and examples
3294 3293
 #' @param vertice_color_peaks Named list. Default \code{list(h = 135, c = 45, l = c(35, 95))}.
3295 3294
 #' @param vertice_color_genes Named list. Default \code{list(h = 260, c = 80, l = c(30, 90))}.
... ...
@@ -3302,596 +3301,617 @@ plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL
3302 3301
 #' @return the GRN object
3303 3302
 #' @export
3304 3303
 visualizeGRN <- function(GRN, outputFolder = NULL,  basenameOutput = NULL, plotAsPDF = TRUE, pdf_width = 12, pdf_height = 12,
3305
-                         title = NULL, maxRowsToPlot = 500, graph = "TF-gene" , colorby = "type", layered = FALSE,
3304
+                         title = NULL, maxRowsToPlot = 500, graph = "TF-gene" , colorby = "type", layout = "fr",
3306 3305
                          vertice_color_TFs = list(h = 10, c = 85, l = c(25, 95)), vertice_color_peaks = list(h = 135, c = 45, l = c(35, 95)), vertice_color_genes = list(h = 260, c = 80, l = c(30, 90)),
3307 3306
                          vertexLabel_cex = 0.4, vertexLabel_dist = 0, forceRerun = FALSE
3308 3307
 ) {
3309
-  
3310
-  
3311
-  start = Sys.time()
3312
-  GRN = .addFunctionLogToObject(GRN)
3313
-  
3314
-  checkmate::assertFlag(plotAsPDF)
3315
-  checkmate::assertNumeric(pdf_width, lower = 5, upper = 99)
3316
-  checkmate::assertNumeric(pdf_height, lower = 5, upper = 99)
3317
-  checkmate::assertNumeric(maxRowsToPlot)
3318
-  checkmate::assertSubset(graph, c("TF-gene", "TF-peak-gene"))
3319
-  checkmate::assertSubset(colorby, c("type", "community"))
3320
-  checkmate::assertFlag(layered)
3321
-  checkmate::assertList(vertice_color_TFs)
3322
-  checkmate::assertNames(names(vertice_color_TFs), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3323
-  checkmate::assertList(vertice_color_peaks)
3324
-  checkmate::assertNames(names(vertice_color_peaks), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3325
-  checkmate::assertList(vertice_color_genes)
3326
-  checkmate::assertNames(names(vertice_color_genes), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3327
-  checkmate::assertNumeric(vertexLabel_cex)
3328
-  checkmate::assertNumeric(vertexLabel_dist)
3329
-  checkmate::assertFlag(forceRerun)
3330
-  
3331
-  
3332
-  outputFolder = .checkOutputFolder(GRN, outputFolder)
3333
-  
3334
-  metadata_visualization.l = getBasic_metadata_visualization(GRN)
3335
-  # if (useDefaultMetadata) {
3336
-  #   metadata_visualization.l = getBasic_metadata_visualization(GRN)
3337
-  #   vertice_color_TFs   = list(metadata_visualization.l[["RNA_expression_TF"]],    "HOCOID",     "baseMean_log")
3338
-  #   vertice_color_genes = list(metadata_visualization.l[["RNA_expression_genes"]], "ENSEMBL_ID", "baseMean_log")
3339
-  #   vertice_color_peaks = list(metadata_visualization.l[["Peaks_accessibility"]],   "peakID",     "mean_log")
3340
-  # }
3341
-  # 
3342
-  #grn.merged = getGRNConnections(GRN, permuted = permuted, type = "all.filtered")
3343
-  # check that it's in sync with the @ graph
3344
-  if (graph == "TF-gene"){
3345
-    grn.merged = GRN@graph$TF_gene$table %>%
3346
-      dplyr::rename(TF.name = V1_name)
3347
-    
3348
-    edges_final = grn.merged %>%
3349
-      dplyr::rename(from = TF.name, to = V2) %>%
3350
-      dplyr::mutate(weight = 1, R = 1, linetype = "solid")
3351
-    
3352
-  }else{
3353
-    
3354
-    grn.merged = GRN@graph$TF_peak_gene$table %>%
3355
-      dplyr::rename(TF.name = V1_name) 
3356
-    grn.merged$V1[!is.na(grn.merged$TF.name)] = as.character(grn.merged$TF.name[!is.na(grn.merged$TF.name)]) # replace TF ensembl with TF name
3357
-    
3358
-    edges_final = grn.merged %>%
3359
-      dplyr::mutate(R = as.vector(stats::na.omit(c(TF_peak.r, peak_gene.r))),
3360
-                    weight = as.vector(stats::na.omit(c(1- TF_peak.fdr, peak_gene.r))),
3361
-                    linetype = "solid") %>%
3362
-      dplyr::rename(from = V1, to = V2) 
3363
-    
3364
-  }
3365
-  
3366
-  edges_final = edges_final %>%
3367
-    dplyr::mutate(weight_transformed = dplyr::case_when(weight < 0.2 ~ 1,
3368
-                                                        weight < 0.4 ~ 1.5,
3369
-                                                        weight < 0.6 ~ 2,
3370
-                                                        weight < 0.8 ~ 2.5,
3371
-                                                        TRUE ~ 3),
3372
-                  R_direction = dplyr::case_when(R < 0 ~ "neg", TRUE ~ "pos"),
3373
-                  color       = dplyr::case_when(R < 0 ~ "blue", TRUE ~ "grey")) %>%
3374
-    dplyr::select(.data$from, .data$to, .data$weight, .data$R, .data$linetype, .data$weight_transformed, .data$R_direction, .data$color)
3375
-  
3376
-  
3377
-  
3378
-  nRows = nrow(edges_final)
3379
-  
3380
-  futile.logger::flog.info(paste0("Number of rows: ",nRows))
3381
-  if (maxRowsToPlot > 500 & nRows > 500) {
3382
-    futile.logger::flog.info(paste0("Plotting many connections takes a lot of time and memory"))
3383
-  }
3384
-  
3385
-  
3386
-  
3387
-  if (plotAsPDF) {
3388
-    futile.logger::flog.info(paste0("Plotting GRN network to ", outputFolder, dplyr::if_else(is.null(basenameOutput), .getOutputFileName("plot_network"), basenameOutput),".pdf"))
3389
-    grDevices::pdf(file = paste0(outputFolder,"/", ifelse(is.null(basenameOutput), .getOutputFileName("plot_network"), basenameOutput),".pdf"), width = pdf_width, height = pdf_height )
3390
-  } else {
3391
-    futile.logger::flog.info(paste0("Plotting GRN network"))
3392
-  }
3393
-  
3394
-  if (nRows > maxRowsToPlot) { 
3395
-    futile.logger::flog.info(paste0("Number of rows to plot (", nRows, ") exceeds limit of the maxRowsToPlot parameter. Plotting only empty page"))
3396
-    plot(c(0, 1), c(0, 1), ann = FALSE, bty = 'n', type = 'n', xaxt = 'n', yaxt = 'n', main = title)
3397
-    message = paste0(title, "\n\nPlotting omitted.\n\nThe number of rows in the GRN (", nRows, ") exceeds the maximum of ", maxRowsToPlot, ".\nSee the maxRowsToPlot parameter to increase the limit")
3398
-    text(x = 0.5, y = 0.5, message, cex = 1.6, col = "red")
3399 3308
     
3400
-    if (plotAsPDF) {
3401
-      grDevices::dev.off()
3402
-    }
3403 3309
     
3404
-    .printExecutionTime(start)
3405
-    return(GRN)
3406
-  }
3407
-  
3408
-  if (nrow(grn.merged) == 0) {
3409
-    
3410
-    futile.logger::flog.warn(paste0("No rows left in the GRN. Creating empty plot."))
3411
-    
3412
-    plot(c(0, 1), c(0, 1), ann = FALSE, bty = 'n', type = 'n', xaxt = 'n', yaxt = 'n', main = title)
3413
-    message = paste0(title, "\n\nThe GRN has no edges that pass the filter criteria.")
3414
-    text(x = 0.5, y = 0.5, message, cex = 1.6, col = "red")
3415
-    
3416
-  } else {
3417
-    
3418
-    # Fix with length
3419
-    
3420
-    if (graph == "TF-peak-gene"){
3421
-      colors_categories.l = list(
3422
-        "TF"   = RColorBrewer::brewer.pal(3,"Set1")[1], 
3423
-        "PEAK" = RColorBrewer::brewer.pal(3,"Set1")[2], 
3424
-        "GENE" = RColorBrewer::brewer.pal(3,"Set1")[3])
3425
-      
3426
-      symbols_categories.l = list(
3427
-        "TF"   = 15, # square
3428
-        "PEAK" = 21, # circle
3429
-        "GENE" = 21 # circle
3430
-      )
3310
+    start = Sys.time()
3311
+    GRN = .addFunctionLogToObject(GRN)
3312
+    
3313
+    checkmate::assertFlag(plotAsPDF)
3314
+    checkmate::assertNumeric(pdf_width, lower = 5, upper = 99)
3315
+    checkmate::assertNumeric(pdf_height, lower = 5, upper = 99)
3316
+    checkmate::assertNumeric(maxRowsToPlot)
3317
+    checkmate::assertSubset(graph, c("TF-gene", "TF-peak-gene"))
3318
+    checkmate::assertSubset(colorby, c("type", "community"))
3319
+    #checkmate::assertFlag(layered)
3320
+    checkmate::assertSubset(layout, c("star", "fr", "sugiyama", "kk", "lgl", "graphopt", "mds", "sphere"))
3321
+    checkmate::assertList(vertice_color_TFs)
3322
+    checkmate::assertNames(names(vertice_color_TFs), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3323
+    checkmate::assertList(vertice_color_peaks)
3324
+    checkmate::assertNames(names(vertice_color_peaks), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3325
+    checkmate::assertList(vertice_color_genes)
3326
+    checkmate::assertNames(names(vertice_color_genes), must.include = c("h", "c", "l"), subset.of = c("h", "c", "l"))
3327
+    checkmate::assertNumeric(vertexLabel_cex)
3328
+    checkmate::assertNumeric(vertexLabel_dist)
3329
+    checkmate::assertFlag(forceRerun)
3330
+    
3331
+    
3332
+    outputFolder = .checkOutputFolder(GRN, outputFolder)
3333
+    
3334
+    metadata_visualization.l = getBasic_metadata_visualization(GRN)
3335
+    # if (useDefaultMetadata) {
3336
+    #   metadata_visualization.l = getBasic_metadata_visualization(GRN)
3337
+    #   vertice_color_TFs   = list(metadata_visualization.l[["RNA_expression_TF"]],    "HOCOID",     "baseMean_log")
3338
+    #   vertice_color_genes = list(metadata_visualization.l[["RNA_expression_genes"]], "ENSEMBL_ID", "baseMean_log")
3339
+    #   vertice_color_peaks = list(metadata_visualization.l[["Peaks_accessibility"]],   "peakID",     "mean_log")
3340
+    # }
3341
+    # 
3342
+    #grn.merged = getGRNConnections(GRN, permuted = permuted, type = "all.filtered")
3343
+    # check that it's in sync with the @ graph
3344
+    if (graph == "TF-gene"){
3345
+        grn.merged = GRN@graph$TF_gene$table %>%
3346
+            dplyr::rename(TF.name = V1_name)
3347
+        
3348
+        edges_final = grn.merged %>%
3349
+            dplyr::rename(from = TF.name, to = V2) %>%
3350
+            dplyr::mutate(weight = 1, R = 1, linetype = "solid")
3351
+        
3431 3352
     }else{
3432
-      colors_categories.l = list(
3433
-        "TF"   = RColorBrewer::brewer.pal(3,"Set1")[1], 
3434
-        "GENE" = RColorBrewer::brewer.pal(3,"Set1")[3])
3435
-      
3436
-      symbols_categories.l = list(
3437
-        "TF"   = 15, # square
3438
-        "GENE" = 21 # circle
3439
-      )
3353
+        
3354
+        grn.merged = GRN@graph$TF_peak_gene$table %>%
3355
+            dplyr::rename(TF.name = V1_name) 
3356
+        grn.merged$V1[!is.na(grn.merged$TF.name)] = as.character(grn.merged$TF.name[!is.na(grn.merged$TF.name)]) # replace TF ensembl with TF name
3357
+        
3358
+        edges_final = grn.merged %>%
3359
+            dplyr::mutate(R = as.vector(stats::na.omit(c(TF_peak.r, peak_gene.r))),
3360
+                          weight = as.vector(stats::na.omit(c(1- TF_peak.fdr, peak_gene.r))),
3361
+                          linetype = "solid") %>%
3362
+            dplyr::rename(from = V1, to = V2) 
3363
+        
3440 3364
     }
3441 3365
     
3366
+    edges_final = edges_final %>%
3367
+        dplyr::mutate(weight_transformed = dplyr::case_when(weight < 0.2 ~ 1,
3368
+                                                            weight < 0.4 ~ 1.5,
3369
+                                                            weight < 0.6 ~ 2,
3370
+                                                            weight < 0.8 ~ 2.5,
3371
+                                                            TRUE ~ 3),
3372
+                      R_direction = dplyr::case_when(R < 0 ~ "neg", TRUE ~ "pos"),
3373
+                      color       = dplyr::case_when(R < 0 ~ "blue", TRUE ~ "grey")) %>%
3374
+        dplyr::select(.data$from, .data$to, .data$weight, .data$R, .data$linetype, .data$weight_transformed, .data$R_direction, .data$color)
3442 3375
     
3443
-    nBins_orig = 100
3444
-    nBins_discard = 25
3445
-    nBins_real = nBins_orig - nBins_discard
3446
-    
3447
-    #if (!is.null(vertice_color_TFs)) {
3448
-    color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_TFs[["h"]], c = vertice_color_TFs[["c"]], l = vertice_color_TFs[["l"]]))[(nBins_discard + 1):nBins_orig] # red
3449
-    colors_categories.l[["TF"]]  = c(color_gradient[1], color_gradient[nBins_real]) 
3450
-    colors_categories.l[["TF"]]  = color_gradient 
3451
-    symbols_categories.l[["TF"]] = c(15,NA,15)
3452
-    vertice_color_TFs   = append(list(metadata_visualization.l[["RNA_expression_TF"]],    "HOCOID",     "baseMean_log"), vertice_color_TFs)
3453
-    #}
3454
-    
3455
-    if(graph == "TF-peak-gene"){
3456
-      #if (!is.null(vertice_color_peaks)) {
3457
-      color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_peaks[["h"]], c = vertice_color_peaks[["c"]], l = vertice_color_peaks[["l"]]))[(nBins_discard + 1):nBins_orig]  # green
3458
-      colors_categories.l[["PEAK"]] = c(color_gradient[1], color_gradient[nBins_real])
3459
-      colors_categories.l[["PEAK"]] = color_gradient
3460
-      symbols_categories.l[["PEAK"]] = c(21,NA,21)
3461
-      vertice_color_peaks = append(list(metadata_visualization.l[["Peaks_accessibility"]],   "peakID",     "mean_log"), vertice_color_peaks)
3462
-      # }
3463
-    }
3464 3376
     
3465
-    #if (!is.null(vertice_color_genes)) {
3466
-    color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_genes[["h"]], c = vertice_color_genes[["c"]], l = vertice_color_genes[["l"]]))[(nBins_discard + 1):nBins_orig] # blue
3467
-    colors_categories.l[["GENE"]] = c(color_gradient[1], color_gradient[nBins_real]) 
3468
-    colors_categories.l[["GENE"]] = color_gradient
3469
-    symbols_categories.l[["GENE"]] = c(21,NA,21)
3470
-    vertice_color_genes = append(list(metadata_visualization.l[["RNA_expression_genes"]], "ENSEMBL_ID", "baseMean_log"), vertice_color_genes)
3471
-    #}
3472 3377
     
3473
-    ## VERTICES ##
3474
-    
3475
-    shape_vertex = c("square","circle", "circle")
3476
-    names(shape_vertex) = names(colors_categories.l)
3378
+    nRows = nrow(edges_final)
3477 3379
     
3380
+    futile.logger::flog.info(paste0("Number of rows: ",nRows))
3381
+    if (maxRowsToPlot > 500 & nRows > 500) {
3382
+        futile.logger::flog.info(paste0("Plotting many connections takes a lot of time and memory"))
3383
+    }
3478 3384
     
3479
-    vertices = tibble::tribble(~id,
3480
-                               ~type,
3481
-                               ~label,
3482
-                               ~color_raw,
3483
-                               ~color_bin,
3484
-                               ~color_final)
3485 3385
     
3486
-    ## 1. TFs ##
3487 3386
     
3488
-    # Make the vertices unique, so that the same peak has only one vertice 
3489
-    # vertices_TFs = unique_TF_peak.con %>%
3490
-    #   dplyr::group_by(TF.name) %>%
3491
-    #   dplyr::summarize(label = unique(TF.name)) %>%
3492
-    #   dplyr::ungroup()
3387
+    if (plotAsPDF) {
3388
+        futile.logger::flog.info(paste0("Plotting GRN network to ", outputFolder, dplyr::if_else(is.null(basenameOutput), .getOutputFileName("plot_network"), basenameOutput),".pdf"))
3389
+        grDevices::pdf(file = paste0(outputFolder,"/", ifelse(is.null(basenameOutput), .getOutputFileName("plot_network"), basenameOutput),".pdf"), width = pdf_width, height = pdf_height )
3390
+    } else {
3391
+        futile.logger::flog.info(paste0("Plotting GRN network"))
3392
+    }
3493 3393
     
3494
-    vertices_TFs = grn.merged %>%
3495
-      dplyr::filter(grepl("^tf", connectionType)) %>%
3496
-      #dplyr::rename(TF.name = V1) %>%
3497
-      dplyr::group_by(TF.name) %>%
3498
-      dplyr::summarize(label = unique(TF.name)) %>%
3499
-      dplyr::ungroup()
3394
+    if (nRows > maxRowsToPlot) { 
3395
+        futile.logger::flog.info(paste0("Number of rows to plot (", nRows, ") exceeds limit of the maxRowsToPlot parameter. Plotting only empty page"))
3396
+        plot(c(0, 1), c(0, 1), ann = FALSE, bty = 'n', type = 'n', xaxt = 'n', yaxt = 'n', main = title)
3397
+        message = paste0(title, "\n\nPlotting omitted.\n\nThe number of rows in the GRN (", nRows, ") exceeds the maximum of ", maxRowsToPlot, ".\nSee the maxRowsToPlot parameter to increase the limit")
3398
+        text(x = 0.5, y = 0.5, message, cex = 1.6, col = "red")
3399
+        
3400
+        if (plotAsPDF) {
3401
+            grDevices::dev.off()
3402
+        }
3403
+        
3404
+        .printExecutionTime(start)
3405
+        return(GRN)
3406
+    }
3500 3407
     
3501
-    if (nrow(vertices_TFs) > 0) {
3502
-      
3503
-      if (!is.null(vertice_color_TFs)) {
3408
+    if (nrow(grn.merged) == 0) {
3504 3409
         
3505
-        .verifyArgument_verticeType(vertice_color_TFs)
3410
+        futile.logger::flog.warn(paste0("No rows left in the GRN. Creating empty plot."))
3506 3411
         
3507
-        vertices_TFs = vertices_TFs %>%
3508
-          dplyr::left_join(vertice_color_TFs[[1]], by = c("TF.name" = vertice_color_TFs[[2]])) %>%
3509
-          dplyr::rename(color_raw = !!(vertice_color_TFs[[3]])) %>%
3510
-          dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["TF"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3412
+        plot(c(0, 1), c(0, 1), ann = FALSE, bty = 'n', type = 'n', xaxt = 'n', yaxt = 'n', main = title)
3413
+        message = paste0(title, "\n\nThe GRN has no edges that pass the filter criteria.")
3414
+        text(x = 0.5, y = 0.5, message, cex = 1.6, col = "red")
3511 3415
         
3416
+    } else {
3512 3417
         
3513
-      } else {
3514
-        vertices_TFs = dplyr::mutate(vertices_TFs, color_raw = NA, color_bin = colors_categories.l[["TF"]])
3515
-      } 
3516
-      
3517
-      vertices = tibble::add_row(vertices, 
3518
-                                 id = vertices_TFs$TF.name, 
3519
-                                 type = "TF", 
3520
-                                 label = as.vector(vertices_TFs$label), 
3521
-                                 color_raw = vertices_TFs$color_raw,
3522
-                                 color_bin = vertices_TFs$color_bin) 
3523
-    }
3524
-    
3525
-    
3526
-    ## 2. PEAKS ##
3527
-    
3528
-    if (graph == "TF-peak-gene"){
3529
-      
3530
-      # Make the vertices unique, so that the same peak has only one vertice 
3531
-      peaks1 = grn.merged %>% dplyr::filter(grepl("peak$", connectionType)) %>% dplyr::pull(V2)
3532
-      peaks2 = grn.merged %>% dplyr::filter(grepl("^peak", connectionType)) %>% dplyr::pull(V1)
3533
-      #vertices_peaks = tibble::tibble(peak = unique(c(unique_peak_gene.con$peak.ID, unique_TF_peak.con$peak.ID)), label = NA)
3534
-      vertices_peaks = tibble::tibble(peak = unique(c(peaks1, peaks2)), label = NA)
3535
-      
3536
-      if (nrow(vertices_peaks) > 0) {
3418
+        # Fix with length
3537 3419
         
3538
-        if (!is.null(vertice_color_peaks)) {
3539
-          
3540
-          .verifyArgument_verticeType(vertice_color_peaks)
3541
-          
3542
-          vertices_peaks = vertices_peaks %>%
3543
-            dplyr::left_join(vertice_color_peaks[[1]], by = c("peak" = vertice_color_peaks[[2]])) %>%
3544
-            dplyr::rename(color_raw = !!(vertice_color_peaks[[3]])) %>%
3545
-            dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["PEAK"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3546
-          
3547
-        } else {
3548
-          vertices_peaks = dplyr::mutate(vertices_peaks, color_raw = NA, color_bin = colors_categories.l[["PEAK"]])
3549
-        } 
3420
+        if (graph == "TF-peak-gene"){
3421
+            colors_categories.l = list(
3422
+                "TF"   = RColorBrewer::brewer.pal(3,"Set1")[1], 
3423
+                "PEAK" = RColorBrewer::brewer.pal(3,"Set1")[2], 
3424
+                "GENE" = RColorBrewer::brewer.pal(3,"Set1")[3])
3425
+            
3426
+            symbols_categories.l = list(
3427
+                "TF"   = 15, # square
3428
+                "PEAK" = 21, # circle
3429
+                "GENE" = 21 # circle
3430
+            )
3431
+        }else{
3432
+            colors_categories.l = list(
3433
+                "TF"   = RColorBrewer::brewer.pal(3,"Set1")[1], 
3434
+                "GENE" = RColorBrewer::brewer.pal(3,"Set1")[3])
3435
+            
3436
+            symbols_categories.l = list(
3437
+                "TF"   = 15, # square
3438
+                "GENE" = 21 # circle
3439
+            )
3440
+        }
3550 3441
         
3551
-        vertices = tibble::add_row(vertices, 
3552
-                                   id = vertices_peaks$peak, 
3553
-                                   type = "PEAK", 
3554
-                                   label = vertices_peaks$label, 
3555
-                                   color_raw = vertices_peaks$color_raw,
3556
-                                   color_bin = vertices_peaks$color_bin) 
3557
-      }
3558
-      
3559
-    }
3560
-    
3561
-    
3562
-    ## 3. GENES ##
3563
-    
3564
-    # Make the vertices unique, so that the same gene has only one vertice 
3565
-    # vertices_genes = unique_peak_gene.con %>%
3566
-    #   dplyr::group_by(gene.ENSEMBL) %>%
3567
-    #   dplyr::summarize(label = NA) %>% #, id2 = paste0(SYMBOL, collapse = ",")) %>%
3568
-    #   dplyr::ungroup()
3569
-    
3570
-    vertices_genes = grn.merged %>%
3571
-      dplyr::filter(grepl("gene$", connectionType)) %>%
3572
-      #dplyr::rename(peak.ID = V1) %>%
3573
-      dplyr::group_by(V2) %>%
3574
-      dplyr::summarize(label = NA) %>% #, id2 = paste0(SYMBOL, collapse = ",")) %>%
3575
-      dplyr::ungroup() %>%
3576
-      dplyr::rename(gene.ENSEMBL = V2)
3577
-    
3578
-    if (nrow(vertices_genes) > 0) {
3579
-      
3580
-      if (!is.null(vertice_color_genes)) {
3581 3442
         
3582
-        .verifyArgument_verticeType(vertice_color_genes)
3443
+        nBins_orig = 100
3444
+        nBins_discard = 25
3445
+        nBins_real = nBins_orig - nBins_discard
3446
+        
3447
+        #if (!is.null(vertice_color_TFs)) {
3448
+        color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_TFs[["h"]], c = vertice_color_TFs[["c"]], l = vertice_color_TFs[["l"]]))[(nBins_discard + 1):nBins_orig] # red
3449
+        colors_categories.l[["TF"]]  = c(color_gradient[1], color_gradient[nBins_real]) 
3450
+        colors_categories.l[["TF"]]  = color_gradient 
3451
+        symbols_categories.l[["TF"]] = c(15,NA,15)
3452
+        vertice_color_TFs   = append(list(metadata_visualization.l[["RNA_expression_TF"]],    "HOCOID",     "baseMean_log"), vertice_color_TFs)
3453
+        #}
3454
+        
3455
+        if(graph == "TF-peak-gene"){
3456
+            #if (!is.null(vertice_color_peaks)) {
3457
+            color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_peaks[["h"]], c = vertice_color_peaks[["c"]], l = vertice_color_peaks[["l"]]))[(nBins_discard + 1):nBins_orig]  # green
3458
+            colors_categories.l[["PEAK"]] = c(color_gradient[1], color_gradient[nBins_real])
3459
+            colors_categories.l[["PEAK"]] = color_gradient
3460
+            symbols_categories.l[["PEAK"]] = c(21,NA,21)
3461
+            vertice_color_peaks = append(list(metadata_visualization.l[["Peaks_accessibility"]],   "peakID",     "mean_log"), vertice_color_peaks)
3462
+            # }
3463
+        }
3583 3464
         
3584
-        vertices_genes = vertices_genes %>%
3585
-          dplyr::left_join(vertice_color_genes[[1]], by = c("gene.ENSEMBL" = vertice_color_genes[[2]])) %>%
3586
-          dplyr::rename(color_raw = !!(vertice_color_genes[[3]])) %>%
3587
-          dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["GENE"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3465
+        #if (!is.null(vertice_color_genes)) {
3466
+        color_gradient = rev(colorspace::sequential_hcl(nBins_orig, h = vertice_color_genes[["h"]], c = vertice_color_genes[["c"]], l = vertice_color_genes[["l"]]))[(nBins_discard + 1):nBins_orig] # blue
3467
+        colors_categories.l[["GENE"]] = c(color_gradient[1], color_gradient[nBins_real]) 
3468
+        colors_categories.l[["GENE"]] = color_gradient
3469
+        symbols_categories.l[["GENE"]] = c(21,NA,21)
3470
+        vertice_color_genes = append(list(metadata_visualization.l[["RNA_expression_genes"]], "ENSEMBL_ID", "baseMean_log"), vertice_color_genes)
3471
+        #}
3588 3472
         
3589
-      } else {
3590
-        vertices_genes = dplyr::mutate(vertices_genes, color_raw = NA, color_bin = colors_categories.l[["GENE"]])
3591
-      } 
3592
-      
3593
-      
3594
-      vertices = tibble::add_row(vertices, 
3595
-                                 id = vertices_genes$gene.ENSEMBL, 
3596
-                                 type = "GENE", 
3597
-                                 label = vertices_genes$label, 
3598
-                                 color_raw = vertices_genes$color_raw,
3599
-                                 color_bin = vertices_genes$color_bin) 
3600
-      
3601
-    }
3602
-    
3603
-    
3604
-    
3605
-    vertices = vertices %>%
3606
-      dplyr::mutate(size = dplyr::case_when(type == "TF" ~ 6,
3607
-                                            type == "PEAK" ~ 3,
3608
-                                            TRUE ~ 4),
3609
-                    size_transformed = NA) 
3610
-    
3611
-    
3612
-    vertices_colorRanges = vertices %>% dplyr::group_by(.data$type) %>% dplyr::summarize(min = min(color_raw, na.rm = TRUE), max = max(color_raw, na.rm = TRUE))
3613
-    
3614
-    if (nrow(dplyr::filter(vertices_colorRanges, .data$type == "GENE")) == 0) {
3615
-      vertices_colorRanges = tibble::add_row(vertices_colorRanges, type = "GENE", min = NA, max = NA)
3616
-    }
3617
-    
3618
-    if(graph == "TF-peak-gene"){
3619
-      text_categories.l = list(
3620
-        "TF"   = "TF",
3621
-        "PEAK" = "PEAK",
3622
-        "GENE" = "GENE"
3623
-      )
3624
-    }else{
3625
-      text_categories.l = list(
3626
-        "TF"   = "TF",
3627
-        "GENE" = "GENE"
3628
-      )
3629
-    }
3630
-    
3631
-    
3632
-    if (!is.null(vertice_color_TFs)) {
3633
-      subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "TF") 
3634
-      text_categories.l[["TF"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3635
-                                    paste0("TF expression (", vertice_color_TFs[[3]], ")"),
3636
-                                    signif(dplyr::pull(subsetCur, max),2)
3637
-      )
3638
-    }
3639
-    
3640
-    if( graph  == "TF-peak-gene"){
3641
-      if (!is.null(vertice_color_peaks)) {
3642
-        subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "PEAK") 
3643
-        text_categories.l[["PEAK"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3644
-                                        paste0("Peak accessibility (", vertice_color_peaks[[3]], ")"),
3645
-                                        signif(dplyr::pull(subsetCur, max),2)
3473
+        ## VERTICES ##
3474
+        
3475
+        shape_vertex = c("square","circle", "circle")
3476
+        names(shape_vertex) = names(colors_categories.l)
3477
+        
3478
+        
3479
+        vertices = tibble::tribble(~id,
3480
+                                   ~type,
3481
+                                   ~label,
3482
+                                   ~color_raw,
3483
+                                   ~color_bin,
3484
+                                   ~color_final)
3485
+        
3486
+        ## 1. TFs ##
3487
+        
3488
+        # Make the vertices unique, so that the same peak has only one vertice 
3489
+        # vertices_TFs = unique_TF_peak.con %>%
3490
+        #   dplyr::group_by(TF.name) %>%
3491
+        #   dplyr::summarize(label = unique(TF.name)) %>%
3492
+        #   dplyr::ungroup()
3493
+        
3494
+        vertices_TFs = grn.merged %>%
3495
+            dplyr::filter(grepl("^tf", connectionType)) %>%
3496
+            #dplyr::rename(TF.name = V1) %>%
3497
+            dplyr::group_by(TF.name) %>%
3498
+            dplyr::summarize(label = unique(TF.name)) %>%
3499
+            dplyr::ungroup()
3500
+        
3501
+        if (nrow(vertices_TFs) > 0) {
3502
+            
3503
+            if (!is.null(vertice_color_TFs)) {
3504
+                
3505
+                .verifyArgument_verticeType(vertice_color_TFs)
3506
+                
3507
+                vertices_TFs = vertices_TFs %>%
3508
+                    dplyr::left_join(vertice_color_TFs[[1]], by = c("TF.name" = vertice_color_TFs[[2]])) %>%
3509
+                    dplyr::rename(color_raw = !!(vertice_color_TFs[[3]])) %>%
3510
+                    dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["TF"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3511
+                
3512
+                
3513
+            } else {
3514
+                vertices_TFs = dplyr::mutate(vertices_TFs, color_raw = NA, color_bin = colors_categories.l[["TF"]])
3515
+            } 
3516
+            
3517
+            vertices = tibble::add_row(vertices, 
3518
+                                       id = vertices_TFs$TF.name, 
3519
+                                       type = "TF", 
3520
+                                       label = as.vector(vertices_TFs$label), 
3521
+                                       color_raw = vertices_TFs$color_raw,
3522
+                                       color_bin = vertices_TFs$color_bin) 
3523
+        }
3524
+        
3525
+        
3526
+        ## 2. PEAKS ##
3527
+        
3528
+        if (graph == "TF-peak-gene"){
3529
+            
3530
+            # Make the vertices unique, so that the same peak has only one vertice 
3531
+            peaks1 = grn.merged %>% dplyr::filter(grepl("peak$", connectionType)) %>% dplyr::pull(V2)
3532
+            peaks2 = grn.merged %>% dplyr::filter(grepl("^peak", connectionType)) %>% dplyr::pull(V1)
3533
+            #vertices_peaks = tibble::tibble(peak = unique(c(unique_peak_gene.con$peak.ID, unique_TF_peak.con$peak.ID)), label = NA)
3534
+            vertices_peaks = tibble::tibble(peak = unique(c(peaks1, peaks2)), label = NA)
3535
+            
3536
+            if (nrow(vertices_peaks) > 0) {
3537
+                
3538
+                if (!is.null(vertice_color_peaks)) {
3539
+                    
3540
+                    .verifyArgument_verticeType(vertice_color_peaks)
3541
+                    
3542
+                    vertices_peaks = vertices_peaks %>%
3543
+                        dplyr::left_join(vertice_color_peaks[[1]], by = c("peak" = vertice_color_peaks[[2]])) %>%
3544
+                        dplyr::rename(color_raw = !!(vertice_color_peaks[[3]])) %>%
3545
+                        dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["PEAK"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3546
+                    
3547
+                } else {
3548
+                    vertices_peaks = dplyr::mutate(vertices_peaks, color_raw = NA, color_bin = colors_categories.l[["PEAK"]])
3549
+                } 
3550
+                
3551
+                vertices = tibble::add_row(vertices, 
3552
+                                           id = vertices_peaks$peak, 
3553
+                                           type = "PEAK", 
3554
+                                           label = vertices_peaks$label, 
3555
+                                           color_raw = vertices_peaks$color_raw,
3556
+                                           color_bin = vertices_peaks$color_bin) 
3557
+            }
3558
+            
3559
+        }
3560
+        
3561
+        
3562
+        ## 3. GENES ##
3563
+        
3564
+        # Make the vertices unique, so that the same gene has only one vertice 
3565
+        # vertices_genes = unique_peak_gene.con %>%
3566
+        #   dplyr::group_by(gene.ENSEMBL) %>%
3567
+        #   dplyr::summarize(label = NA) %>% #, id2 = paste0(SYMBOL, collapse = ",")) %>%
3568
+        #   dplyr::ungroup()
3569
+        
3570
+        vertices_genes = grn.merged %>%
3571
+            dplyr::filter(grepl("gene$", connectionType)) %>%
3572
+            #dplyr::rename(peak.ID = V1) %>%
3573
+            dplyr::group_by(V2) %>%
3574
+            dplyr::summarize(label = NA) %>% #, id2 = paste0(SYMBOL, collapse = ",")) %>%
3575
+            dplyr::ungroup() %>%
3576
+            dplyr::rename(gene.ENSEMBL = V2)
3577
+        
3578
+        if (nrow(vertices_genes) > 0) {
3579
+            
3580
+            if (!is.null(vertice_color_genes)) {
3581
+                
3582
+                .verifyArgument_verticeType(vertice_color_genes)
3583
+                
3584
+                vertices_genes = vertices_genes %>%
3585
+                    dplyr::left_join(vertice_color_genes[[1]], by = c("gene.ENSEMBL" = vertice_color_genes[[2]])) %>%
3586
+                    dplyr::rename(color_raw = !!(vertice_color_genes[[3]])) %>%
3587
+                    dplyr::mutate(color_bin = as.character(cut(color_raw, nBins_real, labels = colors_categories.l[["GENE"]], ordered_result = TRUE)))  # Transform the colors for the vertices
3588
+                
3589
+            } else {
3590
+                vertices_genes = dplyr::mutate(vertices_genes, color_raw = NA, color_bin = colors_categories.l[["GENE"]])
3591
+            } 
3592
+            
3593
+            
3594
+            vertices = tibble::add_row(vertices, 
3595
+                                       id = vertices_genes$gene.ENSEMBL, 
3596
+                                       type = "GENE", 
3597
+                                       label = vertices_genes$label, 
3598
+                                       color_raw = vertices_genes$color_raw,
3599
+                                       color_bin = vertices_genes$color_bin) 
3600
+            
3601
+        }
3602
+        
3603
+        
3604
+        
3605
+        vertices = vertices %>%
3606
+            dplyr::mutate(size = dplyr::case_when(type == "TF" ~ 6,
3607
+                                                  type == "PEAK" ~ 3,
3608
+                                                  TRUE ~ 4),
3609
+                          size_transformed = NA) 
3610
+        
3611
+        
3612
+        vertices_colorRanges = vertices %>% dplyr::group_by(.data$type) %>% dplyr::summarize(min = min(color_raw, na.rm = TRUE), max = max(color_raw, na.rm = TRUE))
3613
+        
3614
+        if (nrow(dplyr::filter(vertices_colorRanges, .data$type == "GENE")) == 0) {
3615
+            vertices_colorRanges = tibble::add_row(vertices_colorRanges, type = "GENE", min = NA, max = NA)
3616
+        }
3617
+        
3618
+        if(graph == "TF-peak-gene"){
3619
+            text_categories.l = list(
3620
+                "TF"   = "TF",
3621
+                "PEAK" = "PEAK",
3622
+                "GENE" = "GENE"
3623
+            )
3624
+        }else{
3625
+            text_categories.l = list(
3626
+                "TF"   = "TF",
3627
+                "GENE" = "GENE"
3628
+            )
3629
+        }
3630
+        
3631
+        
3632
+        if (!is.null(vertice_color_TFs)) {
3633
+            subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "TF") 
3634
+            text_categories.l[["TF"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3635
+                                          paste0("TF expression (", vertice_color_TFs[[3]], ")"),
3636
+                                          signif(dplyr::pull(subsetCur, max),2)
3637
+            )
3638
+        }
3639
+        
3640
+        if( graph  == "TF-peak-gene"){
3641
+            if (!is.null(vertice_color_peaks)) {
3642
+                subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "PEAK") 
3643
+                text_categories.l[["PEAK"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3644
+                                                paste0("Peak accessibility (", vertice_color_peaks[[3]], ")"),
3645
+                                                signif(dplyr::pull(subsetCur, max),2)
3646
+                )
3647
+            }
3648
+        }
3649
+        
3650
+        if (!is.null(vertice_color_genes)) {
3651
+            subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "GENE") 
3652
+            text_categories.l[["GENE"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3653
+                                            paste0("Gene expression (", vertice_color_genes[[3]], ")"),
3654
+                                            signif(dplyr::pull(subsetCur, max),2)
3655
+            )
3656
+        }
3657
+        
3658
+        
3659
+        net <- igraph::graph_from_data_frame(d=edges_final, vertices = vertices, directed = FALSE) 
3660
+        
3661
+        
3662
+        # TODO: Integrate network stats: https://kateto.net/networks-r-igraph
3663
+        # Make a separate df_to_igraph function for the entwork stats
3664
+        
3665
+        
3666
+        ########### Color and Shape parameters 
3667
+        
3668
+        # TODO: https://stackoverflow.com/questions/48490378/order-vertices-within-layers-on-tripartite-igraph
3669
+        # note: the layout_with_sugiyama which can convert the layout to tri/bipartite creates an order that minimizes edge overlap/crossover, makes it cleaner to visualize. do we want to enforce a custom order?
3670
+        
3671
+        net <- igraph::simplify(net, remove.multiple = FALSE, remove.loops = TRUE)
3672
+        deg <- igraph::degree(net, mode="all", normalized = TRUE) # added normalized = T in case later used to determine node size. for now not rly needed
3673
+        #V(net)$size <- deg*2
3674
+        #igraph::V(net)$vertex_degree <-  deg*4 # the vertex_degree attribute doesn't need to be changed 
3675
+        igraph::V(net)$label = vertices$label
3676
+        
3677
+        
3678
+        
3679
+        #assign colors to the 5 largest communities, rest is grey
3680
+        if (colorby == "type"){
3681
+            igraph::V(net)$vertex.color = vertices$color_bin
3682
+        }else{
3683
+            
3684
+            if (is.null(GRN@graph$TF_gene$clusterGraph)){
3685
+                GRN = calculateCommunitiesStats(GRN)
3686
+            }
3687
+            
3688
+            ncommunities = length(unique(GRN@graph$TF_gene$clusterGraph$membership))
3689
+            
3690
+            if (ncommunities >=8){
3691
+                community_colors = data.frame(community = names(sort(table(GRN@graph$TF_gene$clusterGraph$membership), decreasing = TRUE)[1:nCommunitiesMax]),
3692
+                                              color = rainbow(7))
3693
+                fillercolors = data.frame(community = nCommunitiesMax:ncommunities, color = "847E89") # only color the x largest communities
3694
+                community_colors = rbind(community_colors, fillercolors)
3695
+                
3696
+            }else{
3697
+                community_colors = data.frame(community = names(sort(table(GRN@graph$TF_gene$clusterGraph$membership), decreasing = TRUE)[1:ncommunities]),
3698
+                                              color = rainbow(ncommunities))
3699
+            }
3700
+            
3701
+            TF_ensembl = GRN@graph$TF_gene$table$V1[match(vertices$id, GRN@graph$TF_gene$table$V1_name)] %>% stats::na.omit() %>% as.vector()
3702
+            gene_ensembl = GRN@graph$TF_gene$table$V2[match(vertices$id, GRN@graph$TF_gene$table$V2)] %>% stats::na.omit() %>% as.vector()
3703
+            if(graph == "TF-peak-gene"){
3704
+                network_ensembl = c(TF_ensembl, rep(NA, length(unique(vertices_peaks$peak))), gene_ensembl) 
3705
+            }else{
3706
+                network_ensembl = c(TF_ensembl, gene_ensembl) 
3707
+            }
3708
+            
3709
+            
3710
+            communities = GRN@graph$TF_gene$clusterGraph$membership[match(network_ensembl, GRN@graph$TF_gene$clusterGraph$names)]
3711
+            igraph::V(net)$vertex.color = community_colors$color[match(communities, community_colors$community)]
3712
+            
3713
+        }
3714
+        
3715
+        igraph::V(net)$vertex.size = vertices$size
3716
+        # https://rstudio-pubs-static.s3.amazonaws.com/337696_c6b008e0766e46bebf1401bea67f7b10.html
3717
+        # TODO: E(net)$weight <- edges_final$weight_transformed
3718
+        igraph::E(net)$color = edges_final$color
3719
+        
3720
+        #change arrow size and edge color:
3721
+        #igraph::E(net)$arrow.size <- .1
3722
+        igraph::E(net)$edge.color <- edges_final$color
3723
+        # TODO: E(net)$lty = edges_final$linetype
3724
+        # TODO: E(net)$width <- 1+E(net)$weight/12
3725
+        #igraph::E(net)$width <- 1+igraph::E(net)$weight/12
3726
+        igraph::E(net)$width <- igraph::E(net)$weight
3727
+        #igraph::E(net)$weight <- edges_final$weight_transformed # too block-y for large networks. stick to givren weight.
3728
+        
3729
+        
3730
+        if (layout == "sugiyama"){
3731
+            l <- igraph::layout_with_sugiyama(net, layers = as.numeric(as.factor(igraph::V(net)$type)), hgap = 1)$layout
3732
+            l <- cbind(l[,2], l[,1])
3733
+        }
3734
+        if (layout == "fr"){
3735
+            l <- igraph::layout_with_fr(net)
3736
+        }
3737
+        if(layout == "star"){
3738
+            l <- igraph::layout_as_star(net)
3739
+        }
3740
+        if(layout == "kk"){
3741
+            l <- igraph::layout_with_kk(net)
3742
+        }
3743
+        if(layout == "lgl"){
3744
+            l <- igraph::layout_with_lgl(net)
3745
+        }
3746
+        if(layout == "graphopt"){
3747
+            l <- igraph::layout_with_graphopt(net)
3748
+        }
3749
+        if (layout == "mds"){
3750
+            l <- igraph::layout_with_mds(net)
3751
+        } 
3752
+        if (layout == "sphere"){
3753
+            l <- igraph::layout_on_sphere(net)
3754
+        }
3755
+        
3756
+        
3757
+        
3758
+        # MyLO = matrix(0, nrow=vcount(net), ncol=2)
3759
+        # 
3760
+        # ## Horizontal position is determined by layer
3761
+        # layer <- rep(NA, length(V(net)$name))
3762
+        # layer[vertices$type == "TF"]   = 1
3763
+        # layer[vertices$type == "PEAK"] = 2
3764
+        # layer[vertices$type == "GENE"] = 3
3765
+        # MyLO[,1] = layer
3766
+        # 
3767
+        # ## Vertical position is determined by sum of sorted vertex_degree
3768
+        # for(i in 1:3) {
3769
+        #     L  = which(layer ==i)
3770
+        #     OL = order(V(net)$vertex_degree[L], decreasing=TRUE)
3771
+        #     MyLO[L[OL],2] = cumsum(V(net)$vertex_degree[L][OL])
3772
+        # }
3773
+        # 
3774
+        # layout = layout_with_sugiyama(net, layers=layer)
3775
+        # plot(net,
3776
+        #      layout=cbind(layer,layout$layout[,1]),edge.curved=0,
3777
+        #      vertex.shape=c("square","circle","square")[layer],
3778
+        #      vertex.frame.color = c("darkolivegreen","darkgoldenrod","orange3")[layer],
3779
+        #      vertex.color=c("olivedrab","goldenrod1","orange1")[layer],
3780
+        #      vertex.label.color="white",
3781
+        #      vertex.label.font=1,
3782
+        #      vertex.size=V(net)$vertex_degree,
3783
+        #      vertex.label.dist=c(0,0,0)[layer],
3784
+        #      vertex.label.degree=0)
3785
+        
3786
+        # 
3787
+        # vertex.color	 Node color
3788
+        # vertex.frame.color	 Node border color
3789
+        # vertex.shape	 One of “none”, “circle”, “square”, “csquare”, “rectangle” “crectangle”, “vrectangle”, “pie”, “raster”, or “sphere”
3790
+        # vertex.size	 Size of the node (default is 15)
3791
+        # vertex.size2	 The second size of the node (e.g. for a rectangle)
3792
+        # vertex.label	 Character vector used to label the nodes
3793
+        # vertex.label.family	 Font family of the label (e.g.“Times”, “Helvetica”)
3794
+        # vertex.label.font	 Font: 1 plain, 2 bold, 3, italic, 4 bold italic, 5 symbol
3795
+        # vertex.label.cex	 Font size (multiplication factor, device-dependent)
3796
+        # vertex.label.dist	 Distance between the label and the vertex
3797
+        # vertex.label.degree	 The position of the label in relation to the vertex, where 0 right, “pi” is left, “pi/2” is below, and “-pi/2” is above
3798
+        # EDGES	 
3799
+        # edge.color	 Edge color
3800
+        # edge.width	 Edge width, defaults to 1
3801
+        # edge.arrow.size	 Arrow size, defaults to 1
3802
+        # edge.arrow.width	 Arrow width, defaults to 1
3803
+        # edge.lty	 Line type, could be 0 or “blank”, 1 or “solid”, 2 or “dashed”, 3 or “dotted”, 4 or “dotdash”, 5 or “longdash”, 6 or “twodash”
3804
+        # edge.label	 Character vector used to label edges
3805
+        # edge.label.family	 Font family of the label (e.g.“Times”, “Helvetica”)
3806
+        # edge.label.font	 Font: 1 plain, 2 bold, 3, italic, 4 bold italic, 5 symbol
3807
+        # edge.label.cex	 Font size for edge labels
3808
+        # edge.curved	 Edge curvature, range 0-1 (FALSE sets it to 0, TRUE to 0.5)
3809
+        # arrow.mode	 Vector specifying whether edges should have arrows,
3810
+        # possible values: 0 no arrow, 1 back, 2 forward, 3 both
3811
+        
3812
+        #par(mar=c(5, 4, 4, 2) + 0.1)
3813
+        
3814
+        
3815
+        # Calling plot.new() might be necessary here
3816
+        # if(!plotAsPDF){
3817
+        #     #plot.new()
3818
+        # }
3819
+        par(mar=c(7,0,0,0) + 0.2)
3820
+        
3821
+        plot(
3822
+            net, layout=l,
3823
+            #edge.arrow.size= 0.4, 
3824
+            # TODO: edge.arrow.width= E(net)$weight, 
3825
+            edge.font= 2,
3826
+            # TODO: edge.lty = E(net)$lty,
3827
+            vertex.size= igraph::V(net)$vertex.size,
3828
+            vertex.color=igraph::V(net)$vertex.color,
3829
+            edge.color = igraph::E(net)$color,
3830
+            edge.width = igraph::E(net)$weight,
3831
+            vertex.label=igraph::V(net)$label,
3832
+            vertex.label.font=1, 
3833
+            vertex.label.cex = vertexLabel_cex, 
3834
+            vertex.label.family="Helvetica", 
3835
+            vertex.label.color = "black",
3836
+            vertex.label.degree= -pi/2,
3837
+            vertex.label=igraph::V(net)$label,
3838
+            vertex.label.dist= vertexLabel_dist,
3839
+            vertex.shape = shape_vertex[igraph::V(net)$type],
3840
+            main = title
3646 3841
         )
3647
-      }
3648
-    }
3649
-    
3650
-    if (!is.null(vertice_color_genes)) {
3651
-      subsetCur = dplyr::filter(vertices_colorRanges, .data$type == "GENE") 
3652
-      text_categories.l[["GENE"]] = c(signif(dplyr::pull(subsetCur, min),2), 
3653
-                                      paste0("Gene expression (", vertice_color_genes[[3]], ")"),
3654
-                                      signif(dplyr::pull(subsetCur, max),2)
3655
-      )
3656
-    }
3657
-    
3658
-    
3659
-    net <- igraph::graph_from_data_frame(d=edges_final, vertices = vertices, directed = FALSE) 
3660
-    
3661
-    
3662
-    # TODO: Integrate network stats: https://kateto.net/networks-r-igraph
3663
-    # Make a separate df_to_igraph function for the entwork stats
3664
-    
3665
-    
3666
-    ########### Color and Shape parameters 
3667
-    
3668
-    # TODO: https://stackoverflow.com/questions/48490378/order-vertices-within-layers-on-tripartite-igraph
3669
-    # note: the layout_with_sugiyama which can convert the layout to tri/bipartite creates an order that minimizes edge overlap/crossover, makes it cleaner to visualize. do we want to enforce a custom order?
3670
-    
3671
-    net <- igraph::simplify(net, remove.multiple = FALSE, remove.loops = TRUE)
3672
-    deg <- igraph::degree(net, mode="all", normalized = TRUE) # added normalized = T in case later used to determine node size. for now not rly needed
3673
-    #V(net)$size <- deg*2
3674
-    #igraph::V(net)$vertex_degree <-  deg*4 # the vertex_degree attribute doesn't need to be changed 
3675
-    igraph::V(net)$label = vertices$label
3676
-    
3677
-    
3678
-    
3679
-    #assign colors to the 5 largest communities, rest is grey
3680
-    if (colorby == "type"){
3681
-      igraph::V(net)$vertex.color = vertices$color_bin
3682
-    }else{
3683
-      
3684
-      if (is.null(GRN@graph$TF_gene$clusterGraph)){
3685
-        GRN = calculateCommunitiesStats(GRN)
3686
-      }
3687
-      
3688
-      ncommunities = length(unique(GRN@graph$TF_gene$clusterGraph$membership))
3689
-      
3690
-      if (ncommunities >=8){
3691
-        community_colors = data.frame(community = names(sort(table(GRN@graph$TF_gene$clusterGraph$membership), decreasing = TRUE)[1:nCommunitiesMax]),
3692
-                                      color = rainbow(7))
3693
-        fillercolors = data.frame(community = nCommunitiesMax:ncommunities, color = "847E89") # only color the x largest communities
3694
-        community_colors = rbind(community_colors, fillercolors)
3695 3842
         
3696
-      }else{
3697
-        community_colors = data.frame(community = names(sort(table(GRN@graph$TF_gene$clusterGraph$membership), decreasing = TRUE)[1:ncommunities]),
3698
-                                      color = rainbow(ncommunities))
3699
-      }
3700
-      
3701
-      TF_ensembl = GRN@graph$TF_gene$table$V1[match(vertices$id, GRN@graph$TF_gene$table$V1_name)] %>% stats::na.omit() %>% as.vector()
3702
-      gene_ensembl = GRN@graph$TF_gene$table$V2[match(vertices$id, GRN@graph$TF_gene$table$V2)] %>% stats::na.omit() %>% as.vector()
3703
-      if(graph == "TF-peak-gene"){
3704
-        network_ensembl = c(TF_ensembl, rep(NA, length(unique(vertices_peaks$peak))), gene_ensembl) 
3705
-      }else{
3706
-        network_ensembl = c(TF_ensembl, gene_ensembl) 
3707
-      }
3708
-      
3709
-      
3710
-      communities = GRN@graph$TF_gene$clusterGraph$membership[match(network_ensembl, GRN@graph$TF_gene$clusterGraph$names)]
3711
-      igraph::V(net)$vertex.color = community_colors$color[match(communities, community_colors$community)]
3712
-      
3713
-    }
3714
-    
3715
-    igraph::V(net)$vertex.size = vertices$size
3716
-    # https://rstudio-pubs-static.s3.amazonaws.com/337696_c6b008e0766e46bebf1401bea67f7b10.html
3717
-    # TODO: E(net)$weight <- edges_final$weight_transformed
3718
-    igraph::E(net)$color = edges_final$color
3719
-    
3720
-    #change arrow size and edge color:
3721
-    #igraph::E(net)$arrow.size <- .1
3722
-    igraph::E(net)$edge.color <- edges_final$color
3723
-    # TODO: E(net)$lty = edges_final$linetype
3724
-    # TODO: E(net)$width <- 1+E(net)$weight/12
3725
-    #igraph::E(net)$width <- 1+igraph::E(net)$weight/12
3726
-    igraph::E(net)$width <- igraph::E(net)$weight
3727
-    #igraph::E(net)$weight <- edges_final$weight_transformed # too block-y for large networks. stick to givren weight.
3728
-    
3729
-    if (layered){
3730
-      l <- igraph::layout_with_sugiyama(net, layers = as.numeric(as.factor(igraph::V(net)$type)), hgap = 1)$layout
3731
-      l <- cbind(l[,2], l[,1])
3732
-    }else{
3733
-      l <- igraph::layout_with_fr(net)
3843
+        
3844
+        if (colorby == "type"){
3845
+            
3846
+            text_final    = c(c(paste0(sapply(text_categories.l, '[[', 1), " (sel. min.)"), "negative (fixed color)"),   
3847
+                              c(sapply(text_categories.l, '[[', 2), "Correlation between vertices"),    
3848
+                              c(paste0(sapply(text_categories.l, '[[', 3), " (sel. max.)"), "positive (fixed color)")#, 
3849
+                              #c("Negative correlation", "Positive correlation", "bla")
3850
+            )
3851
+            symbols_final = c(c(sapply(symbols_categories.l, '[[', 1), 20),
3852
+                              c(sapply(symbols_categories.l, '[[', 2), NA), 
3853
+                              c(sapply(symbols_categories.l, '[[', 3), 20)#,
3854
+                              #c(20,20,20)
3855
+            )
3856
+            if (graph == "TF-peak-gene"){
3857
+                colors_final  = c(c(sapply(colors_categories.l , '[[', 1), "blue"), 
3858
+                                  c(rep(NA,3), NA), 
3859
+                                  c(sapply(colors_categories.l , '[[', nBins_real), "grey")#,
3860
+                                  #c("red","blue","green")
3861
+                )
3862
+            }else{
3863
+                colors_final  = c(c(sapply(colors_categories.l , '[[', 1), "blue"), 
3864
+                                  c(rep(NA,2), NA), 
3865
+                                  c(sapply(colors_categories.l , '[[', nBins_real), "grey")#,
3866
+                                  #c("red","blue","green")
3867
+                )
3868
+            }
3869
+            
3870
+            legend(x= "bottom", text_final, 
3871
+                   pch=symbols_final,
3872
+                   col=colors_final, 
3873
+                   pt.bg=colors_final, 
3874
+                   pt.cex=1, cex=.8, bty="n", xpd = TRUE, ncol=3, xjust = 0.5, yjust = 0.5, 
3875
+                   inset=c(0,-0.1)
3876
+            )  
3877
+            
3878
+        }else{
3879
+            
3880
+            text_final = community_colors$community
3881
+            symbols_final = rep (21, length(text_final))
3882
+            colors_final = community_colors$color
3883
+            
3884
+            legend(x = "bottom", title = "community",
3885
+                   legend = text_final,
3886
+                   pch = symbols_final,
3887
+                   #fill = colors_final,
3888
+                   #col = colors_final,
3889
+                   pt.bg=colors_final,
3890
+                   pt.cex=1, cex=.8, bty="n", xpd = TRUE,
3891
+                   ncol= length(text_final), inset=c(0,-0.1)) #divide by something?
3892
+            legend(x = "bottomright", title = "Node Type",
3893
+                   legend = c("TF", ifelse(graph =="TF-gene",  "gene", "peak/gene")),
3894
+                   pch = c(22,21),
3895
+                   pt.cex=1, cex=.8, bty="n",  xpd = TRUE,
3896
+                   ncol = 1, inset=c(0,-0.1))
3897
+            
3898
+        }
3899
+        
3900
+        # https://stackoverflow.com/questions/24933703/adjusting-base-graphics-legend-label-width
3901
+        #labels = c("6.4", "blaaaaaaaaaaaaaaaaaaaaaaaa", "6.4")
3902
+        
3903
+        #par(mar=c(5, 2, 2, 2) + 0.1)
3904
+        #bottom, left, top, and right.
3905
+        
3734 3906
     }
3735 3907
     
3736
-    #test.layout <- layout_(net,with_dh(weight.edge.lengths = edge_density(net)/1000))
3737
-    
3738
-    # MyLO = matrix(0, nrow=vcount(net), ncol=2)
3739
-    # 
3740
-    # ## Horizontal position is determined by layer
3741
-    # layer <- rep(NA, length(V(net)$name))
3742
-    # layer[vertices$type == "TF"]   = 1
3743
-    # layer[vertices$type == "PEAK"] = 2
3744
-    # layer[vertices$type == "GENE"] = 3
3745
-    # MyLO[,1] = layer
3746
-    # 
3747
-    # ## Vertical position is determined by sum of sorted vertex_degree
3748
-    # for(i in 1:3) {
3749
-    #     L  = which(layer ==i)
3750
-    #     OL = order(V(net)$vertex_degree[L], decreasing=TRUE)
3751
-    #     MyLO[L[OL],2] = cumsum(V(net)$vertex_degree[L][OL])
3752
-    # }
3753
-    # 
3754
-    # layout = layout_with_sugiyama(net, layers=layer)
3755
-    # plot(net,
3756
-    #      layout=cbind(layer,layout$layout[,1]),edge.curved=0,
3757
-    #      vertex.shape=c("square","circle","square")[layer],
3758
-    #      vertex.frame.color = c("darkolivegreen","darkgoldenrod","orange3")[layer],
3759
-    #      vertex.color=c("olivedrab","goldenrod1","orange1")[layer],
3760
-    #      vertex.label.color="white",
3761
-    #      vertex.label.font=1,
3762
-    #      vertex.size=V(net)$vertex_degree,
3763
-    #      vertex.label.dist=c(0,0,0)[layer],
3764
-    #      vertex.label.degree=0)
3765
-    
3766
-    # 
3767
-    # vertex.color	 Node color
3768
-    # vertex.frame.color	 Node border color
3769
-    # vertex.shape	 One of “none”, “circle”, “square”, “csquare”, “rectangle” “crectangle”, “vrectangle”, “pie”, “raster”, or “sphere”
3770
-    # vertex.size	 Size of the node (default is 15)
3771
-    # vertex.size2	 The second size of the node (e.g. for a rectangle)
3772
-    # vertex.label	 Character vector used to label the nodes
3773
-    # vertex.label.family	 Font family of the label (e.g.“Times”, “Helvetica”)
3774
-    # vertex.label.font	 Font: 1 plain, 2 bold, 3, italic, 4 bold italic, 5 symbol
3775
-    # vertex.label.cex	 Font size (multiplication factor, device-dependent)
3776
-    # vertex.label.dist	 Distance between the label and the vertex
3777
-    # vertex.label.degree	 The position of the label in relation to the vertex, where 0 right, “pi” is left, “pi/2” is below, and “-pi/2” is above
3778
-    # EDGES	 
3779
-    # edge.color	 Edge color
3780
-    # edge.width	 Edge width, defaults to 1
3781
-    # edge.arrow.size	 Arrow size, defaults to 1
3782
-    # edge.arrow.width	 Arrow width, defaults to 1
3783
-    # edge.lty	 Line type, could be 0 or “blank”, 1 or “solid”, 2 or “dashed”, 3 or “dotted”, 4 or “dotdash”, 5 or “longdash”, 6 or “twodash”
3784
-    # edge.label	 Character vector used to label edges
3785
-    # edge.label.family	 Font family of the label (e.g.“Times”, “Helvetica”)
3786
-    # edge.label.font	 Font: 1 plain, 2 bold, 3, italic, 4 bold italic, 5 symbol
3787
-    # edge.label.cex	 Font size for edge labels
3788
-    # edge.curved	 Edge curvature, range 0-1 (FALSE sets it to 0, TRUE to 0.5)
3789
-    # arrow.mode	 Vector specifying whether edges should have arrows,
3790
-    # possible values: 0 no arrow, 1 back, 2 forward, 3 both
3791
-    
3792
-    #par(mar=c(5, 4, 4, 2) + 0.1)
3793
-    
3794
-    
3795
-    # Calling plot.new() might be necessary here
3796
-    # if(!plotAsPDF){
3797
-    #     #plot.new()
3798
-    # }
3799
-    par(mar=c(7,0,0,0) + 0.2)
3800
-    
3801
-    plot(
3802
-      net, layout=l,
3803
-      #edge.arrow.size= 0.4, 
3804
-      # TODO: edge.arrow.width= E(net)$weight, 
3805
-      edge.font= 2,
3806
-      # TODO: edge.lty = E(net)$lty,
3807
-      vertex.size= igraph::V(net)$vertex.size,
3808
-      vertex.color=igraph::V(net)$vertex.color,
3809
-      edge.color = igraph::E(net)$color,
3810
-      edge.width = igraph::E(net)$weight,
3811
-      vertex.label=igraph::V(net)$label,
3812
-      vertex.label.font=1, 
3813
-      vertex.label.cex = vertexLabel_cex, 
3814
-      vertex.label.family="Helvetica", 
3815
-      vertex.label.color = "black",
3816
-      vertex.label.degree= -pi/2,
3817
-      vertex.label=igraph::V(net)$label,
3818
-      vertex.label.dist= vertexLabel_dist,
3819
-      vertex.shape = shape_vertex[igraph::V(net)$type],
3820
-      main = title
3821
-    )
3822
-    
3823
-    
3824
-    if (colorby == "type"){
3825
-      
3826
-      text_final    = c(c(paste0(sapply(text_categories.l, '[[', 1), " (sel. min.)"), "negative (fixed color)"),   
3827
-                        c(sapply(text_categories.l, '[[', 2), "Correlation between vertices"),    
3828
-                        c(paste0(sapply(text_categories.l, '[[', 3), " (sel. max.)"), "positive (fixed color)")#, 
3829
-                        #c("Negative correlation", "Positive correlation", "bla")
3830
-      )
3831
-      symbols_final = c(c(sapply(symbols_categories.l, '[[', 1), 20),
3832
-                        c(sapply(symbols_categories.l, '[[', 2), NA), 
3833
-                        c(sapply(symbols_categories.l, '[[', 3), 20)#,
3834
-                        #c(20,20,20)
3835
-      )
3836
-      if (graph == "TF-peak-gene"){
3837
-        colors_final  = c(c(sapply(colors_categories.l , '[[', 1), "blue"), 
3838
-                          c(rep(NA,3), NA), 
3839
-                          c(sapply(colors_categories.l , '[[', nBins_real), "grey")#,
3840
-                          #c("red","blue","green")
3841
-        )
3842
-      }else{
3843
-        colors_final  = c(c(sapply(colors_categories.l , '[[', 1), "blue"), 
3844
-                          c(rep(NA,2), NA), 
3845
-                          c(sapply(colors_categories.l , '[[', nBins_real), "grey")#,
3846
-                          #c("red","blue","green")
3847
-        )
3848
-      }
3849
-      
3850
-      legend(x= "bottom", text_final, 
3851
-             pch=symbols_final,
3852
-             col=colors_final, 
3853
-             pt.bg=colors_final, 
3854
-             pt.cex=1, cex=.8, bty="n", xpd = TRUE, ncol=3, xjust = 0.5, yjust = 0.5, 
3855
-             inset=c(0,-0.1)
3856
-      )  
3857
-      
3858
-    }else{
3859
-      
3860
-      text_final = community_colors$community
3861
-      symbols_final = rep (21, length(text_final))
3862
-      colors_final = community_colors$color
3863
-      
3864
-      legend(x = "bottom", title = "community",
3865
-             legend = text_final,
3866
-             pch = symbols_final,
3867
-             #fill = colors_final,
3868
-             #col = colors_final,
3869
-             pt.bg=colors_final,
3870
-             pt.cex=1, cex=.8, bty="n", xpd = TRUE,
3871
-             ncol= length(text_final), inset=c(0,-0.1)) #divide by something?
3872
-      legend(x = "bottomright", title = "Node Type",
3873
-             legend = c("TF", ifelse(graph =="TF-gene",  "gene", "peak/gene")),
3874
-             pch = c(22,21),
3875
-             pt.cex=1, cex=.8, bty="n",  xpd = TRUE,
3876
-             ncol = 1, inset=c(0,-0.1))
3877
-      
3908
+    if (plotAsPDF) {
3909
+        grDevices::dev.off()
3878 3910
     }
3879 3911
     
3880
-    # https://stackoverflow.com/questions/24933703/adjusting-base-graphics-legend-label-width
3881
-    #labels = c("6.4", "blaaaaaaaaaaaaaaaaaaaaaaaa", "6.4")
3882
-    
3883
-    #par(mar=c(5, 2, 2, 2) + 0.1)
3884
-    #bottom, left, top, and right.
3912
+    .printExecutionTime(start)
3885 3913
     
3886
-  }
3887
-  
3888
-  if (plotAsPDF) {
3889
-    grDevices::dev.off()
3890
-  }
3891
-  
3892
-  .printExecutionTime(start)
3893
-  
3894
-  GRN
3914
+    GRN
3895 3915
 }
3896 3916
 
3897 3917
 
... ...
@@ -15,6 +15,7 @@ performAllNetworkAnalyses(
15 15
   display = "byRank",
16 16
   topnGenes = 20,
17 17
   topnTFs = 20,
18
+  maxWidth_nchar_plot = 50,
18 19
   display_pAdj = FALSE,
19 20
   outputFolder = NULL,
20 21
   forceRerun = FALSE
... ...
@@ -41,6 +42,8 @@ performAllNetworkAnalyses(
41 42
 
42 43
 \item{topnTFs}{Integer. Default 20. Number of TFs to plot, sorted by their rank or label.}
43 44
 
45
+\item{maxWidth_nchar_plot}{Integer (>=10). Default 50. Maximum number of characters for a term before it is truncated.}
46
+
44 47
 \item{display_pAdj}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Is the p-value being displayed in the plots the adjusted p-value? This parameter is relevant for KEGG, Disease Ontology, and Reactome enrichments, and does not affect GO enrichments.}
45 48
 
46 49
 \item{outputFolder}{Character or \code{NULL}. Default \code{NULL}. If set to \code{NULL}, the default output folder as specified when initiating the object in \code{link{initializeGRN}} will be used. Otherwise, all output from this function will be put into the specified folder. We recommend specifying an absolute path.}
... ...
@@ -1,28 +1,9 @@
1 1
 % Generated by roxygen2: do not edit by hand
2
-% Please edit documentation in R/plot.R, R/plot.new.R
2
+% Please edit documentation in R/plot.R
3 3
 \name{plotCommunitiesEnrichment}
4 4
 \alias{plotCommunitiesEnrichment}
5 5
 \title{Plot community-based enrichment results}
6 6
 \usage{
7
-plotCommunitiesEnrichment(
8
-  GRN,
9
-  outputFolder = NULL,
10
-  basenameOutput = NULL,
11
-  display = "byRank",
12
-  communities = NULL,
13
-  topn_pvalue = 30,
14
-  p = 0.05,
15
-  nSignificant = 2,
16
-  nID = 10,
17
-  maxWidth_nchar_plot = 50,
18
-  display_pAdj = FALSE,
19
-  plotAsPDF = TRUE,
20
-  pdf_width = 12,
21
-  pdf_height = 12,
22
-  pages = NULL,
23
-  forceRerun = FALSE
24
-)
25
-
26 7
 plotCommunitiesEnrichment(
27 8
   GRN,
28 9
   outputFolder = NULL,
... ...
@@ -76,20 +57,13 @@ plotCommunitiesEnrichment(
76 57
 \item{forceRerun}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Force execution, even if the GRN object already contains the result. Overwrites the old results.}
77 58
 }
78 59
 \value{
79
-The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results.
80
-
81 60
 The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results.
82 61
 }
83 62
 \description{
84
-Similarly to \code{\link{plotGeneralEnrichment}}, the results of the community-based enrichment analysis are plotted.. By default, the results for the 10 largest communities are displayed. Additionally, if a general enrichment analysis was previously generated, this function plots an additional heatmap to compare the general enrichment with the community based enrichment. A reduced version of this heatmap is also produced where terms are filtered out to improve visibility and display and highlight the most significant terms.
85
-
86 63
 Similarly to \code{\link{plotGeneralEnrichment}}, the results of the community-based enrichment analysis are plotted.. By default, the results for the 10 largest communities are displayed. Additionally, if a general enrichment analysis was previously generated, this function plots an additional heatmap to compare the general enrichment with the community based enrichment. A reduced version of this heatmap is also produced where terms are filtered out to improve visibility and display and highlight the most significant terms.
87 64
 }
88 65
 \examples{
89 66
 # See the Workflow vignette on the GRaNIE website for examples
90 67
 GRN = loadExampleObject()
91 68
 GRN = plotCommunitiesEnrichment(GRN, plotAsPDF = FALSE)
92
-# See the Workflow vignette on the GRaNIE website for examples
93
-GRN = loadExampleObject()
94
-GRN = plotCommunitiesEnrichment(GRN, plotAsPDF = FALSE)
95 69
 }
... ...
@@ -1,24 +1,9 @@
1 1
 % Generated by roxygen2: do not edit by hand
2
-% Please edit documentation in R/plot.R, R/plot.new.R
2
+% Please edit documentation in R/plot.R
3 3
 \name{plotCommunitiesStats}
4 4
 \alias{plotCommunitiesStats}
5 5
 \title{Plot general structure & connectivity statistics for each community in a filtered \code{\linkS4class{GRN}}}
6 6
 \usage{
7
-plotCommunitiesStats(
8
-  GRN,
9
-  outputFolder = NULL,
10
-  basenameOutput = NULL,
11
-  display = "byRank",
12
-  communities = seq_len(10),
13
-  topnGenes = 20,
14
-  topnTFs = 20,
15
-  plotAsPDF = TRUE,
16
-  pdf_width = 12,
17
-  pdf_height = 12,
18
-  pages = NULL,
19