Browse code

Advance GraphPlot family

Giulio Benedetti authored on 10/03/2025 08:48:13
Showing 13 changed files

... ...
@@ -37,6 +37,7 @@ Imports:
37 37
     shinyWidgets,
38 38
     SingleCellExperiment,
39 39
     SummarizedExperiment,
40
+    tidygraph,
40 41
     TreeSummarizedExperiment,
41 42
     utils
42 43
 Suggests:
... ...
@@ -62,4 +62,5 @@ importFrom(purrr,reduce)
62 62
 importFrom(shiny,plotOutput)
63 63
 importFrom(shiny,renderPlot)
64 64
 importFrom(shinyWidgets,addSpinner)
65
+importFrom(tidygraph,activate)
65 66
 importFrom(utils,stack)
... ...
@@ -17,3 +17,4 @@ Changes in version 1.1.X
17 17
 Changes in version 1.2.X
18 18
 * Created TreePlot family
19 19
 * Added typical tree operations
20
+* Created GraphPlot family
... ...
@@ -23,7 +23,9 @@ graph_slots <- c(name="character", assay.type="character", layout="character",
23 23
     edge.type="character", show.label="logical", add.legend="logical",
24 24
     edge.colour.by="character", edge.size.by="character",
25 25
     node.colour.by="character", node.shape.by="character",
26
-    node.size.by="character")
26
+    node.size.by="character", visual_parameters="character",
27
+    size_parameters="character", shape_parameters="character",
28
+    colour_parameters="character")
27 29
 
28 30
 #' @rdname GraphPlot
29 31
 #' @export
... ...
@@ -1,10 +1,10 @@
1 1
 #' Column graph plot
2 2
 #'
3
-#' Hierarchical tree for the rows of a
4
-#' \code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
5
-#' object. The tree can be produced with \code{\link[mia:taxonomy-methods]{addTaxonomyTree}}
6
-#' and gets stored in the \code{\link[TreeSummarizedExperiment:rowLinks]{rowTree}}
7
-#' slot of the experiment object. The panel implements \code{\link[miaViz:plotTree]{plotRowTree}}
3
+#' Network organisation for the samples of a
4
+#' \code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
5
+#' object. The igraph should be stored in the \code{metadata} slot by a name
6
+#' containing \code{"graph"}. This panel uses
7
+#' \code{\link[miaViz:plotColGraph]{plotColGraph}}
8 8
 #' to generate the plot.
9 9
 #'
10 10
 #' @section Slot overview:
... ...
@@ -17,10 +17,17 @@
17 17
 #' \code{...} as a named argument.
18 18
 #'
19 19
 #' @examples
20
-#' # Import TreeSE
21 20
 #' library(mia)
22
-#' data("Tengeler2020", package = "mia")
23
-#' tse <- Tengeler2020
21
+#' library(miaViz)
22
+#' data("GlobalPatterns", library = "mia")
23
+#' data("col_graph", library = "miaViz")
24
+#' 
25
+#' tse <- GlobalPatterns
26
+#' tse <- agglomerateByRank(tse,
27
+#'                          rank = "Genus",
28
+#'                          na.rm = TRUE)
29
+#'                          
30
+#' metadata(tse)$graph <- col_graph
24 31
 #' 
25 32
 #' # Store panel into object
26 33
 #' panel <- ColumnGraphPlot()
... ...
@@ -32,6 +39,10 @@
32 39
 #'   iSEE(tse, initial = c(panel))
33 40
 #' }
34 41
 #' 
42
+#' @seealso
43
+#' \linkS4class{GraphPlot}
44
+#' \linkS4class{RowGraphPlot}
45
+#' 
35 46
 #' @author Giulio Benedetti
36 47
 #' 
37 48
 #' @docType methods
