Skip to content
Snippets Groups Projects
Commit 9cbf455f authored by Ustjanzew's avatar Ustjanzew
Browse files

extended the functionality

parent dd217637
No related branches found
No related tags found
No related merge requests found
Showing
with 660 additions and 47 deletions
......@@ -14,4 +14,5 @@ LazyData: true
RoxygenNote: 6.1.1
Imports:
knitr,
flexdashboard
flexdashboard,
yaml
......@@ -4,4 +4,6 @@ export("%>%")
exportClasses(i2dashboard)
exportMethods(add_component)
exportMethods(add_page)
exportMethods(assemble)
exportMethods(remove_page)
importFrom(magrittr,"%>%")
setGeneric("assemble", function(object, ...) standardGeneric("assemble"))
#' Method to assemble a dashboard and write it to a file
#'
#' @param object A \linkS4class{i2dash::i2dashboard} object.
#' @param output_file The output filename (recommend that the suffix should be '.Rmd'). This file will be saved in the working directory.
#' @param pages A string or vector with the names of pages, which should be assemble to a report.
#' @param ... Additional parameters passed to the components render function.
#'
#' @rdname idashboard-class
#' @export
setMethod("assemble", "i2dashboard", function(object, output_file, pages, ...) {
yaml_list <- list(title = object@title,
author = object@author,
output = list("flexdashboard::flex_dashboard" = list(theme = object@theme)))
if (object@interactive){
yaml_list[["runtime"]] <- "shiny"
}
yaml_part <- yaml::as.yaml(yaml_list)
header_string <- paste0("---\n", yaml_part, "---\n")
tmp_document <- tempfile()
# create variable final_document
final_document <- file.path(object@workdir, output_file)
# write header to tempfile
cat(header_string, file = tmp_document, append = FALSE, sep='')
# write page to tempfile
for (pagename in pages){
name <- .create_page_name(pagename)
if (name %in% names(object@pages)){
# Create a content string from all components
components <- paste0(object@pages[[name]]$components, sep = "")
#components <- "here are the components"
# Create variable "title" & "menu" & "layout" for readability
title <- object@pages[[name]]$title
menu <- object@pages[[name]]$menu
layout <- object@pages[[name]]$layout
# Check menu argument
if (is.null(menu)){
menu <- ""
}
# Check layout argument
if (any(layout == "storyboard")){
layout <- ".storyboard"
} else {
if(!is.null(layout)) warning("layout argument is not known.")
layout <- ""
}
layout_with_menu <- sprintf('{%s data-navmenu="%s"}', layout, menu)
timestamp <- Sys.time()
full_content <- knitr::knit_expand(file = system.file("templates", "page_template.Rmd", package = "i2dash"), title = title, layout_with_menu = layout_with_menu, components = components, date = timestamp)
cat(full_content, file = tmp_document, append = TRUE, sep='')
#cat(object@pages[[name]]$header, file = tmp_document, append = TRUE, sep='')
#cat(object@pages[[name]]$components, file = tmp_document, append = TRUE, sep='')
} else {
warning(sprintf("i2dashboard object does not contain Pagename '%s'", pagename))
}
}
# copy tempfile to final_document
file.copy(from = tmp_document, to = final_document, overwrite = TRUE)
})
\ No newline at end of file
......@@ -9,7 +9,7 @@ setGeneric("add_component", function(object, ...) standardGeneric("add_component
#'
#' @rdname idashboard-class
#' @export
setMethod("add_component", "i2dashboard", function(object, page, component, ...) {
setMethod("add_component", "i2dashboard", function(object, page = "default", component, ...) {
pn <- strsplit(component, "::")[[1]]
eval_function <- if(length(pn) == 1) {
get(paste0("render_", pn[[1]]), envir = asNamespace("i2dash"), mode = "function")
......@@ -17,7 +17,13 @@ setMethod("add_component", "i2dashboard", function(object, page, component, ...)
get(paste0("render_", pn[[2]]), envir = asNamespace(pn[[1]]), mode = "function")
}
component <- do.call(eval_function, args = list(...))
object@pages[[page]]$components <- append(object@pages[[page]]$components, component)
component <- do.call(eval_function, args = list(object, ...))
name <- .create_page_name(page)
if (name %in% names(object@pages)){
object@pages[[name]]$components <- append(object@pages[[name]]$components, component)
} else {
warning(sprintf("i2dashboard object does not contain Pagename %s", name))
}
return(object)
})
#' Renders a features by factor violin plot
#'
#' @param plot_title The title of the Component
#' @param x A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#' @param y A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.(Needs to be categorial. Horizontal violinplots are not possible.)
#'
#' @return A string containing markdown code for the rendered textbox
render_features_by_factors <- function(object, plot_title, x, y) {
env_id <- .create_id()
# validate input, create environment variables, save environment object
.validate_input_ff(object, env_id, x, y)
timestamp <- Sys.time()
expanded_component <- knitr::knit_expand(file = system.file("templates", "features_by_factors_template.Rmd", package = "i2dash"), plot_title = plot_title, env_id = env_id, date = timestamp)
return(expanded_component)
}
.create_id <- function(n = 1) {
a <- do.call(paste0, replicate(5, sample(LETTERS, n, TRUE), FALSE))
paste0(a, sprintf("%04d", sample(9999, n, TRUE)), sample(LETTERS, n, TRUE))
}
.validate_input_ff <- function(object, env_id, x, y) {
env <- new.env()
env$x_selection <- FALSE
env$y_selection <- FALSE
# validate x and create environment variables
if(is.list(x) & length(x) == 1) {
if (is.factor(x[[1]])){
env$x <- x
} else {
stop("x should contain factors")
}
} else if (is.list(x) & length(x) > 1) {
for (i in length(x)){
if (is.factor(x[[i]])){
env$x_selection <- TRUE
env$x <- x
} else {
stop("x should contain only factors")
}
}
} else if (!is.list(x) | (is.list(x) & length(x) == 0)){
stop("x needs to be a named list with at least one element")
}
# validate y and create environment variables
if(is.list(y) & length(y) == 1) {
env$y <- y
} else if (is.list(y) & length(y) > 1) {
env$y_selection <- TRUE
env$y <- y
} else if (!is.list(y) | (is.list(y) & length(y) == 0)){
stop("y needs to be a named list with at least one element")
}
# save environment as rds-object
saveRDS(env, file = file.path(object@workdir, "envs", sprintf("%s.rds", env_id)))
}
\ No newline at end of file
#' The idashboard S4 class
#'
#' @slot title The dashboards title
#' @slot author The author of the dashboard
#' @slot interactive If a shiny-based report should be created
#' @slot theme The theme of the dashboard
#' @slot pages A list of dashboard pages
#'
#' @name idashboard-class
#' @rdname idashboard-class
#' @export
i2dashboard <- setClass("i2dashboard",
slots = c(title = "character", pages = "list"))
setClass("i2dashboard",
slots = c(
title = "character",
author = "character",
interactive = "logical",
theme = "character",
workdir = "character",
pages = "list"
),
prototype=list(
theme = "yeti",
pages = list(default = list(title = "Default page", layout = NULL, menu = NULL, components = list()))
)
)
setMethod("show", "i2dashboard", function(object) {
cat("A flexdashboard with the title: ", object@title, "\n", sep = "")
if(length(object@pages) > 0) {
cat("... containing ", length(object@pages), "pages.")
cat("... containing ", length(object@pages), "pages:\n")
for (pagename in names(object@pages)){
cat(sprintf(" ... the page '%s' with the title '%s' contains %i components.\n", pagename, object@pages[[pagename]]$title, length(object@pages[[pagename]]$components)))
}
} else {
cat("... containing 0 pages.")
}
})
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
### Validity.
###
# .valid.RmdReport <- function(object){
# msg <- NULL
# # Checking header
# if (!is.character(object@header)){
# msg <- c(msg, "'header' must be a character-like object")
# }
# # Checking pages
# if (!is.list(object@pages)){
# msg <- c(msg, "'pages' must be a list-like object")
# }
# if (length(msg)) { return(msg) }
# return(TRUE)
# }
#
# setValidity("RmdReport", .valid.RmdReport)
#' Renders a Sequence saturation plot
#'
#' @param plot_title The title of the Component
#' @param x A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#' @param y A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#' @param color_by A list with the color_by values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#'
#' @return A string containing markdown code for the rendered textbox
render_multiplot <- function(object, plot_title, x, y, color_by) {
env_id <- .create_id()
# validate input, create environment variables, save environment object
.validate_input(object, env_id, x, y, color_by)
timestamp <- Sys.time()
expanded_component <- knitr::knit_expand(file = system.file("templates", "multiplot_template.Rmd", package = "i2dash"), plot_title = plot_title, env_id = env_id, date = timestamp)
return(expanded_component)
}
.create_id <- function(n = 1) {
a <- do.call(paste0, replicate(5, sample(LETTERS, n, TRUE), FALSE))
paste0(a, sprintf("%04d", sample(9999, n, TRUE)), sample(LETTERS, n, TRUE))
}
.validate_input <- function(object, env_id, x, y, color_by) {
env <- new.env()
env$x_selection <- FALSE
env$y_selection <- FALSE
env$color_selection <- FALSE
# validate x and create environment variables
if(is.list(x) & length(x) == 1) {
env$x <- x
} else if (is.list(x) & length(x) > 1) {
env$x_selection <- TRUE
env$x <- x
} else if (!is.list(x) | (is.list(x) & length(x) == 0)){
stop("x needs to be a named list with at least one element")
}
# validate y and create environment variables
if(is.list(y) & length(y) == 1) {
env$y <- y
} else if (is.list(y) & length(y) > 1) {
env$y_selection <- TRUE
env$y <- y
} else if (!is.list(y) | (is.list(y) & length(y) == 0)){
stop("y needs to be a named list with at least one element")
}
# validate color_by and create environment variables
if(is.list(color_by) & length(color_by) == 1) {
env$color_by <- color_by
} else if (is.list(color_by) & length(color_by) > 1) {
env$color_selection <- TRUE
env$color_by <- color_by
} else if (!is.list(color_by) | (is.list(color_by) & length(color_by) == 0)){
stop("color_by needs to be a named list with at least one element")
}
# for (i in color_by){
# if (!is.factor(i)){
# stop("color_by needs to be a list with factorial elements")
# }
# }
# save environment as rds-object
saveRDS(env, file = file.path(object@workdir, "envs", sprintf("%s.rds", env_id)))
}
\ No newline at end of file
......@@ -21,14 +21,53 @@ setGeneric("add_page", function(object, ...) standardGeneric("add_page"))
#'
#' @rdname idashboard-class
#' @export
setMethod("add_page", "i2dashboard", function(object, page, title, layout = "storyboard", menu = title, ...) {
setMethod("add_page", "i2dashboard", function(object, page, title, layout = "storyboard", menu = NULL, ...) {
name <- .create_page_name(page)
object@pages[[name]] <- list(title = title, layout = layout, menu = menu, components = list())
# Create working directory and directory for environments
dir.create(object@workdir, showWarnings = FALSE)
dir.create(file.path(object@workdir, "envs"), recursive = T, showWarnings = FALSE)
if (name %in% names(object@pages)){
print("A page with this 'page'-argument already exists.")
answer1 <- menu(c("Yes", "No"), title="Do you want to overwrite this page? If 'No' you can input another 'page'-argument or cancel.")
switch (answer1,
"1"={
print("The page was overwritten.")
object@pages[[name]] <- list(title = title, layout = layout, menu = menu, components = list())
},
"2"={
answer2 <- menu(c("Yes", "Cancel"), title="Do you want to provide another 'page'-argument?")
switch (answer2,
"1"={
new_name <- readline("Please input a new 'page'-argument: ")
if (is.character(new_name)){
new_name <- .create_page_name(new_name)
print("Page with new 'page'-argument created.")
object@pages[[new_name]] <- list(title = title, layout = layout, menu = menu, components = list())
}
},
"2"={
print("Function 'add_page' canceled")
}
)
}
)
} else {
object@pages[[name]] <- list(title = title, layout = layout, menu = menu, components = list())
}
return(object)
})
setGeneric("remove_page", function(object, ...) standardGeneric("remove_page"))
#' Method to remove a page to an i2dashboard object
#'
#' @param object A \linkS4class{i2dash::i2dashboard} object.
#' @param page The name of the page to be removed.
#'
#' @rdname idashboard-class
#' @export
setMethod("remove_page", "i2dashboard", function(object, page) {
name <- .create_page_name(page)
object@pages[[name]] <- NULL
......
#' Renders a Sequence saturation plot
#'
#' @param plot_title The title of the Component
#' @param x A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#' @param y A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#' @param color_by A list with the color_by values. If it is a nested list, a dropdown-field will be provided in the interactive mode.
#'
#' @return A string containing markdown code for the rendered textbox
render_sequence_saturation <- function(object, plot_title, x, y, color_by) {
env_id <- .create_id()
# validate input, create environment variables, save environment object
.validate_input(object, env_id, x, y, color_by)
timestamp <- Sys.time()
expanded_component <- knitr::knit_expand(file = system.file("templates", "sequence_saturation_template.Rmd", package = "i2dash"), plot_title = plot_title, env_id = env_id, date = timestamp)
return(expanded_component)
}
.create_id <- function(n = 1) {
a <- do.call(paste0, replicate(5, sample(LETTERS, n, TRUE), FALSE))
paste0(a, sprintf("%04d", sample(9999, n, TRUE)), sample(LETTERS, n, TRUE))
}
.validate_input <- function(object, env_id, x, y, color_by) {
env <- new.env()
env$x_selection <- FALSE
env$y_selection <- FALSE
env$color_selection <- FALSE
# validate x and create environment variables
if(is.list(x) & length(x) == 1) {
env$x <- x
} else if (is.list(x) & length(x) > 1) {
env$x_selection <- TRUE
env$x <- x
} else if (!is.list(x) | (is.list(x) & length(x) == 0)){
stop("x needs to be a named list with at least one element")
}
# validate y and create environment variables
if(is.list(y) & length(y) == 1) {
env$y <- y
} else if (is.list(y) & length(y) > 1) {
env$y_selection <- TRUE
env$y <- y
} else if (!is.list(y) | (is.list(y) & length(y) == 0)){
stop("y needs to be a named list with at least one element")
}
# validate color_by and create environment variables
if(is.list(color_by) & length(color_by) == 1) {
env$color_by <- color_by
} else if (is.list(color_by) & length(color_by) > 1) {
env$color_selection <- TRUE
env$color_by <- color_by
} else if (!is.list(color_by) | (is.list(color_by) & length(color_by) == 0)){
stop("color_by needs to be a named list with at least one element")
}
# for (i in color_by){
# if (!is.factor(i)){
# stop("color_by needs to be a list with factorial elements")
# }
# }
# save environment as rds-object
saveRDS(env, file = file.path(object@workdir, "envs", sprintf("%s.rds", env_id)))
}
\ No newline at end of file
#' Renders a textbox with arbitrary content
#'
#' @param title The title of the textbox
#' @param content The content of the textbox
#'
#' @return A string containing markdown code for the rendered textbox
render_textbox <- function(title, content) {
knitr::knit_expand(file = system.file("templates", "textbox.Rmd", package = "i2dash"), title = title, content = content)
}
\ No newline at end of file
### {{plot_title}}
<!-- Page created on {{ date }} -->
```{r}
{{ env_id }} = readRDS("envs/{{ env_id }}.rds")
plotly::plotlyOutput("plot_{{ env_id }}")
output$plot_{{ env_id }} <- plotly::renderPlotly({
if (!{{ env_id }}$x_selection){
x_value <- {{ env_id }}$x[[1]]
x_title <- names({{ env_id }}$x)
} else {
x_value <- {{ env_id }}$x[[input$select_x_{{ env_id }}]]
x_title <- input$select_x_{{ env_id }}
}
if (!{{ env_id }}$y_selection){
y_value <- {{ env_id }}$y[[1]]
y_title <- names({{ env_id }}$y)
} else {
y_value <- {{ env_id }}$y[[input$select_y_{{ env_id }}]]
y_title <- input$select_y_{{ env_id }}
}
p <- plotly::plot_ly(data.frame(x_value, y_value),
x = x_value,
y = y_value,
split = x_value,
type = 'violin',
box = list(
visible = T
),
meanline = list(
visible = T
)
)
p <- plotly::layout(p,
xaxis = list(title = x_title),
yaxis = list(title = y_title,
zeroline = F))
p
})
```
***
```{r}
# selection field for x
if ({{ env_id }}$x_selection){
selectInput("select_x_{{ env_id }}", label = "Select data for x axis:",
choices = names({{ env_id }}$x))
}
# selection field for y
if ({{ env_id }}$y_selection){
selectInput("select_y_{{ env_id }}", label = "Select data for y axis:",
choices = names({{ env_id }}$y))
}
```
Plot description:
Sequencing is called *saturated* when generating more sequencing output from a cDNA library does not substantially increase the number of detected features in a sample. Since the number of detected features can act as a technical confounder, and thereby drive substructure in the data, it is advisable to aim for a saturated sequencing by either adding more sequencing output or decreasing the number of samples until saturation is achieved. [@zhang_one_2018] gives advise on how to choose the optimal cell number given a fixed sequencing budget
### {{plot_title}}
<!-- Component created on {{ date }} -->
```{r}
{{ env_id }} = readRDS("envs/{{ env_id }}.rds")
df <- data.frame({{ env_id }}$x, {{ env_id }}$y, {{ env_id }}$color_by)
df.melted <- reshape::melt(df, id=c(names({{ env_id }}$y), names({{ env_id }}$color_by)))
plotly::plotlyOutput("plot_{{ env_id }}")
output$plot_{{ env_id }} <- plotly::renderPlotly({
if (!{{ env_id }}$y_selection){
index_y <- match(names({{ env_id }}$y), names(df.melted))
} else {
index_y <- match(input$select_y_{{ env_id }}, names(df.melted))
}
if (!{{ env_id }}$color_selection){
index_color <- match(names({{ env_id }}$color_by), names(df.melted))
} else {
index_color <- match(input$select_color_{{ env_id }}, names(df.melted))
}
g1 <- ggplot2::ggplot(df.melted, mapping = ggplot2::aes(y = value, x = df.melted[,index_y], color = df.melted[,index_color])) +
ggplot2::geom_jitter() +
ggplot2::geom_violin(mapping = ggplot2::aes(y = value), scale = "count") +
ggplot2::facet_grid(. ~ variable, scales = "free_x") +
ggplot2::theme_bw() +
ggplot2::theme(panel.border = ggplot2::element_blank()) +
ggplot2::scale_colour_viridis_c() +
ggplot2::coord_flip() +
ggplot2::labs( y="Type", x="", color=names(df.melted)[index_color])
plotly::ggplotly(g1)
})
```
***
```{r}
# selection field for y
if ({{ env_id }}$y_selection){
selectInput("select_y_{{ env_id }}", label = "Select data for y axis:",
choices = names({{ env_id }}$y))
}
# selection field for color_by
if ({{ env_id }}$color_selection){
selectInput("select_color_{{ env_id }}", label = "Select experimental factor for coloring:",
choices = names({{ env_id }}$color_by))
}
```
Plot description:
Sequencing is called *saturated* when generating more sequencing output from a cDNA library does not substantially increase the number of detected features in a sample. Since the number of detected features can act as a technical confounder, and thereby drive substructure in the data, it is advisable to aim for a saturated sequencing by either adding more sequencing output or decreasing the number of samples until saturation is achieved. [@zhang_one_2018] gives advise on how to choose the optimal cell number given a fixed sequencing budget
{{ title }} {{ layout_with_menu }}
=========================================
<!-- Page created on {{ date }} -->
{{ components }}
\ No newline at end of file
### {{plot_title}}
<!-- Component created on {{ date }} -->
```{r}
{{ env_id }} = readRDS("envs/{{ env_id }}.rds")
plotly::plotlyOutput("plot_{{ env_id }}")
output$plot_{{ env_id }} <- plotly::renderPlotly({
if (!{{ env_id }}$x_selection){
x_value <- {{ env_id }}$x[[1]]
x_title <- names({{ env_id }}$x)
} else {
x_value <- {{ env_id }}$x[[input$select_x_{{ env_id }}]]
x_title <- input$select_x_{{ env_id }}
}
if (!{{ env_id }}$y_selection){
y_value <- {{ env_id }}$y[[1]]
y_title <- names({{ env_id }}$y)
} else {
y_value <- {{ env_id }}$y[[input$select_y_{{ env_id }}]]
y_title <- input$select_y_{{ env_id }}
}
if (!{{ env_id }}$color_selection){
color_value <- {{ env_id }}$color_by[[1]]
} else {
color_value <- {{ env_id }}$color_by[[input$select_color_{{ env_id }}]]
}
p <- plotly::plot_ly(data.frame(x_value, y_value, color_value),
x = x_value,
y = y_value,
color = color_value
)
p <- plotly::layout(p,
xaxis = list(title = x_title),
yaxis = list(title = y_title))
p
})
```
***
```{r}
# selection field for x
if ({{ env_id }}$x_selection){
selectInput("select_x_{{ env_id }}", label = "Select data for x axis:",
choices = names({{ env_id }}$x))
}
# selection field for y
if ({{ env_id }}$y_selection){
selectInput("select_y_{{ env_id }}", label = "Select data for y axis:",
choices = names({{ env_id }}$y))
}
# selection field for color_by
if ({{ env_id }}$color_selection){
selectInput("select_color_{{ env_id }}", label = "Select experimental factor for coloring:",
choices = names({{ env_id }}$color_by))
}
```
Plot description:
Sequencing is called *saturated* when generating more sequencing output from a cDNA library does not substantially increase the number of detected features in a sample. Since the number of detected features can act as a technical confounder, and thereby drive substructure in the data, it is advisable to aim for a saturated sequencing by either adding more sequencing output or decreasing the number of samples until saturation is achieved. [@zhang_one_2018] gives advise on how to choose the optimal cell number given a fixed sequencing budget
### {{ title }}
### {{ page_title }}
{{ content }} {.storyboard}
{{ content }}
\ No newline at end of file
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/components.R, R/i2dashboard.R, R/pages.R
% Please edit documentation in R/assemble.R, R/components.R, R/i2dashboard.R,
% R/pages.R
\docType{methods}
\name{add_component,i2dashboard-method}
\name{assemble,i2dashboard-method}
\alias{assemble,i2dashboard-method}
\alias{add_component,i2dashboard-method}
\alias{idashboard-class}
\alias{i2dashboard}
\alias{add_page,i2dashboard-method}
\title{Method to add a component to a page of an i2dashboard object}
\alias{remove_page,i2dashboard-method}
\title{Method to assemble a dashboard and write it to a file}
\usage{
\S4method{add_component}{i2dashboard}(object, page, component, ...)
\S4method{assemble}{i2dashboard}(object, output_file, pages, ...)
\S4method{add_component}{i2dashboard}(object, page = "default",
component, ...)
\S4method{add_page}{i2dashboard}(object, page, title,
layout = "storyboard", menu = title, ...)
layout = "storyboard", menu = NULL, ...)
\S4method{remove_page}{i2dashboard}(object, page)
}
\arguments{
\item{object}{A \linkS4class{i2dash::i2dashboard} object.}
\item{page}{The name of the page to add the component to.}
\item{output_file}{The output filename (recommend that the suffix should be '.Rmd'). This file will be saved in the working directory.}
\item{component}{The name of the component.}
\item{pages}{A string or vector with the names of pages, which should be assemble to a report.}
\item{...}{Additional parameters passed to the components render function.}
\item{page}{The name of the page to add the component to.}
\item{component}{The name of the component.}
\item{title}{The title of the page to be added.}
\item{layout}{The page layout (see below).}
......@@ -30,20 +41,38 @@
\item{object}{A \linkS4class{i2dash::i2dashboard} object.}
\item{...}{Additional parameters passed to the components render function.}
\item{object}{A \linkS4class{i2dash::i2dashboard} object.}
\item{page}{The name of the page to be added.}
\item{object}{A \linkS4class{i2dash::i2dashboard} object.}
\item{page}{The name of the page to be removed.}
}
\description{
Method to assemble a dashboard and write it to a file
Method to add a component to a page of an i2dashboard object
The idashboard S4 class
Method to add a page to an i2dashboard object
Method to remove a page to an i2dashboard object
}
\section{Slots}{
\describe{
\item{\code{title}}{The dashboards title}
\item{\code{author}}{The author of the dashboard}
\item{\code{interactive}}{If a shiny-based report should be created}
\item{\code{theme}}{The theme of the dashboard}
\item{\code{pages}}{A list of dashboard pages}
}}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/features_by_factors.R
\name{render_features_by_factors}
\alias{render_features_by_factors}
\title{Renders a features by factor violin plot}
\usage{
render_features_by_factors(object, plot_title, x, y)
}
\arguments{
\item{plot_title}{The title of the Component}
\item{x}{A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
\item{y}{A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.(Needs to be categorial. Horizontal violinplots are not possible.)}
}
\value{
A string containing markdown code for the rendered textbox
}
\description{
Renders a features by factor violin plot
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/multiplot.R
\name{render_multiplot}
\alias{render_multiplot}
\title{Renders a Sequence saturation plot}
\usage{
render_multiplot(object, plot_title, x, y, color_by)
}
\arguments{
\item{plot_title}{The title of the Component}
\item{x}{A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
\item{y}{A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
\item{color_by}{A list with the color_by values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
}
\value{
A string containing markdown code for the rendered textbox
}
\description{
Renders a Sequence saturation plot
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/sequence_saturation.R
\name{render_sequence_saturation}
\alias{render_sequence_saturation}
\title{Renders a Sequence saturation plot}
\usage{
render_sequence_saturation(object, plot_title, x, y, color_by)
}
\arguments{
\item{plot_title}{The title of the Component}
\item{x}{A list with the x-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
\item{y}{A list with the y-axis values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
\item{color_by}{A list with the color_by values. If it is a nested list, a dropdown-field will be provided in the interactive mode.}
}
\value{
A string containing markdown code for the rendered textbox
}
\description{
Renders a Sequence saturation plot
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/textbox.R
\name{render_textbox}
\alias{render_textbox}
\title{Renders a textbox with arbitrary content}
\usage{
render_textbox(title, content)
}
\arguments{
\item{title}{The title of the textbox}
\item{content}{The content of the textbox}
}
\value{
A string containing markdown code for the rendered textbox
}
\description{
Renders a textbox with arbitrary content
}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment