Add overview

This commit is contained in:
Elias Projahn 2022-05-30 20:08:54 +02:00
parent 80d81c572d
commit 20faaea93d
5 changed files with 72 additions and 47 deletions

View file

@ -15,7 +15,7 @@ Description: This package contains precomputed data including comparisons in
License: AGPL (>= 3)
Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.1.2
RoxygenNote: 7.2.0
Depends:
R (>= 2.10)
LazyData: true

66
R/plots.R Normal file
View file

@ -0,0 +1,66 @@
#' Create a plot showing an overview over the provided ranking.
#'
#' @param ranked_data The ranking to visualize.
#' @param sample_proportion Proportion of rows to use as the shown sample.
#'
#' @return A `plotly` figure.
#' @noRd
overview_plot <- function(ranked_data, sample_proportion = 0.05) {
plotly::plot_ly() |>
plotly::add_lines(
data = ranked_data[sample(
nrow(ranked_data),
sample_proportion * nrow(ranked_data)
)],
x = ~rank,
y = ~score
) |>
plotly::layout(
xaxis = list(title = "Ranks"),
yaxis = list(title = "Score")
)
}
#' Create plot showing the distribution of scores using `plotly`.
#'
#' @param ranked_data Data on genes with precomputed ranks.
#' @param ranks How may ranks the x-axis should include. If this parameter is
#' `NULL`, all ranks will be shown.
#'
#' @return A `plotly` figure for rendering.
#' @noRd
scores_plot <- function(ranked_data, ranks = 1000) {
data <- if (is.null(ranks)) {
ranked_data
} else {
ranked_data[1:ranks]
}
ranks_label <- if (is.null(ranks)) {
"Ranks"
} else {
glue::glue("Ranks (1 to {ranks})")
}
plotly::plot_ly() |>
plotly::add_markers(
data = data,
x = ~rank,
y = ~score,
text = ~hgnc_name,
customdata = ~percentile,
hovertemplate = paste0(
"<b>%{text}</b><br>",
"Rank: %{x}<br>",
"Score: %{y:.2}<br>",
"Percentile: %{customdata:.2%}",
"<extra></extra>"
)
) |>
plotly::layout(
xaxis = list(title = ranks_label),
yaxis = list(title = "Score"),
clickmode = "event+select",
dragmode = "select"
)
}

View file

@ -25,6 +25,7 @@ server <- function(input, output) {
data
})
output$overview_plot <- plotly::renderPlotly(overview_plot(ranked_data()))
output$scores_plot <- plotly::renderPlotly(scores_plot(ranked_data()))
output$selected_genes <- DT::renderDataTable({
@ -40,50 +41,6 @@ server <- function(input, output) {
})
}
#' Create plot showing the distribution of scores using `plotly`.
#'
#' @param ranked_data Data on genes with precomputed ranks.
#' @param ranks How may ranks the x-axis should include. If this parameter is
#' `NULL`, all ranks will be shown.
#'
#' @return A `plotly` figure for rendering.
#' @noRd
scores_plot <- function(ranked_data, ranks = 1000) {
data <- if (is.null(ranks)) {
ranked_data
} else {
ranked_data[1:ranks]
}
ranks_label <- if (is.null(ranks)) {
"Ranks"
} else {
glue::glue("Ranks (1 to {ranks})")
}
plotly::plot_ly() |>
plotly::add_markers(
data = data,
x = ~rank,
y = ~score,
text = ~hgnc_name,
customdata = ~percentile,
hovertemplate = paste0(
"<b>%{text}</b><br>",
"Rank: %{x}<br>",
"Score: %{y:.2}<br>",
"Percentile: %{customdata:.2%}",
"<extra></extra>"
)
) |>
plotly::layout(
xaxis = list(title = ranks_label),
yaxis = list(title = "Score"),
clickmode = "event+select",
dragmode = "select"
)
}
#' Create a displayable data table from the gene results data.
#' @noRd
genes_table <- function(data) {

3
R/ui.R
View file

@ -90,6 +90,9 @@ ui <- function() {
mainPanel(
width = 9,
h3("Distribution of scores"),
h4("Overview"),
plotly::plotlyOutput("overview_plot", height = "200px"),
h4("Focus on top genes"),
div(paste0(
"Click or drag within the figure to select genes of ",
"interest."

View file

@ -1,5 +1,4 @@
#' Various things that should be imported into the package namespace.
#'
# Various things that should be imported into the package namespace.
#' @importFrom data.table :=
#' @importFrom data.table .BY
#' @importFrom data.table .EACHI