Skip to content

Commit

Permalink
Fix@missing imports (#151)
Browse files Browse the repository at this point in the history
* added missing imports

* Increment version number to 0.2.20.9000

* additional minor fixes
  • Loading branch information
aviezerl authored Dec 20, 2023
1 parent b0084a2 commit a6d3b12
Show file tree
Hide file tree
Showing 23 changed files with 464 additions and 54 deletions.
23 changes: 15 additions & 8 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: MCView
Title: A Shiny App for Metacell Analysis
Version: 0.2.23
Version: 0.2.23.9000
Authors@R:
person(given = "Aviezer",
family = "Lifshitz",
Expand All @@ -20,11 +20,11 @@ BugReports: https://github.com/tanaylab/MCView/issues
Depends:
R (>= 3.5)
Imports:
anndata,
anndata,
chameleon,
cli,
colourpicker,
circlize,
circlize,
cowplot,
cachem,
dplyr,
Expand All @@ -43,8 +43,9 @@ Imports:
htmltools,
markdown (>= 1.3.0),
matrixStats,
methods,
pkgload,
plotly (>= 4.9.3),
plotly (>= 4.9.3),
promises,
purrr,
qs,
Expand All @@ -58,7 +59,7 @@ Imports:
shinyjqui,
shinycssloaders,
shinydashboard,
shinydashboardPlus (>= 2.0.0),
shinydashboardPlus (>= 2.0.0),
shinyWidgets (>= 0.7.0),
shinybusy,
tglkmeans,
Expand All @@ -71,17 +72,23 @@ Imports:
zip,
Matrix,
ggtext (>= 0.1.0),
waiter
waiter,
stats,
utils,
umap,
graphics
Suggests:
knitr,
R.utils,
processx,
testthat,
withr
withr,
metacell
VignetteBuilder:
knitr
Remotes:
tanaylab/tgutil
tanaylab/tgutil,
tanaylab/metacell
Encoding: UTF-8
LazyData: true
RoxygenNote: 7.2.3
33 changes: 33 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,17 @@ importFrom(golem,add_resource_path)
importFrom(golem,bundle_resources)
importFrom(golem,favicon)
importFrom(golem,with_golem_options)
importFrom(grDevices,col2rgb)
importFrom(grDevices,rgb)
importFrom(graphics,axis)
importFrom(graphics,layout)
importFrom(graphics,par)
importFrom(graphics,plot.new)
importFrom(graphics,plot.window)
importFrom(graphics,polygon)
importFrom(graphics,rect)
importFrom(graphics,segments)
importFrom(graphics,text)
importFrom(htmltools,HTML)
importFrom(htmltools,tagAppendAttributes)
importFrom(htmltools,tagList)
Expand All @@ -49,3 +60,25 @@ importFrom(shiny,NS)
importFrom(shiny,column)
importFrom(shiny,shinyApp)
importFrom(shiny,tagList)
importFrom(stats,approx)
importFrom(stats,as.dendrogram)
importFrom(stats,as.dist)
importFrom(stats,as.hclust)
importFrom(stats,chisq.test)
importFrom(stats,cor)
importFrom(stats,df)
importFrom(stats,ecdf)
importFrom(stats,hclust)
importFrom(stats,loess)
importFrom(stats,median)
importFrom(stats,plogis)
importFrom(stats,quantile)
importFrom(stats,reorder)
importFrom(stats,runif)
importFrom(stats,setNames)
importFrom(stats,time)
importFrom(stats,weighted.mean)
importFrom(utils,head)
importFrom(utils,packageVersion)
importFrom(utils,str)
importFrom(utils,tail)
4 changes: 4 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
# MCView (development version)

* Added some missing package imports.

# MCView 0.2.23

* Fix: plot limits were sometimes too low in differential expression plots.
Expand Down
33 changes: 33 additions & 0 deletions R/MCView-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,5 +22,38 @@
# The following block is used by usethis to automatically manage
# roxygen namespace tags. Modify with care!
## usethis namespace: start
#' @importFrom graphics axis
#' @importFrom graphics layout
#' @importFrom graphics par
#' @importFrom graphics plot.new
#' @importFrom graphics plot.window
#' @importFrom graphics polygon
#' @importFrom graphics rect
#' @importFrom graphics segments
#' @importFrom graphics text
#' @importFrom grDevices col2rgb
#' @importFrom grDevices rgb
#' @importFrom stats approx
#' @importFrom stats as.dendrogram
#' @importFrom stats as.dist
#' @importFrom stats as.hclust
#' @importFrom stats chisq.test
#' @importFrom stats cor
#' @importFrom stats df
#' @importFrom stats ecdf
#' @importFrom stats hclust
#' @importFrom stats loess
#' @importFrom stats median
#' @importFrom stats plogis
#' @importFrom stats quantile
#' @importFrom stats reorder
#' @importFrom stats runif
#' @importFrom stats setNames
#' @importFrom stats time
#' @importFrom stats weighted.mean
#' @importFrom utils head
#' @importFrom utils packageVersion
#' @importFrom utils str
#' @importFrom utils tail
## usethis namespace: end
NULL
4 changes: 2 additions & 2 deletions R/app_ui.R
Original file line number Diff line number Diff line change
Expand Up @@ -99,11 +99,11 @@ app_ui <- function(request) {
app_title <- dataset_ls(project)[1]
config$title <- app_title
} else {
app_title <- glue("MCView {version}", version = packageVersion("MCView"))
app_title <- glue("MCView {version}", version = utils::packageVersion("MCView"))
}
}

app_footer <- glue("MCView {version}", version = packageVersion("MCView"))
app_footer <- glue("MCView {version}", version = utils::packageVersion("MCView"))
if (!is.null(config$metacells_version)) {
app_footer <- glue("{app_footer} | {config$metacells_version}")
}
Expand Down
2 changes: 1 addition & 1 deletion R/atlas_projection.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import_atlas <- function(query, atlas_project, atlas_dataset, projection_weights
)
} else {
if (fs::file_exists(atlas_new_path)) {
fs::file_remove(atlas_new_path)
fs::file_delete(atlas_new_path)
}

fs::link_create(
Expand Down
2 changes: 1 addition & 1 deletion R/import.R
Original file line number Diff line number Diff line change
Expand Up @@ -607,7 +607,7 @@ import_dataset <- function(project,

# write the version of the package
writeLines(
as.character(packageVersion("MCView")),
as.character(utils::packageVersion("MCView")),
project_version_file(project)
)

Expand Down
4 changes: 4 additions & 0 deletions R/import_metacell1.R
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,10 @@ import_dataset_metacell1 <- function(project,
metadata_fields = NULL,
categorical = c(),
...) {
if (!requireNamespace("metacell", quietly = TRUE)) {
stop("Please install metacell R package in order to use this function")
}

verbose <- !is.null(getOption("MCView.verbose")) && getOption("MCView.verbose")
verify_project_dir(project, create = TRUE, ...)

Expand Down
10 changes: 5 additions & 5 deletions R/metadata.R
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ update_metadata <- function(project,
}

cli_alert_info("Reading {.file {anndata_file}}")
library(anndata)
adata <- anndata::read_h5ad(anndata_file)
}
} else {
Expand Down Expand Up @@ -107,6 +106,8 @@ update_metadata_colors <- function(project,
#' Import cell metadata to an MCView dataset
#'
#'
#' @param project path to the project
#' @param dataset name for the dataset, e.g. "PBMC". The name of the dataset can only contain alphanumeric characters, dots, dashes and underscores.
#' @param cell_metadata data frame with a column named "cell_id" with
#' the cell id and other metadata columns, or a name of a delimited file which
#' contains such data frame. For activating the "Samples" tab, the data frame should have an additional
Expand Down Expand Up @@ -261,15 +262,15 @@ add_tab <- function(tab, project) {
#' @examples
#' set.seed(60427)
#' n_cells <- 5e6
#' cell_metadata <- tibble(
#' cell_metadata <- tibble::tibble(
#' cell_id = 1:n_cells,
#' md1 = sample(1:5, size = n_cells, replace = TRUE),
#' md2 = rnorm(n = n_cells),
#' md_categorical1 = sample(paste0("batch", 1:5), size = n_cells, replace = TRUE),
#' md_categorical2 = sample(1:5, size = n_cells, replace = TRUE)
#' )
#'
#' cell_to_metacell <- tibble(
#' cell_to_metacell <- tibble::tibble(
#' cell_id = 1:n_cells,
#' metacell = sample(0:1535, size = n_cells, replace = TRUE)
#' )
Expand All @@ -280,7 +281,7 @@ add_tab <- function(tab, project) {
#' head(metadata)
#'
#' metadata1 <- cell_metadata_to_metacell(
#' cell_metadata[, 11:3], cell_to_metacell,
#' cell_metadata[, 1:3], cell_to_metacell,
#' func = function(x) x * 2
#' )
#' head(metadata1)
Expand Down Expand Up @@ -416,7 +417,6 @@ cell_metadata_to_metacell_from_h5ad <- function(anndata_file, metadata_fields, f
}

cli_alert_info("Reading {.file {anndata_file}}")
library(anndata)
adata <- anndata::read_h5ad(anndata_file)

if (!("metacell_name" %in% colnames(adata$obs))) {
Expand Down
2 changes: 1 addition & 1 deletion R/mod_annotate.R
Original file line number Diff line number Diff line change
Expand Up @@ -570,7 +570,7 @@ mod_annotate_server <- function(id, dataset, metacell_types, cell_type_colors, g

observe({
req(input$cell_type_table_rows_selected)
row <- tail(input$cell_type_table_rows_selected, n = 1)
row <- utils::tail(input$cell_type_table_rows_selected, n = 1)
colourpicker::updateColourInput(session, "selected_new_color", value = cell_type_colors()$color[row])
})

Expand Down
2 changes: 1 addition & 1 deletion R/mod_flow.R
Original file line number Diff line number Diff line change
Expand Up @@ -221,7 +221,7 @@ mod_flow_server <- function(id, dataset, metacell_types, cell_type_colors, gene_
req(has_network(dataset()))
req(input$selected_metacell)

plotly::ggplotly(plot_gene_trajectory(dataset(), input$traj_genes, input$selected_metacell, anchor_gene = NULL) + theme(axis.title.y = element_text(color = "darkblue")), source = "traj_plot", tooltip = "tooltip_text") %>% sanitize_plotly_buttons()
plotly::ggplotly(plot_gene_trajectory(dataset(), input$traj_genes, input$selected_metacell, anchor_genes = NULL) + theme(axis.title.y = element_text(color = "darkblue")), source = "traj_plot", tooltip = "tooltip_text") %>% sanitize_plotly_buttons()
})
}
)
Expand Down
28 changes: 14 additions & 14 deletions R/plot_vein.R
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,10 @@ mctnetwork_g_t_types <- function(net, min_time, max_time, g, mc_egc, mc_colors)


src_flow <- as.data.frame(summarize(group_by(net_t, mc_t1, mc_t2),
g_src = weighted.mean(src_g, flow)
g_src = stats::weighted.mean(src_g, flow)
))
targ_flow <- as.data.frame(summarize(group_by(net_t, mc_t1, mc_t2),
g_targ = weighted.mean(targ_g, flow)
g_targ = stats::weighted.mean(targ_g, flow)
))


Expand Down Expand Up @@ -58,7 +58,7 @@ mctnetwork_g_t_types <- function(net, min_time, max_time, g, mc_egc, mc_colors)


add_alpha <- function(col, alpha) {
return(rgb(t(col2rgb(col)) / 256, alpha = alpha))
return(grDevices::rgb(t(grDevices::col2rgb(col)) / 256, alpha = alpha))
}


Expand All @@ -72,18 +72,18 @@ get_sig_edge <- function(x1, x2, x2t, y1, y2, y2t, flow, col1, col2, col_alpha =
dxt <- x2 - x1
dyt <- y2 - y1t

col1 <- col2rgb(col1)[, 1]
col1 <- grDevices::col2rgb(col1)[, 1]
names(col1) <- c("red", "green", "blue")
col2 <- col2rgb(col2)[, 1]
col2 <- grDevices::col2rgb(col2)[, 1]
names(col2) <- c("red", "green", "blue")
res <- 0.05

beta0 <- plogis(0, loc = 0.5, scale = 0.2)
beta_f <- plogis(1, loc = 0.5, scale = 0.2) - plogis(0, loc = 0.5, scale = 0.2)
beta0 <- stats::plogis(0, loc = 0.5, scale = 0.2)
beta_f <- stats::plogis(1, loc = 0.5, scale = 0.2) - stats::plogis(0, loc = 0.5, scale = 0.2)
polygons <- list()
for (r in seq(0, 0.98, res)) {
beta <- (plogis(r, loc = 0.5, scale = 0.2) - beta0) / beta_f
beta5 <- (plogis(r + res, loc = 0.5, scale = 0.2) - beta0) / beta_f
beta <- (stats::plogis(r, loc = 0.5, scale = 0.2) - beta0) / beta_f
beta5 <- (stats::plogis(r + res, loc = 0.5, scale = 0.2) - beta0) / beta_f

sx1 <- x1 + r * dx
sy1 <- y1 + beta * dy
Expand All @@ -99,7 +99,7 @@ get_sig_edge <- function(x1, x2, x2t, y1, y2, y2t, flow, col1, col2, col_alpha =
rgb_r <- col2["red"] * r_col + col1["red"] * (1 - r_col)
rgb_g <- col2["green"] * r_col + col1["green"] * (1 - r_col)
rgb_b <- col2["blue"] * r_col + col1["blue"] * (1 - r_col)
col <- rgb(rgb_r / 256, rgb_g / 256, rgb_b / 256, col_alpha)
col <- grDevices::rgb(rgb_r / 256, rgb_g / 256, rgb_b / 256, col_alpha)
poly_list <- list(
mat = matrix(c(sx1, sx2, sx2t, sx1t, sy1, sy2, sy2t, sy1t), nrow = 2, byrow = TRUE),
col = col,
Expand Down Expand Up @@ -226,15 +226,15 @@ plot_vein <- function(dataset,
col1 <- egc_to_col((targ_g_tt[[t - 1]][c, c] + src_g_tt[[t]][c, c]) / 2)
}
col2 <- egc_to_col((targ_g_tt[[t]][c, c] + src_g_tt[[t + 1]][c, c]) / 2)
col1 <- col2rgb(col1)[, 1]
col1 <- grDevices::col2rgb(col1)[, 1]
names(col1) <- c("red", "green", "blue")
col2 <- col2rgb(col2)[, 1]
col2 <- grDevices::col2rgb(col2)[, 1]
names(col2) <- c("red", "green", "blue")
for (lamda in seq(0, 0.99, l = 100)) {
rgb_r <- col2["red"] * lamda + col1["red"] * (1 - lamda)
rgb_g <- col2["green"] * lamda + col1["green"] * (1 - lamda)
rgb_b <- col2["blue"] * lamda + col1["blue"] * (1 - lamda)
col <- rgb(rgb_r / 256, rgb_g / 256, rgb_b / 256, col_alpha)
col <- grDevices::rgb(rgb_r / 256, rgb_g / 256, rgb_b / 256, col_alpha)

poly_list <- list(
mat = matrix(c(ys$x[i], ys$x[i + 1], ys$x[i + 1], ys$x[i], base + lo[i], base + lo[i + 1], base - lo[i + 1], base - lo[i]), nrow = 2, byrow = TRUE),
Expand Down Expand Up @@ -382,7 +382,7 @@ plot_vein <- function(dataset,
cols <- purrr::map_chr(polygons, ~ .x$col)
lwds <- purrr::map_dbl(polygons, ~ .x$lwd)
borders <- purrr::map_chr(polygons, ~ .x$border)
polygon(xs, ys, col = cols, border = borders, lwd = lwds)
graphics::polygon(xs, ys, col = cols, border = borders, lwd = lwds)
}

future_promise({
Expand Down
Loading

0 comments on commit a6d3b12

Please sign in to comment.