Skip to content
Snippets Groups Projects
Commit 5edff386 authored by jens.preussner's avatar jens.preussner :ghost:
Browse files

Merged master

parents c28205d2 2c8a458f
No related branches found
No related tags found
1 merge request!17Additions in vignette
Pipeline #132028 canceled
^.*\.Rproj$
^\.Rproj\.user$
^\.ci$
^\.gitlab-ci.yml
^README\.md
^doc$
^Meta$
^_pkgdown\.yml$
^docs$
^pkgdown$
^cran-comments\.md$
r-assertive.sets
r-assertive.types
r-base
bioconductor-biocstyle
r-htmltools
r-flexdashboard
r-glue
r-knitr
r-magrittr
r-stringi
r-stringr
r-yaml
r-ymlthis
qpdf
zip
\ No newline at end of file
......@@ -4,6 +4,5 @@
.Ruserdata
.DS_store
Thumbs.db
*.html
doc
./*.html
Meta
......@@ -21,29 +21,24 @@ Imports:
assertive.types,
rmarkdown,
stringr,
stringi,
glue,
ymlthis
ymlthis,
methods,
stats,
utils
Suggests:
switchr,
highcharter,
plotly,
crosstalk,
gt,
ggplot2,
DT,
leaflet,
dygraphs,
rbokeh,
visNetwork,
d3heatmap,
metricsgraphics,
BiocStyle
BiocStyle,
xfun,
htmltools
Collate:
'i2dashboard.R'
'AllGenerics.R'
'assemble.R'
'colormap.R'
'components.R'
'colormap.R'
'get_set.R'
'pages.R'
'reexports.R'
......
......@@ -26,11 +26,4 @@ export(source)
export(theme)
export(title)
exportClasses(i2dashboard)
exportMethods(add_colormap)
exportMethods(add_component)
exportMethods(add_link)
exportMethods(add_page)
exportMethods(add_to_sidebar)
exportMethods(assemble)
exportMethods(remove_page)
importFrom(magrittr,"%>%")
#' @include i2dashboard.R
#' @export
#' @rdname assemble
setGeneric("assemble", function(dashboard, ...) standardGeneric("assemble"))
#' @export
#' @rdname i2dashboard-pages
setGeneric("add_page", function(dashboard, ...) standardGeneric("add_page"))
#' @export
setGeneric("remove_page", function(dashboard, ...) standardGeneric("remove_page"))
#' @rdname i2dashboard-pages
setGeneric("remove_page", function(dashboard, page) standardGeneric("remove_page"))
#' @export
#' @rdname i2dashboard-content
setGeneric("add_component", function(dashboard, component, ...) standardGeneric("add_component"))
#' @export
#' @rdname i2dashboard-content
setGeneric("add_to_sidebar", function(dashboard, component, ...) standardGeneric("add_to_sidebar"))
#' @export
#' @rdname i2dashboard-content
setGeneric("add_colormap", function(dashboard, ...) standardGeneric("add_colormap"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("interactivity", function(dashboard) standardGeneric("interactivity"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("interactivity<-", function(dashboard, value) standardGeneric("interactivity<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("title", function(dashboard) standardGeneric("title"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("title<-", function(dashboard, value) standardGeneric("title<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("author", function(dashboard) standardGeneric("author"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("author<-", function(dashboard, value) standardGeneric("author<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("theme", function(dashboard) standardGeneric("theme"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("theme<-", function(dashboard, value) standardGeneric("theme<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("datadir", function(dashboard) standardGeneric("datadir"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("datadir<-", function(dashboard, value) standardGeneric("datadir<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("social_links", function(dashboard) standardGeneric("social_links"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("social_links<-", function(dashboard, value) standardGeneric("social_links<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("embed_source<-", function(dashboard, value) standardGeneric("embed_source<-"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("source", function(dashboard) standardGeneric("source"))
#' @export
#' @rdname i2dashboard-methods
setGeneric("source<-", function(dashboard, value) standardGeneric("source<-"))
#' @export
#' @rdname i2dashboard-content
setGeneric("add_link", function(dashboard, ...) standardGeneric("add_link"))
\ No newline at end of file
#' Method to assemble a dashboard to a Rmd file.
#' Generate an RMarkdown file from an i2dashboard object.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param pages A string or vector with the names of pages, which should be assembled to a dashboard.
#' @param file The output filename (recommend that the suffix should be '.Rmd'). This file will be saved in the working directory.
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param pages A string or vector with the names of pages, which should be assembled into the resulting Rmd file.
#' @param file The filename of the resulting Rmd file (recommend that the suffix should be '.Rmd').
#' @param exclude A string or vector with the names of pages, which should be excluded from dashboard assembly.
#' @param render A logical indicating whether the assembled dashboard should immediately be rendered with \code{rmarkdown::render} or run with \code{rmarkdown::run}.
#' @param ... Additional arguments passed on to \code{rmarkdown::render}.
#'
#' @rdname i2dashboard-methods
#' @export
#' @return Invisibly returns the dashboard.
#'
#' @rdname assemble
setMethod("assemble", "i2dashboard", function(dashboard, pages = names(dashboard@pages), file = dashboard@file, exclude = NULL, render = FALSE, ...) {
. = NULL # workaround for R CMD check note: no visible binding for global variable '.'
tmp_document <- tempfile()
# Handle colormap
......@@ -49,7 +51,7 @@ setMethod("assemble", "i2dashboard", function(dashboard, pages = names(dashboard
# Handle exclusion of pages
if(!is.null(exclude)) {
pages <- pages[-na.omit(match(exclude, pages))]
pages <- pages[-stats::na.omit(match(exclude, pages))]
}
# Handle global sidebar if it has content
......
#' Add a color mapping to the dashboards colormaps.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @include components.R
NULL
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param map A character vector containing colors and possible the levels they map to (as names).
#' @param name A name for the color mapping.
#'
#' @rdname i2dashboard-methods
#' @export
#' @rdname i2dashboard-content
setMethod("add_colormap", "i2dashboard", function(dashboard, map, name) {
dashboard@colormaps[[make.names(name)]] <- map
return(dashboard)
......
#' Method to add a component to a page of an i2dashboard.
#' Add content to an i2dashboard object.
#'
#' Components can be created by evaluating a function, or by including an object, a text or image file.
#' Content can be added to the dashboards pages, the sidebar or the navigation bar.
#'
#' @section Adding content by evaluating a function:
#' If the argument \code{component} is a function, the function will be called and its return value is used as content.
#' The options to add content in detail:
#' \itemize{
#' \item \strong{\code{add_component}} adds content to a page of the dashboard by evaluating a function, or by including an object, a text or image file.
#' \item \strong{\code{add_to_sidebar}} adds content to the dashboards global sidebar or to a pages local sidebar.
#' \item \strong{\code{add_link}} adds a link to the navigation bar.
#' \item \strong{\code{add_colormap}} adds a global color mapping to the dashboards colormaps.
#' }
#'
#' @section Adding plain text as content:
#' If the argument \code{component} is a character and ends with \code{.md} or \code{.txt}, the function will try to open a file and use its content.
#' The mechanism to add different types of content to a dashboards page or sidebar depends on the class of the object passed to the function \code{add_component} or \code{add_to_sidebar}:
#'
#' @section Adding images as content:
#' If the argument \code{component} is a character and its end matches \code{\\.[png|jpg|jpeg|gif]}, the function will try to include an image as the content.
#' \itemize{
#' \item A function will be evaluated and its return value is used as content.
#' \item A string that ends with \code{.md} or \code{.txt} will be used to open a file and use its content.
#' \item A string that ends with \code{\\.[png|jpg|jpeg|gif]} will be used to include an image as content.
#' \item An R object (e.g. a htmlwidget) will be included if a suitable signature method is implemented.
#' }
#'
#' @section Adding a R object as content:
#' If the argument \code{component} is a supported R object (e.g. a htmlwidget), the function will include its representation as content.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param page The name of the page to add the component to.
#' @param component A R object, function, or character.
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param page The name of the page to add the component or sidebar to.
#' @param component An R object, function, or string.
#' @param copy Whether or not to copy images to \code{dashboard@datadir}.
#' @param ... Additional parameters passed to the components render function.
#'
#' @rdname add-component
#' @export
#' @return The (modified) \linkS4class{i2dashboard} object.
#'
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "character"),
function(dashboard, component, page = "default", copy = FALSE, ...) {
function(dashboard, page = "default", component, copy = FALSE, ...) {
# Logic to guess intended usage
mode <- NULL
if(stringr::str_detect(tolower(component), "\\.[md|txt]+$")) {
......@@ -58,8 +64,9 @@ setMethod("add_component",
return(.add_component(dashboard, name, component))
})
#' @rdname i2dashboard-content
setMethod("add_component", signature(dashboard = "i2dashboard", component = "function"),
function(dashboard, component, page = "default", ...) {
function(dashboard, page = "default", component, ...) {
# validate "page" input
name <- .create_page_name(page)
if (!(name %in% names(dashboard@pages))) {
......@@ -76,6 +83,81 @@ setMethod("add_component", signature(dashboard = "i2dashboard", component = "fun
return(.add_component(dashboard, name, content))
})
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "gg"),
definition = function(dashboard, component, page = "default", ...) {
add_vis_object(dashboard, component, "ggplot2", page, ...) })
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "gt_tbl"),
definition = function(dashboard, component, page = "default", ...) {
add_vis_object(dashboard, component,"gt", page, ...) })
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "knitr_kable"),
definition = function(dashboard, component, page = "default", ...) {
add_vis_object(dashboard, component, "kableExtra", page, ...) })
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "Heatmap"),
definition = function(dashboard, component, page = "default", ...) {
add_vis_object(dashboard, component, "ComplexHeatmap", page, ...) })
#' @rdname i2dashboard-content
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "ANY"),
definition = function(dashboard, component, page = "default", ...) {
# HTMLWIDGETS
if(inherits(component, "htmlwidget")) {
package <- methods::packageSlot(component)
if(is.null(package)) {
warning("No component added, since the package name of the HTML widget could not be determined.")
return(dashboard)
}
return(add_vis_object(dashboard, component, package, page, ...))
}
# OTHER
warning("The component did not inherit from any of the currently supported classes ('htmlwidget').")
return(dashboard)
})
#' @param href The target of the link.
#' @param title The link title.
#' @param icon An optional link icon (see https://rmarkdown.rstudio.com/flexdashboard/using.html#icon-sets)
#' @param align Optional argument that can be “left” or “right” (defaults = “right”) defining the alignment of the links in the navigation bar
#' @param target An optional target (e.g. "_blank")
#'
#' @rdname i2dashboard-content
setMethod("add_link", "i2dashboard", function(dashboard, href, title = NULL, icon = NULL, align = c("right","left"), target = NULL) {
align <- match.arg(align)
if(is.null(title) & is.null(icon)) {
warning("Both, title and icon, cannot be NULL when adding a link.")
return(dashboard)
}
# Workaround for NULL values
if(is.null(icon)) {
icon <- ""
}
if(is.null(title)) {
title = ""
}
if(is.null(target)) {
target = ""
}
dashboard@navbar <- append(dashboard@navbar, list(list("href" = href, "title" = title, "icon" = icon, "align" = align, "target" = target)))
dashboard
})
#' Method to download embed files into an Rmd-file
#'
#' @param x Data, which will be written to the embedded file.
......@@ -84,7 +166,7 @@ setMethod("add_component", signature(dashboard = "i2dashboard", component = "fun
#' @export
embed_var <- function(x, ...) {
f = tempfile(fileext = '.csv')
write.csv(x, f)
utils::write.csv(x, f)
xfun::embed_file(f, text = 'Download data', ...)
}
......@@ -129,7 +211,7 @@ render_image <- function(image, image_alt_text = NULL, title = NULL, raw = FALSE
#' Helper function to add components to the dashboard
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param page The name of the page to add the component to.
#' @param component A string or list.
#'
......
#' Get/set the interactivity of the i2dashboard.
#' Accessor methods for slots of an \linkS4class{i2dashboard} object.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#' Getter and Setter methods can be used to directly manipulate properties (slots) of an \linkS4class{i2dashboard} object. See \linkS4class{i2dashboard} for details.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param value The value of the desired property. See \linkS4class{i2dashboard} for details.
#'
#' @rdname i2dashboard-methods
setMethod("interactivity", "i2dashboard", function(dashboard) dashboard@interactive)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("interactivity<-", "i2dashboard", function(dashboard, value) {
dashboard@interactive <- value
dashboard
})
#' Get/set the title of the i2dashboard.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("title", "i2dashboard", function(dashboard) dashboard@title)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("title<-", "i2dashboard", function(dashboard, value) {
dashboard@title <- value
dashboard
})
#' Get/set the author of the i2dashboard.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("author", "i2dashboard", function(dashboard) dashboard@author)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("author<-", "i2dashboard", function(dashboard, value) {
dashboard@author <- value
dashboard
})
#' Get/set the theme of the i2dashboard.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("theme", "i2dashboard", function(dashboard) dashboard@theme)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("theme<-", "i2dashboard", function(dashboard, value) {
dashboard@theme <- value
dashboard
})
#' Get/set the datadir of the i2dashboard.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("datadir", "i2dashboard", function(dashboard) dashboard@datadir)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("datadir<-", "i2dashboard", function(dashboard, value) {
dashboard@datadir <- value
dashboard
})
#' Get/set the links to be shown for sharing on social media. Any of the following services are allowed: “facebook”, “twitter”, “google-plus”, “linkedin”, and “pinterest”. You can also specify “menu” to provide a generic sharing drop-down menu that includes all of the services.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("social_links", "i2dashboard", function(dashboard) dashboard@social_links)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("social_links<-", "i2dashboard", function(dashboard, value) {
i <- intersect(tolower(value), c("facebook", "twitter", "google-plus", "linkedin", "pinterest", "menu"))
if (length(i) > 0) {
......@@ -97,24 +62,16 @@ setMethod("social_links<-", "i2dashboard", function(dashboard, value) {
dashboard
})
#' Get/set the embedding of the source code of the i2dashboard. Can either be a URL pointing to where the source code can be found online or whether or not to embed the source code into the document.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param value The value of the desired property. A URL pointing to where the source code can be found online.
#'
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("source", "i2dashboard", function(dashboard) dashboard@source)
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("source<-", "i2dashboard", function(dashboard, value) {
dashboard@source <- tolower(as.character(value))
dashboard
})
#' @name i2dashboard-class
#' @rdname i2dashboard-class
#' @rdname i2dashboard-methods
setMethod("embed_source<-", "i2dashboard", function(dashboard, value) {
if(value) {
dashboard@source <- "embed"
......@@ -124,36 +81,3 @@ setMethod("embed_source<-", "i2dashboard", function(dashboard, value) {
dashboard
})
#' Add a link to the navigation bar.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param href The target of the link.
#' @param title The link title.
#' @param icon An optional link icon (see https://rmarkdown.rstudio.com/flexdashboard/using.html#icon-sets)
#' @param align Optional argument that can be “left” or “right” (defaults = “right”) defining the alignment of the links in the navigation bar
#' @param target An optional target (e.g. "_blank")
#'
#' @rdname i2dashboard-methods
#' @export
setMethod("add_link", "i2dashboard", function(dashboard, href, title = NULL, icon = NULL, align = c("right","left"), target = NULL) {
align <- match.arg(align)
if(is.null(title) & is.null(icon)) {
warning("Both, title and icon, cannot be NULL when adding a link.")
return(dashboard)
}
# Workaround for NULL values
if(is.null(icon)) {
icon <- ""
}
if(is.null(title)) {
title = ""
}
if(is.null(target)) {
target = ""
}
dashboard@navbar <- append(dashboard@navbar, list(list("href" = href, "title" = title, "icon" = icon, "align" = align, "target" = target)))
dashboard
})
#' The idashboard S4 class.
#' i2dash: A package for programmatic creation of interactive, web-based dashboards
#'
#' i2dash relies on the widely used R packages flexdashboard, knitr and rmarkdown. i2dash introduces a new class from R's S4 object system named \linkS4class{i2dashboard}, which by design provides the main functionality of the package. Besides global properties such as the dashboard title, author and theme, an instance of the \linkS4class{i2dashboard} class also stores individual dashboard pages and the navigation menu, as well as all components that make up the content of individual pages.
#'
#' @section Citation:
#'
#' When using the package in your work, please cite: tba.
#'
#' @docType package
#' @name i2dash
NULL
#' The \linkS4class{i2dashboard} S4 class.
#'
#' The \linkS4class{i2dashboard} S4 class provides main functionality of the package. Besides global properties such as the dashboard title, author and theme, an instance of the i2dashboard class also stores individual dashboard pages and the navigation menu, as well as all components that make up the content of individual pages. A new instance can be created using the \code{i2dashboard} function.
#'
#' @param object An object of class \linkS4class{i2dashboard}.
#' @param .Object An object of class \linkS4class{i2dashboard}.
#' @param ... Named slots of the \linkS4class{i2dashboard} object.
#'
#' @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 theme The theme of the dashboard (see the \href{https://rmarkdown.rstudio.com/flexdashboard/using.html#appearance}{documentation of flexdashboard} for available themes)
#' @slot datadir Path to the directory, where report data is stored.
#' @slot file The output filename (recommend that the suffix should be '.Rmd').
#' @slot pages A list of dashboard pages
......@@ -11,12 +29,11 @@
#' @slot colormaps A named list with color mappings.
#' @slot source Either a logical value describing whether the source code should be embeded through an item in the navigation bar or a link to a URL where the source code can be found online.
#' @slot social A vector with any number of the following services: “facebook”, “twitter”, “google-plus”, “linkedin”, and “pinterest”. You can also specify “menu” to provide a generic sharing drop-down menu that includes all of the services.
#' @slot navbar A list of links in the navigation bar (see https://rmarkdown.rstudio.com/flexdashboard/using.html#navigation_bar).
#' @slot navbar A list of links in the navigation bar (see the \href{https://rmarkdown.rstudio.com/flexdashboard/using.html#navigation_bar}{documentation of flexdashboard}).
#'
#' @return An i2dashboard object.
#' @return An \linkS4class{i2dashboard} object.
#'
#' @name idashboard-class
#' @rdname idashboard-class
#' @rdname i2dashboard-class
#' @exportClass i2dashboard
setClass("i2dashboard",
slots = c(
......@@ -44,13 +61,11 @@ setClass("i2dashboard",
)
)
#' Constructor method of the i2dashboard class.
#'
#' @name idashboard-class
#' @rdname idashboard-class
#' @rdname i2dashboard-class
setMethod("initialize", "i2dashboard", function(.Object, ...) {
# Do prototyping
.Object <- callNextMethod()
.Object <- methods::callNextMethod()
# Create nice filename from title
if(length(.Object@file) == 0 & length(.Object@title) > 0) {
......@@ -64,46 +79,23 @@ setMethod("initialize", "i2dashboard", function(.Object, ...) {
return(.Object)
})
#' Show method of the i2dashboard class.
#' Show method of the \linkS4class{i2dashboard} class.
#'
#' @param object An \linkS4class{i2dashboard} class object.
#'
#' @name idashboard-class
#' @rdname idashboard-class
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:\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)))
#' @rdname i2dashboard-class
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:\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.")
}
})
#' Create a new i2dashboard object.
#'
#' @name idashboard-class
#' @rdname idashboard-class
#' @rdname i2dashboard-class
#' @export
i2dashboard <- function(...) new("i2dashboard", ...)
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
### 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)
i2dashboard <- function(...) methods::new("i2dashboard", ...)
#' Sanitize component names
#'
#' This function takes a character string, replaces spaces by underscores and runs make.names.
#' Methods to add and remove pages of an i2dashboard.
#'
#' @param x A character string.
#' \code{add_page} creates a page and adds it to the \linkS4class{i2dashboard} object.
#' \code{remove_page} removes a page from the \linkS4class{i2dashboard} object.
#'
#' @return A sanitized string.
.create_page_name <- function(x) {
x %>% tolower %>% gsub(x = ., pattern = " ", replacement = "_") %>% make.names %>% return
}
#' Method to add a page to an i2dashboard
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param page The name of the page to be added.
#' @param dashboard A \linkS4class{i2dashboard}.
#' @param page The name of the page to be added or removed.
#' @param title The title of the page to be added.
#' @param layout The page layout (see below).
#' @param menu The name of the menu, under which the page should appear.
#' @param sidebar A Markdown string. Preferably, use the function add_to_sidebar.
#' @param ... Additional arguments.
#'
#' @rdname i2dashboard-methods
#' @export
#' @return The \linkS4class{i2dashboard} object.
#'
#' @rdname i2dashboard-pages
setMethod("add_page", "i2dashboard", function(dashboard, page, title, layout = "default", menu = NULL, sidebar = NULL, ...) {
name <- .create_page_name(page)
......@@ -44,15 +39,21 @@ setMethod("add_page", "i2dashboard", function(dashboard, page, title, layout = "
return(dashboard)
})
#' Method to remove a page to an i2dashboard
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param page The name of the page to be removed.
#'
#' @rdname i2dashboard-methods
#' @export
#' @rdname i2dashboard-pages
setMethod("remove_page", "i2dashboard", function(dashboard, page) {
name <- .create_page_name(page)
dashboard@pages[[name]] <- NULL
return(dashboard)
})
#' Sanitize component names
#'
#' This function takes a character string, replaces spaces by underscores and runs make.names.
#'
#' @param x A character string.
#'
#' @return A sanitized string.
.create_page_name <- function(x) {
. = NULL # workaround for R CMD check note: no visible binding for global variable '.'
x %>% tolower %>% gsub(x = ., pattern = " ", replacement = "_") %>% make.names %>% return
}
\ No newline at end of file
#' Add content to a sidebar
#'
#' This method allows to add content either to the global sidebar, or to a sidebar of an existing page.
#'
#' @param dashboard A \linkS4class{i2dash::i2dashboard}.
#' @param content The name of a function of a path to a file.
#' @param page The name of the page to which add the sidebar.
#' @include components.R
#' @param global Whether or not to add the content to the global sidebar.
#' @param copy Whether or not to copy images to \code{dashboard@datadir}.
#' @param ... Additional parameters passed to the components render function.
#'
#' @rdname i2dashboard-methods
#' @export
setMethod("add_to_sidebar", "i2dashboard", function(dashboard, content, page = "default", global = FALSE, copy = FALSE, ...) {
#' @rdname i2dashboard-content
setMethod("add_to_sidebar", "i2dashboard", function(dashboard, component, page = "default", global = FALSE, copy = FALSE, ...) {
# Logic to guess intended usage
mode <- "function"
if(stringr::str_detect(tolower(content), "\\.[md|txt]+$")) {
if(stringr::str_detect(tolower(component), "\\.[md|txt]+$")) {
mode <- "text"
}
if(stringr::str_detect(tolower(content), "\\.[png|jpg|jpeg|gif]+$")) {
if(stringr::str_detect(tolower(component), "\\.[png|jpg|jpeg|gif]+$")) {
if(copy) {
location <- file.path(dashboard@datadir, basename(content))
file.copy(content, location)
content <- location
location <- file.path(dashboard@datadir, basename(component))
file.copy(component, location)
component <- location
}
mode <- "image"
}
if(mode == "function") {
pn <- strsplit(content, "::")[[1]]
pn <- strsplit(component, "::")[[1]]
eval_function <- if(length(pn) == 1) {
get(pn[[1]], envir = asNamespace("i2dash"), mode = "function")
} else {
......@@ -35,26 +26,26 @@ setMethod("add_to_sidebar", "i2dashboard", function(dashboard, content, page = "
}
}
content <- switch(mode,
component <- switch(mode,
"function" = do.call(eval_function, args = list(dashboard, ...)),
"text" = do.call("render_text", args = list(content, raw = TRUE)),
"image" = do.call("render_image", args = list(content, raw = TRUE)))
"text" = do.call("render_text", args = list(component, raw = TRUE)),
"image" = do.call("render_image", args = list(component, raw = TRUE)))
if(is.list(content)) {
if(is.list(component)) {
warning(sprintf("Component function returned unsupported content for sidebar."))
return(dashboard)
}
if(global) {
dashboard@sidebar <- paste0(dashboard@sidebar, content)
dashboard@sidebar <- paste0(dashboard@sidebar, component)
} else {
name <- .create_page_name(page)
if (!(name %in% names(dashboard@pages))) {
warning(sprintf("i2dashboard dashboard does not contain a page named '%s'", name))
return(dashboard)
}
dashboard@pages[[name]]$sidebar <- paste0(dashboard@pages[[name]]$sidebar, content)
dashboard@pages[[name]]$sidebar <- paste0(dashboard@pages[[name]]$sidebar, component)
}
return(dashboard)
})
#' @include components.R
NULL
#' General method to add an object as component to a page of an i2dashboard.
#'
#' @param dashboard The \linkS4class{i2dash::i2dashboard}.
#' @param dashboard The \linkS4class{i2dashboard}.
#' @param object The R visualization object to be addedd.
#' @param package The name of the R package that defines the class(object).
#' @param page The name of the page to add the object to.
#' @param title An optional component title.
add_vis_object <- function(dashboard, object, package, page = "default", title = NULL, ...){
sanitised_page <- i2dash:::.create_page_name(page)
add_vis_object <- function(dashboard, object, package, page = "default", title = NULL){
sanitised_page <- .create_page_name(page)
if (!(sanitised_page %in% names(dashboard@pages))) {
warning(sprintf("i2dashboard does not contain a page named '%s'", sanitised_page))
return(dashboard)
......@@ -29,7 +32,7 @@ add_vis_object <- function(dashboard, object, package, page = "default", title =
delim = c("<%", "%>"),
title = title,
package = package,
class = is(object),
class = methods::is(object),
component_id = component_id,
timestamp = timestamp)
......@@ -38,46 +41,3 @@ add_vis_object <- function(dashboard, object, package, page = "default", title =
return(dashboard)
}
#
# Methods to add common visualization objects
#
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "gg"),
definition = function(dashboard, component, page = "default", title = NULL, ...) {
add_vis_object(dashboard, component, "ggplot2", page, title, ...) })
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "gt_tbl"),
definition = function(dashboard, component, page = "default", title = NULL, ...) {
add_vis_object(dashboard, component,"gt", page, title, ...) })
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "knitr_kable"),
definition = function(dashboard, component, page = "default", title = NULL, ...) {
add_vis_object(dashboard, component, "kableExtra", page, title, ...) })
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "Heatmap"),
definition = function(dashboard, component, page = "default", title = NULL, ...) {
add_vis_object(dashboard, component, "ComplexHeatmap", page, title, ...) })
setMethod("add_component",
signature = signature(dashboard = "i2dashboard", component = "ANY"),
definition = function(dashboard, component, page = "default", title = NULL, ...) {
# HTMLWIDGETS
if(inherits(component, "htmlwidget")) {
package <- packageSlot(component)
if(is.null(package)) {
warning("No component added, since the package name of the HTML widget could not be determined.")
return(dashboard)
}
return(add_vis_object(dashboard, component, package, page, title, ...))
}
# OTHER
warning("The component did not inherit from any of the currently supported classes ('htmlwidget').")
return(dashboard)
})
# **i2dash**: - **I**nteractive & **i**terative **dash**boards in R <img src="man/figures/i2dash_logo.png" align="right" width="150px"/>
# Interactive & iterative dashboards in R
## Abstract <img src="vignettes/images/i2dash_logo.png" align="right" width="150px" />
## Abstract
Scientific communication and data visualization are important aspects to illustrate complex concepts and results from data analyses. The R package i2dash provides functionality to create customized, web-based dashboards for data presentation, exploration and sharing. i2dash integrates easily into existing data analysis pipelines and can organize scientific findings thematically across different pages and layouts.
Scientific communication and data visualization are important aspects to illustrate complex concepts and results from data analyses. The R package **i2dash** provides functionality to create customized, web-based dashboards for data presentation, exploration and sharing. **i2dash** integrates easily into existing data analysis pipelines and can organize scientific findings thematically across different pages and layouts.
### Main features
- Easy integration into existing analysis pipelines in R
- Support for multiple components, such as htmlwidgets, tabular data, text, images etc.
- Easy integration into existing analysis pipelines in R for programmatic dashboard creation
- Provides a selection of predefined layouts to arrange content
- Support for multiple components, such as htmlwidgets, tables, text, images etc.
- Creation of web-based, sharable, static or interactive dashboards
- Enables a flexible and iterative cycle of dashboard development
![](man/figures/i2dash_image.jpg)
![](vignettes/images/i2dash_intro.png)
*(A) dashboard is initialized at the beginning of a data analysis pipeline. During the pipeline run, new content, results, or data visualizations are iteratively added to the dashboard’s pages. The final dashboard is rendered into a static or interactive document. (B) Pages added to the dashboard can be arranged in a flexible manner from a selection of predefined layouts. (C) Examples of programmatically created dashboards. (D) The i2dash docker container, providing all dependencies for interactive, shiny based apps, can be used to easily deploy individual data interpretations on a cloud infrastructure, such as Kubernetes, as a micro service.*
*A customized dashboards can be integrated into an existing data analysis pipelines in R (left). After initialization, pages containing components with customized content can be added step-by-step to the dashboard at any stage of the data analysis. The final dashboard is assembled into an R markdown file, and shared together with RDS data files for further use within RStudio, or can also be deployed on a R Shiny Server or as stand-alone HTML file.*
## Installation
## Installation:
The package can be installed with:
```r
install.packages("BiocManager")
BiocManager::install("i2dash")
```
install.packages("i2dash")
```
## Where to start
......@@ -29,13 +30,15 @@ BiocManager::install("i2dash")
## Extension
It is possible to extend the core functionality of **i2dash** with tempates for components and pre-defined pages. This enables to provide an enhanced user interactivity e.g. dynamic change of plot settings. Further, extensions allow an easier integration of complex calculations and data manipulation, hidden behind functions.
It is possible to extend the core functionality of **i2dash** with templates for components and pre-defined pages. This enables to provide an enhanced user interactivity e.g. dynamic change of plot settings. Further, extensions allow an easier integration of complex calculations and data manipulation, hidden behind functions.
- [**i2dash.scrnaseq**](https://gitlab.gwdg.de/loosolab/software/i2dash.scrnaseq) enables an enhanced user interactivity and contains simple but effective tools for the creation of an i2dashboard with focus on single-cell RNA-sequencing data visualization and exploration.
## How to cite
Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum.
If you use **i2dash** or **i2dash.scrnaseq** in your work, please cite:
Ustjanzew A., Preussner J., Bentsen M., Kuenne C., and Looso M. i2dash: creation of flexible, interactive and web-based dashboards from data analysis pipelines. *tba* (2020)
## License
......
## Test environments
- R-hub windows-x86_64-devel (r-devel)
- R-hub ubuntu-gcc-release (r-release)
- R-hub fedora-clang-devel (r-devel)
## R CMD check results
> On windows-x86_64-devel (r-devel), ubuntu-gcc-release (r-release), fedora-clang-devel (r-devel)
checking CRAN incoming feasibility ... NOTE
Maintainer: 'Arsenij Ustjanzew <arsenij.ustjanzew@mpi-bn.mpg.de>'
New submission
License components with restrictions and base license permitting such:
MIT + file LICENSE
File 'LICENSE':
MIT License
Copyright (c) 2019 Mario Looso, Jens Preussner and Arsenij Ustjanzew
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
> On windows-x86_64-devel (r-devel), ubuntu-gcc-release (r-release), fedora-clang-devel (r-devel)
checking installed package size ... NOTE
installed size is 5.6Mb
sub-directories of 1Mb or more:
doc 5.3Mb
0 errors √ | 0 warnings √ | 2 notes x
* This is a new release.
<!-- Generated by pkgdown: do not edit by hand -->
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Page not found (404) • i2dash</title>
<!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="favicon-16x16.png">
<link rel="icon" type="image/png" sizes="32x32" href="favicon-32x32.png">
<link rel="apple-touch-icon" type="image/png" sizes="180x180" href="apple-touch-icon.png" />
<link rel="apple-touch-icon" type="image/png" sizes="120x120" href="apple-touch-icon-120x120.png" />
<link rel="apple-touch-icon" type="image/png" sizes="76x76" href="apple-touch-icon-76x76.png" />
<link rel="apple-touch-icon" type="image/png" sizes="60x60" href="apple-touch-icon-60x60.png" />
<!-- jquery -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script>
<!-- Bootstrap -->
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous" />
<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script>
<!-- bootstrap-toc -->
<link rel="stylesheet" href="bootstrap-toc.css">
<script src="bootstrap-toc.js"></script>
<!-- Font Awesome icons -->
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous" />
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous" />
<!-- clipboard.js -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script>
<!-- headroom.js -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script>
<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script>
<!-- pkgdown -->
<link href="pkgdown.css" rel="stylesheet">
<script src="pkgdown.js"></script>
<meta property="og:title" content="Page not found (404)" />
<!-- mathjax -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script>
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script>
<!--[if lt IE 9]>
<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
<![endif]-->
</head>
<body data-spy="scroll" data-target="#toc">
<div class="container template-title-body">
<header>
<div class="navbar navbar-default navbar-fixed-top" role="navigation">
<div class="container">
<div class="navbar-header">
<button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false">
<span class="sr-only">Toggle navigation</span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">i2dash</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.2</span>
</span>
</div>
<div id="navbar" class="navbar-collapse collapse">
<ul class="nav navbar-nav">
<li>
<a href="index.html">
<span class="fas fa fas fa-home fa-lg"></span>
</a>
</li>
<li>
<a href="reference/index.html">Reference</a>
</li>
<li class="dropdown">
<a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false">
Articles
<span class="caret"></span>
</a>
<ul class="dropdown-menu" role="menu">
<li>
<a href="articles/i2dash-intro.html">Creating iterative and interactive dashboards with i2dash</a>
</li>
</ul>
</li>
</ul>
<ul class="nav navbar-nav navbar-right">
</ul>
</div><!--/.nav-collapse -->
</div><!--/.container -->
</div><!--/.navbar -->
</header>
<div class="row">
<div class="contents col-md-9">
<div class="page-header">
<h1>Page not found (404)</h1>
</div>
Content not found. Please use links in the navbar.
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">
<h2 data-toc-skip>Contents</h2>
</nav>
</div>
</div>
<footer>
<div class="copyright">
<p>Developed by Arsenij Ustjanzew, Jens Preussner, Mario Looso.</p>
</div>
<div class="pkgdown">
<p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.</p>
</div>
</footer>
</div>
</body>
</html>
<!-- Generated by pkgdown: do not edit by hand -->
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>License • i2dash</title>
<!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="favicon-16x16.png">
<link rel="icon" type="image/png" sizes="32x32" href="favicon-32x32.png">
<link rel="apple-touch-icon" type="image/png" sizes="180x180" href="apple-touch-icon.png" />
<link rel="apple-touch-icon" type="image/png" sizes="120x120" href="apple-touch-icon-120x120.png" />
<link rel="apple-touch-icon" type="image/png" sizes="76x76" href="apple-touch-icon-76x76.png" />
<link rel="apple-touch-icon" type="image/png" sizes="60x60" href="apple-touch-icon-60x60.png" />
<!-- jquery -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script>
<!-- Bootstrap -->
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous" />
<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script>
<!-- bootstrap-toc -->
<link rel="stylesheet" href="bootstrap-toc.css">
<script src="bootstrap-toc.js"></script>
<!-- Font Awesome icons -->
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous" />
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous" />
<!-- clipboard.js -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script>
<!-- headroom.js -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script>
<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script>
<!-- pkgdown -->
<link href="pkgdown.css" rel="stylesheet">
<script src="pkgdown.js"></script>
<meta property="og:title" content="License" />
<!-- mathjax -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script>
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script>
<!--[if lt IE 9]>
<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
<![endif]-->
</head>
<body data-spy="scroll" data-target="#toc">
<div class="container template-title-body">
<header>
<div class="navbar navbar-default navbar-fixed-top" role="navigation">
<div class="container">
<div class="navbar-header">
<button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false">
<span class="sr-only">Toggle navigation</span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">i2dash</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.2</span>
</span>
</div>
<div id="navbar" class="navbar-collapse collapse">
<ul class="nav navbar-nav">
<li>
<a href="index.html">
<span class="fas fa fas fa-home fa-lg"></span>
</a>
</li>
<li>
<a href="reference/index.html">Reference</a>
</li>
<li class="dropdown">
<a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false">
Articles
<span class="caret"></span>
</a>
<ul class="dropdown-menu" role="menu">
<li>
<a href="articles/i2dash-intro.html">Creating iterative and interactive dashboards with i2dash</a>
</li>
</ul>
</li>
</ul>
<ul class="nav navbar-nav navbar-right">
</ul>
</div><!--/.nav-collapse -->
</div><!--/.container -->
</div><!--/.navbar -->
</header>
<div class="row">
<div class="contents col-md-9">
<div class="page-header">
<h1>License</h1>
</div>
<pre>MIT License
Copyright (c) 2019 Mario Looso, Jens Preussner and Arsenij Ustjanzew
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">
<h2 data-toc-skip>Contents</h2>
</nav>
</div>
</div>
<footer>
<div class="copyright">
<p>Developed by Arsenij Ustjanzew, Jens Preussner, Mario Looso.</p>
</div>
<div class="pkgdown">
<p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.</p>
</div>
</footer>
</div>
</body>
</html>
docs/android-icon-144x144.png

13.1 KiB

docs/android-icon-192x192.png

16 KiB

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