... ...
@@ -71,10 +82,27 @@ setMethod(".generateOutput", "ColumnGraphPlot",
71 82
     args[["layout"]] <- deparse(slot(x, "layout"))
72 83
     args[["edge.type"]] <- deparse(slot(x, "edge.type"))
73 84
     args[["add.legend"]] <- deparse(slot(x, "add.legend"))
74
-
85
+    
86
+    if( "Colour" %in% slot(x, "visual_parameters") ){
87
+        args <- .assign_viz_param(args, x, "Edge", "colour")
88
+        args <- .assign_viz_param(args, x, "Node", "colour",
89
+            arg.name = "colour.by")
90
+    }
91
+    
92
+    if( "Shape" %in% slot(x, "visual_parameters") ){
93
+        args <- .assign_viz_param(args, x, "Node", "shape",
94
+            arg.name = "shape.by")
95
+    }
96
+    
97
+    if( "Size" %in% slot(x, "visual_parameters") ){
98
+        args <- .assign_viz_param(args, x, "Edge", "size",
99
+            arg.name = "edge.width.by")
100
+        args <- .assign_viz_param(args, x, "Node", "size", arg.name = "size.by")
101
+    }
102
+    
75 103
     args <- sprintf("%s=%s", names(args), args)
76 104
     args <- paste(args, collapse = ", ")
77
-    fun_call <- sprintf("p <- plotColGraph(se, %s)", args)
105
+    fun_call <- sprintf("p <- miaViz::plotColGraph(se, %s)", args)
78 106
 
79 107
     fun_cmd <- paste(strwrap(fun_call, width = 80, exdent = 4), collapse = "\n")
80 108
     plot_out <- .textEval(fun_cmd, panel_env)
... ...
@@ -1,10 +1,10 @@
1 1
 #' Row graph plot
2 2
 #'
3
-#' Hierarchical tree for the rows of a
4
-#' \code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
5
-#' object. The tree can be produced with \code{\link[mia:taxonomy-methods]{addTaxonomyTree}}
6
-#' and gets stored in the \code{\link[TreeSummarizedExperiment:rowLinks]{rowTree}}
7
-#' slot of the experiment object. The panel implements \code{\link[miaViz:plotTree]{plotRowTree}}
3
+#' Network organisation for the features of a
4
+#' \code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
5
+#' object. The igraph should be stored in the \code{metadata} slot by a name
6
+#' containing \code{"graph"}. This panel uses
7
+#' \code{\link[miaViz:plotColGraph]{plotRowGraph}}
8 8
 #' to generate the plot.
9 9
 #'
10 10
 #' @section Slot overview:
... ...
@@ -17,10 +17,17 @@
17 17
 #' as a named argument.
18 18
 #'
19 19
 #' @examples
20
-#' # Import TreeSE
21 20
 #' library(mia)
22
-#' data("Tengeler2020", package = "mia")
23
-#' tse <- Tengeler2020
21
+#' library(miaViz)
22
+#' data("GlobalPatterns", library = "mia")
23
+#' data("row_graph", library = "miaViz")
24
+#' 
25
+#' tse <- GlobalPatterns
26
+#' tse <- agglomerateByRank(tse,
27
+#'                          rank = "Genus",
28
+#'                          na.rm = TRUE)
29
+#'                          
30
+#' metadata(tse)$graph <- row_graph
24 31
 #' 
25 32
 #' # Store panel into object
26 33
 #' panel <- RowGraphPlot()
... ...
@@ -32,6 +39,10 @@
32 39
 #'   iSEE(tse, initial = c(panel))
33 40
 #' }
34 41
 #' 
42
+#' @seealso
43
+#' \linkS4class{GraphPlot}
44
+#' \linkS4class{ColumnGraphPlot}
45
+#' 
35 46
 #' @author Giulio Benedetti
36 47
 #' 
37 48
 #' @docType methods
... ...
@@ -71,11 +82,28 @@ setMethod(".generateOutput", "RowGraphPlot",
71 82
     args[["layout"]] <- deparse(slot(x, "layout"))
72 83
     args[["edge.type"]] <- deparse(slot(x, "edge.type"))
73 84
     args[["add.legend"]] <- deparse(slot(x, "add.legend"))
85
+    
86
+    if( "Colour" %in% slot(x, "visual_parameters") ){
87
+        args <- .assign_viz_param(args, x, "Edge", "colour")
88
+        args <- .assign_viz_param(args, x, "Node", "colour",
89
+            arg.name = "colour.by")
90
+    }
91
+    
92
+    if( "Shape" %in% slot(x, "visual_parameters") ){
93
+        args <- .assign_viz_param(args, x, "Node", "shape",
94
+            arg.name = "shape.by")
95
+    }
96
+    
97
+    if( "Size" %in% slot(x, "visual_parameters") ){
98
+        args <- .assign_viz_param(args, x, "Edge", "size",
99
+            arg.name = "edge.width.by")
100
+        args <- .assign_viz_param(args, x, "Node", "size", arg.name = "size.by")
101
+    }
74 102
 
75 103
     args <- sprintf("%s=%s", names(args), args)
76 104
     args <- paste(args, collapse = ", ")
77
-    fun_call <- sprintf("p <- plotRowGraph(se, %s)", args)
78
-
105
+    fun_call <- sprintf("p <- miaViz::plotRowGraph(se, %s)", args)
106
+    
79 107
     fun_cmd <- paste(strwrap(fun_call, width = 80, exdent = 4), collapse = "\n")
80 108
     plot_out <- .textEval(fun_cmd, panel_env)
81 109
     all_cmds[["fun"]] <- fun_cmd
... ...
@@ -1,11 +1,11 @@
1 1
 #' Graph plot
2 2
 #'
3
-#' The Graph plot is a virtual class that creates the network structure of
3
+#' The Graph plot is a virtual class that showcases the network organisation of
4 4
 #' either the features or samples of a
5
-#' \code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
5
+#' \code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
6 6
 #' object. The \linkS4class{RowGraphPlot} and \linkS4class{ColumnGraphPlot}
7 7
 #' classes belong to this family and are specialised to visualise the feature
8
-#' or sample graphs stored in metadata, respectively.
8
+#' or sample igraphs stored in metadata, respectively.
9 9
 #'
10 10
 #' @section Slot overview:
11 11
 #' The following slots control the thresholds used in the visualisation:
... ...
@@ -36,7 +36,11 @@
36 36
 #'
37 37
 #' In addition, this class inherits all slots from its parent class
38 38
 #' \linkS4class{Panel}.
39
-#'
39
+#' 
40
+#' @seealso
41
+#' \linkS4class{RowGraphPlot}
42
+#' \linkS4class{ColumnGraphPlot}
43
+#' 
40 44
 #' @author Giulio Benedetti
41 45
 #' 
42 46
 #' @docType methods
... ...
@@ -48,8 +52,8 @@ setValidity2("GraphPlot", function(x) {
48 52
     msg <- character(0)
49 53
     
50 54
     msg <- .singleStringError(msg, x, fields=c("name", "assay.type", "layout",
51
-        "edge.type", "edge.colour.by", "edge.size.by", "colour.by", "shape.by",
52
-        "size.by"))
55
+        "edge.type", "edge.colour.by", "edge.size.by", "node.colour.by",
56
+        "node.shape.by", "node.size.by"))
53 57
     msg <- .validLogicalError(msg, x, fields=c("add.legend", "show.label"))
54 58
 
55 59
     if (length(msg)) {
... ...
@@ -70,9 +74,13 @@ setMethod("initialize", "GraphPlot", function(.Object, ...) {
70 74
     args <- .emptyDefault(args, "add.legend", TRUE)
71 75
     args <- .emptyDefault(args, "edge.colour.by", NA_character_)
72 76
     args <- .emptyDefault(args, "edge.size.by", NA_character_)
73
-    args <- .emptyDefault(args, "colour.by", NA_character_)
74
-    args <- .emptyDefault(args, "size.by", NA_character_)
75
-    args <- .emptyDefault(args, "shape.by", NA_character_)
77
+    args <- .emptyDefault(args, "node.colour.by", NA_character_)
78
+    args <- .emptyDefault(args, "node.size.by", NA_character_)
79
+    args <- .emptyDefault(args, "node.shape.by", NA_character_)
80
+    args <- .emptyDefault(args, "visual_parameters", NA_character_)
81
+    args <- .emptyDefault(args, "colour_parameters", NA_character_)
82
+    args <- .emptyDefault(args, "shape_parameters", NA_character_)
83
+    args <- .emptyDefault(args, "size_parameters", NA_character_)
76 84
 
77 85
     do.call(callNextMethod, c(list(.Object), args))
78 86
 })
... ...
@@ -102,12 +110,13 @@ setMethod(".createObservers", "GraphPlot",
102 110
     panel_name <- .getEncodedName(x)
103 111
 
104 112
     .createProtectedParameterObservers(panel_name, c("layout", "assay.type",
105
-        "name", "edge.type", "show.label", "add.legend", "RowSelectionSource"),
106
-        input=input, pObjects=pObjects, rObjects=rObjects)
113
+        "name", "edge.type", "show.label", "add.legend", "RowSelectionSource",
114
+        "visual_parameters", "colour_parameters", "size_parameters",
115
+        "shape_parameters"), input=input, pObjects=pObjects, rObjects=rObjects)
107 116
     
108 117
     .createUnprotectedParameterObservers(panel_name, c("edge.colour.by",
109
-        "edge.size.by", "size.by", "shape.by", "size.by"), input=input,
110
-        pObjects=pObjects, rObjects=rObjects)
118
+        "edge.size.by", "node.size.by", "node.colour.by", "node.shape.by",
119
+        "node.size.by"), input=input, pObjects=pObjects, rObjects=rObjects)
111 120
     
112 121
     invisible(NULL)
113 122
 })
... ...
@@ -172,9 +181,14 @@ setMethod(".definePanelTour", "GraphPlot", function(x) {
172 181
     callNextMethod())
173 182
 })
174 183
 
184
+#' @importFrom methods slot
185
+#' @importFrom S4Vectors metadata
186
+#' @importFrom tidygraph activate
175 187
 #' @importFrom SummarizedExperiment rowData colData
176 188
 .create_visual_box_for_graph <- function(x, se) {
177 189
     panel_name <- .getEncodedName(x)
190
+    
191
+    edge_data <- as.data.frame(activate(metadata(se)[[slot(x, "name")]], "edges"))
178 192
     gr_data <- switch(substr(panel_name, 1, 3),
179 193
         Row = rowData(se), Col = colData(se))
180 194
 
... ...
@@ -198,49 +212,109 @@ setMethod(".definePanelTour", "GraphPlot", function(x) {
198 212
             and one of them can be selected.")))})
199 213
     .addSpecificTour(class(x)[1], "edge.size.by", function(panel_name) {
200 214
         data.frame(rbind(c(element = paste0("#", panel_name,
201
-            "_edge\\.width\\.by + .selectize-control"), intro = "Here, we can
215
+            "_edge\\.size\\.by + .selectize-control"), intro = "Here, we can
202 216
             choose whether or not to colour the tips by a variable from the
203 217
             <code>metadata</code>. When active, the available options are listed
204 218
             and one of them can be selected.")))})
205
-    .addSpecificTour(class(x)[1], "colour.by", function(panel_name) {
219
+    .addSpecificTour(class(x)[1], "node.colour.by", function(panel_name) {
206 220
         data.frame(rbind(c(element = paste0("#", panel_name,
207
-            "_colour\\.by + .selectize-control"), intro = "Here, we can choose
208
-            whether or not to colour the nodes by a variable from the
221
+            "_node\\.colour\\.by + .selectize-control"), intro = "Here, we can
222
+            choose whether or not to colour the nodes by a variable from the
209 223
             <code>metadata</code>. When active, the available options are listed
210 224
             and one of them can be selected.")))})
211
-    .addSpecificTour(class(x)[1], "shape.by", function(panel_name) {
225
+    .addSpecificTour(class(x)[1], "node.shape.by", function(panel_name) {
212 226
         data.frame(rbind(c(element = paste0("#", panel_name,
213
-            "_shape\\.by + .selectize-control"), intro = "Here, we can order
214
-            the tree alphabetically.")))})
215
-    .addSpecificTour(class(x)[1], "size.by", function(panel_name) {
227
+            "_node\\.shape\\.by + .selectize-control"), intro = "Here, we can
228
+            order the tree alphabetically.")))})
229
+    .addSpecificTour(class(x)[1], "node.size.by", function(panel_name) {
216 230
         data.frame(rbind(c(element = paste0("#", panel_name,
217
-            "_size\\.by + .selectize-control"), intro = "Here, we can
231
+            "_node\\.size\\.by + .selectize-control"), intro = "Here, we can
218 232
             choose how to colour the  tips by.")))})
233
+    .addSpecificTour(class(x)[1], "visual_parameters", function(panel_name) {
234
+        data.frame(rbind(c(element = paste0("#", panel_name,
235
+            "_visual_parameters"), intro = "Here, we can 
236
+            choose to show the different visual parameters.")))})
237
+    .addSpecificTour(class(x)[1], "colour_parameters", function(panel_name) {
238
+        data.frame(rbind(c(element = paste0("#", panel_name,
239
+            "_colour_parameters"), intro = "Here, we can make 
240
+            the colour depend on the value of a
241
+            categorical column data field for each plot components
242
+            (line, tip, node).")))})
243
+    .addSpecificTour(class(x)[1], "shape_parameters", function(panel_name) {
244
+        data.frame(rbind(c(element = paste0("#", panel_name,
245
+            "_shape_parameters"), intro = "Here, we can make 
246
+            the shape depend on the value of a
247
+            categorical column data field for each plot components
248
+            (line, tip, node).")))})
249
+    .addSpecificTour(class(x)[1], "size_parameters", function(panel_name) {
250
+        data.frame(rbind(c(element = paste0("#", panel_name,
251
+            "_size_parameters"), intro = "Here, we can make 
252
+            the size depend on the value of a
253
+            categorical column data field for each plot components
254
+            (line, tip, node).")))})
219 255
     
220 256
     # Define what parameters the user can adjust
221 257
     collapseBox(paste0(panel_name, "_VisualBoxOpen"),
222 258
         title="Visual parameters", open=FALSE,
223 259
         # Graph layout
224 260
         .selectInput.iSEE(x, field="layout", label="Layout:",
225
-            choices=c("auto", "fan", "igraph", "dendrogram", "linear", "matrix",
261
+            choices=c("kk", "fan", "link", "arc", "parallel", "linear", "matrix",
226 262
                 "treemap", "circlepack", "partition", "hive", "cactustree",
227 263
                 "backbone", "centrality", "eigen", "fabric", "focus", "pmds",
228 264
                 "stress", "unrooted", "htree"), selected=slot(x, "layout")),
229 265
         .selectInput.iSEE(x, field="edge.type", label="Edge type:",
230
-            choices=c("link", "arc", "parallel", "fan", "loop", "diagonal",
231
-                "elbow", "bend", "hive", "span", "point", "tile", "density",
232
-                "force", "path", "minimal", "sf"), selected=slot(x, "edge.type")),
266
+            choices=c("fan", "link", "arc", "parallel"),
267
+            selected=slot(x, "edge.type")),
233 268
         .checkboxInput.iSEE(x, field="add.legend", label="View legend",
234 269
             value=slot(x, "add.legend")),
235
-        .selectInput.iSEE(x, field="edge.colour.by", label="Color edges by",
236
-            choices=names(gr_data), selected=slot(x, "edge.colour.by")),
237
-        .selectInput.iSEE(x, field="edge.size.by", label="Widen edges by",
238
-            choices=names(gr_data), selected=slot(x, "edge.size.by")),
239
-        .selectInput.iSEE(x, field="colour.by", label="Color nodes by",
240
-            choices=names(gr_data), selected=slot(x, "colour.by")),
241
-        .selectInput.iSEE(x, field="shape.by", label="Shape nodes by",
242
-            choices=names(gr_data), selected=slot(x, "shape.by")),
243
-        .selectInput.iSEE(x, field="size.by", label="Size edges by",
244
-            choices=names(gr_data), selected=slot(x, "size.by")))
245
-
246
-}
247 270
\ No newline at end of file
271
+        .checkboxGroupInput.iSEE(x, field="visual_parameters", label=NULL,
272
+            inline=TRUE, selected=slot(x, "visual_parameters"),
273
+            choices=c("Colour", "Size", "Shape")),
274
+        
275
+        .conditionalOnCheckGroup(
276
+            paste0(panel_name, "_visual_parameters"), "Colour",
277
+            list(
278
+                .checkboxGroupInput.iSEE(x, field="colour_parameters",
279
+                    inline=TRUE, selected=slot(x, "colour_parameters"),
280
+                    choices=c("Edge", "Node"), label="Colour by:"),
281
+                .conditionalOnCheckGroup(
282
+                    paste0(panel_name, "_colour_parameters"), "Edge",
283
+                        .selectInput.iSEE(x, field="edge.colour.by",
284
+                            label="Colour lines by", choices=names(edge_data),
285
+                            selected=slot(x, "edge.colour.by"))),
286
+                .conditionalOnCheckGroup(
287
+                    paste0(panel_name, "_colour_parameters"), "Node",
288
+                        .selectInput.iSEE(x, field="node.colour.by",
289
+                            label="Colour nodes by", choices=names(gr_data),
290
+                            selected=slot(x, "node.colour.by"))))),
291
+        
292
+        .conditionalOnCheckGroup(
293
+            paste0(panel_name, "_visual_parameters"), "Size",
294
+            list(
295
+                .checkboxGroupInput.iSEE(x, field="size_parameters",
296
+                    inline=TRUE, selected=slot(x, "size_parameters"),
297
+                    choices=c("Edge", "Node"), label="Size by:"),
298
+                .conditionalOnCheckGroup(
299
+                    paste0(panel_name, "_size_parameters"), "Edge",
300
+                        .selectInput.iSEE(x, field="edge.size.by",
301
+                            label="Size lines by", choices=names(edge_data),
302
+                            selected=slot(x, "edge.size.by"))),
303
+                .conditionalOnCheckGroup(
304
+                    paste0(panel_name, "_size_parameters"), "Node",
305
+                        .selectInput.iSEE(x, field="node.size.by",
306
+                            label="Size nodes by", choices=names(gr_data),
307
+                            selected=slot(x, "node.size.by"))))),
308
+        
309
+        .conditionalOnCheckGroup(
310
+            paste0(panel_name, "_visual_parameters"), "Shape",
311
+            list(
312
+                .checkboxGroupInput.iSEE(x, field="shape_parameters",
313
+                    inline=TRUE, selected=slot(x, "shape_parameters"),
314
+                    choices=c("Node"), label="Shape by:"),
315
+                .conditionalOnCheckGroup(
316
+                    paste0(panel_name, "_shape_parameters"), "Node",
317
+                        .selectInput.iSEE(x, field="node.shape.by",
318
+                            label="Shape nodes by", choices=names(gr_data),
319
+                            selected=slot(x, "node.shape.by"))))))
320
+
321
+}
... ...
@@ -216,24 +216,26 @@ setMethod(".definePanelTour", "TreePlot", function(x) {
216 216
         data.frame(rbind(c(element = paste0("#", panel_name,
217 217
             "_add\\.legend"), intro = "Here, we can choose
218 218
             whether or not to show a legend.")))})
219
-    .addSpecificTour(class(x)[1], "edge_colour", function(panel_name) {
219
+    .addSpecificTour(class(x)[1], "add.tip.lab", function(panel_name) {
220 220
         data.frame(rbind(c(element = paste0("#", panel_name,
221
-            "_edge_colour"), intro = "Here, we can choose
222
-            whether or not to colour the lines by a variable from the
223
-            <code>metadata</code>. When active, the available options are listed
224
-            and one of them can be selected.")))})
225
-    .addSpecificTour(class(x)[1], "tip_colour", function(panel_name) {
221
+            "_add\\.tip\\.lab"), intro = "Here, we can choose
222
+            whether or not to show the tip labels.")))})
223
+    .addSpecificTour(class(x)[1], "add.node.lab", function(panel_name) {
226 224
         data.frame(rbind(c(element = paste0("#", panel_name,
227
-            "_tip_colour"), intro = "Here, we can choose
228
-            whether or not to colour the tips by a variable from the
229
-            <code>metadata</code>. When active, the available options are listed
230
-            and one of them can be selected.")))})
231
-    .addSpecificTour(class(x)[1], "node_colour", function(panel_name) {
225
+            "_add\\.node\\.lab"), intro = "Here, we can choose
226
+            whether or not to show the node numbers.")))})
227
+    .addSpecificTour(class(x)[1], "rotate.angle", function(panel_name) {
232 228
         data.frame(rbind(c(element = paste0("#", panel_name,
233
-            "_node_colour"), intro = "Here, we can choose
234
-            whether or not to colour the nodes by a variable from the
235
-            <code>metadata</code>. When active, the available options are listed
236
-            and one of them can be selected.")))})
229
+            "_rotate\\.angle"), intro = "Here, we can specify the angle by which
230
+            to rotate the tree.")))})
231
+    .addSpecificTour(class(x)[1], "open.angle", function(panel_name) {
232
+        data.frame(rbind(c(element = paste0("#", panel_name,
233
+            "_open\\.angle"), intro = "Here, we can specify the angle by which
234
+            to open the tree.")))})
235
+    .addSpecificTour(class(x)[1], "branch.length", function(panel_name) {
236
+        data.frame(rbind(c(element = paste0("#", panel_name,
237
+            "_branch\\.length"), intro = "Here, we can choose whether branch
238
+            length should be equalised.")))})
237 239
     .addSpecificTour(class(x)[1], "order.tree", function(panel_name) {
238 240
         data.frame(rbind(c(element = paste0("#", panel_name,
239 241
             "_order\\.tree"), intro = "Here, we can order
... ...
@@ -371,13 +373,16 @@ setMethod(".definePanelTour", "TreePlot", function(x) {
371 373
 }
372 374
 
373 375
 #' @importFrom methods slot
374
-.assign_viz_param <- function(args, x, element, aesthetic) {
375
-  
376
-    param_name <- paste(tolower(element), aesthetic, "by", sep = ".")
377
-    
376
+.assign_viz_param <- function(args, x, element, aesthetic, arg.name = NULL) {
377
+    # Build panel slot name
378
+    slot_name <- paste(tolower(element), aesthetic, "by", sep = ".")
379
+    # Use slot name if arg name is not given
380
+    if( is.null(arg.name) ){
381
+        arg.name <- slot_name
382
+    }
383
+    # Add slot value to args
378 384
     if( element %in% slot(x, paste(aesthetic, "parameters", sep = "_")) ){
379
-        args[[param_name]] <- deparse(slot(x, param_name))
385
+        args[[arg.name]] <- deparse(slot(x, slot_name))
380 386
     }
381
-  
382 387
     return(args)
383 388
 }
384 389
\ No newline at end of file
... ...
@@ -11,11 +11,11 @@ ColumnGraphPlot class, where any slot and its value can be passed to
11 11
 \code{...} as a named argument.
12 12
 }
13 13
 \description{
14
-Hierarchical tree for the rows of a
15
-\code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
16
-object. The tree can be produced with \code{\link[mia:taxonomy-methods]{addTaxonomyTree}}
17
-and gets stored in the \code{\link[TreeSummarizedExperiment:rowLinks]{rowTree}}
18
-slot of the experiment object. The panel implements \code{\link[miaViz:plotTree]{plotRowTree}}
14
+Network organisation for the samples of a
15
+\code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
16
+object. The igraph should be stored in the \code{metadata} slot by a name
17
+containing \code{"graph"}. This panel uses
18
+\code{\link[miaViz:plotColGraph]{plotColGraph}}
19 19
 to generate the plot.
20 20
 }
21 21
 \section{Slot overview}{
... ...
@@ -25,10 +25,17 @@ This class inherits all slots from its parent class \linkS4class{GraphPlot}.
25 25
 }
26 26
 
27 27
 \examples{
28
-# Import TreeSE
29 28
 library(mia)
30
-data("Tengeler2020", package = "mia")
31
-tse <- Tengeler2020
29
+library(miaViz)
30
+data("GlobalPatterns", library = "mia")
31
+data("col_graph", library = "miaViz")
32
+
33
+tse <- GlobalPatterns
34
+tse <- agglomerateByRank(tse,
35
+                         rank = "Genus",
36
+                         na.rm = TRUE)
37
+                         
38
+metadata(tse)$graph <- col_graph
32 39
 
33 40
 # Store panel into object
34 41
 panel <- ColumnGraphPlot()
... ...
@@ -40,6 +47,10 @@ if (interactive()) {
40 47
   iSEE(tse, initial = c(panel))
41 48
 }
42 49
 
50
+}
51
+\seealso{
52
+\linkS4class{GraphPlot}
53
+\linkS4class{RowGraphPlot}
43 54
 }
44 55
 \author{
45 56
 Giulio Benedetti
... ...
@@ -6,12 +6,12 @@
6 6
 \alias{GraphPlot}
7 7
 \title{Graph plot}
8 8
 \description{
9
-The Graph plot is a virtual class that creates the network structure of
9
+The Graph plot is a virtual class that showcases the network organisation of
10 10
 either the features or samples of a
11
-\code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
11
+\code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
12 12
 object. The \linkS4class{RowGraphPlot} and \linkS4class{ColumnGraphPlot}
13 13
 classes belong to this family and are specialised to visualise the feature
14
-or sample graphs stored in metadata, respectively.
14
+or sample igraphs stored in metadata, respectively.
15 15
 }
16 16
 \section{Slot overview}{
17 17
 
... ...
@@ -45,6 +45,10 @@ In addition, this class inherits all slots from its parent class
45 45
 \linkS4class{Panel}.
46 46
 }
47 47
 
48
+\seealso{
49
+\linkS4class{RowGraphPlot}
50
+\linkS4class{ColumnGraphPlot}
51
+}
48 52
 \author{
49 53
 Giulio Benedetti
50 54
 }
... ...
@@ -11,11 +11,11 @@ RowGraphPlot class, where any slot and its value can be passed to \code{...}
11 11
 as a named argument.
12 12
 }
13 13
 \description{
14
-Hierarchical tree for the rows of a
15
-\code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-constructor]{TreeSummarizedExperiment}}
16
-object. The tree can be produced with \code{\link[mia:taxonomy-methods]{addTaxonomyTree}}
17
-and gets stored in the \code{\link[TreeSummarizedExperiment:rowLinks]{rowTree}}
18
-slot of the experiment object. The panel implements \code{\link[miaViz:plotTree]{plotRowTree}}
14
+Network organisation for the features of a
15
+\code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}}
16
+object. The igraph should be stored in the \code{metadata} slot by a name
17
+containing \code{"graph"}. This panel uses
18
+\code{\link[miaViz:plotColGraph]{plotRowGraph}}
19 19
 to generate the plot.
20 20
 }
21 21
 \section{Slot overview}{
... ...
@@ -25,10 +25,17 @@ This class inherits all slots from its parent class \linkS4class{GraphPlot}.
25 25
 }
26 26
 
27 27
 \examples{
28
-# Import TreeSE
29 28
 library(mia)
30
-data("Tengeler2020", package = "mia")
31
-tse <- Tengeler2020
29
+library(miaViz)
30
+data("GlobalPatterns", library = "mia")
31
+data("row_graph", library = "miaViz")
32
+
33
+tse <- GlobalPatterns
34
+tse <- agglomerateByRank(tse,
35
+                         rank = "Genus",
36
+                         na.rm = TRUE)
37
+                         
38
+metadata(tse)$graph <- row_graph
32 39
 
33 40
 # Store panel into object
34 41
 panel <- RowGraphPlot()
... ...
@@ -40,6 +47,10 @@ if (interactive()) {
40 47
   iSEE(tse, initial = c(panel))
41 48
 }
42 49
 
50
+}
51
+\seealso{
52
+\linkS4class{GraphPlot}
53
+\linkS4class{ColumnGraphPlot}
43 54
 }
44 55
 \author{
45 56
 Giulio Benedetti
... ...
@@ -155,6 +155,10 @@ Supported operations:
155 155
 - selecting edge type
156 156
 - customising aesthetics
157 157
 
158
+```{r tree_plot, echo=FALSE, out.width="100%"}
159
+SCREENSHOT("screenshots/RowGraphPlot.png", delay=20)
160
+```
161
+
158 162
 # Other panels {#sec-other}
159 163
 
160 164
 | Panel name         | Panel class    | Purpose                                     |
161 165
new file mode 100644
162 166
Binary files /dev/null and b/vignettes/screenshots/RowGraphPlot.png differ