Skip to content

Commit

Permalink
remove prep dimensions (#105)
Browse files Browse the repository at this point in the history
* this is causing issue at #101

* fix warnings

* return and see if it plots correctly?

* Revert "return and see if it plots correctly?"

This reverts commit 63878e5.

* ok fixed it!

* Update vignette_v5.rmd
  • Loading branch information
zktuong authored Feb 19, 2024
1 parent c90d6bf commit 0c33012
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 28 deletions.
18 changes: 8 additions & 10 deletions R/plot_cpdb.R
Original file line number Diff line number Diff line change
Expand Up @@ -271,13 +271,7 @@ plot_cpdb <- function(
# .prep_data_query_celltype( .data = cellsign_mat, .query = query,
# .cell_type = cell_type, .celltype = celltype, ... ) }
}
if (length(means_mat) == 0) {
stop("Please check your options for splitby_key and your celltypes.")
} else {
if (!all(dim(pvals_mat) == dim(means_mat))) {
pvals_mat <- .prep_dimensions(pvals_mat, means_mat)
}
}

# rearrange the columns so that it interleaves the two groups
if (!is.null(splitby_key)) {
if (length(groups) > 0) {
Expand Down Expand Up @@ -555,7 +549,11 @@ plot_cpdb <- function(
if (filter_by_cellsign == TRUE) {
requireNamespace("dplyr")
df <- df %>%
dplyr::filter(cellsign >= 1)
dplyr::filter(!is.na(cellsign))
df <- df %>%
dplyr::group_by(Var1) %>%
dplyr::filter(dplyr::n_distinct(significant) > 1) %>%
as.data.frame()
}
if (scale_alpha_by_cellsign == TRUE) {
if (default_style) {
Expand Down Expand Up @@ -786,11 +784,11 @@ plot_cpdb <- function(
g <- g + geom_point(aes(
x = Var2, y = Var1, colour = scaled_means,
size = scaled_means
), data = df2, inherit_aes = FALSE, na_rm = TRUE)
), data = df2, inherit.aes = FALSE, na.rm = TRUE)
} else {
df2$means[df$pvals < 0.05] <- NA
g <- g + geom_point(aes(x = Var2, y = Var1, colour = means, size = means),
data = df2, inherit_aes = FALSE, na_rm = TRUE
data = df2, inherit.aes = FALSE, na.rm = TRUE
)
}
if (length(col_option) == 1) {
Expand Down
16 changes: 0 additions & 16 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,22 +12,6 @@ SPECIAL_SEP <- paste0(rep(DEFAULT_SEP, 3), collapse = "")
DEFAULT_CPDB_SEP <- "|"


.prep_dimensions <- function(input, reference) {
requireNamespace("reshape2")
tmp_mat <- reference
tmp_mat <- (tmp_mat * 0) + 1
melted_A <- reshape2::melt(as.matrix(tmp_mat))
melted_B <- reshape2::melt(as.matrix(input))
rownames(melted_A) <- paste0(melted_A$Var1, DEFAULT_SEP, melted_A$Var2)
rownames(melted_B) <- paste0(melted_B$Var1, DEFAULT_SEP, melted_B$Var2)
melted_A[row.names(melted_B), ] <- melted_B
tmp_mat <- reshape2::dcast(melted_A, Var1 ~ Var2, value.var = "value")
rownames(tmp_mat) <- tmp_mat$Var1
tmp_mat <- tmp_mat[, -1]
tmp_mat <- tmp_mat[rownames(reference), colnames(reference)]
return(tmp_mat)
}

.prep_table <- function(data) {
dat <- data
rownames(dat) <- paste0(dat$id_cp_interaction, SPECIAL_SEP, dat$interacting_pair)
Expand Down
4 changes: 2 additions & 2 deletions vignettes/vignette_v5.rmd
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ vignette: >

# CellPhoneDB v5 results

From version 5 of [CellPhoneDB](https://www.github.com/ventolab/cellphonedb), there is a new output file - `interaction_scores`.
From version 5 of [CellPhoneDB](https://www.github.com/ventolab/cellphonedb), there are two new output files - `interaction_scores` and `CellSign`.

According to the official repository, this table corresponds to:

Expand All @@ -31,7 +31,7 @@ To score interactions CellPhoneDB v5 employs the following protocol:

`cellsign`: accepts the new `CellSign` data.

The aim of the CellSign module is to identify activated receptors and prioritise high-confidence interactions by leveraging the activity of the downstream transcription factors (TFs). CellSign relies on a database of receptors linked to their putative downstream TFs.
The aim of the CellSign module is to identify activated receptors and prioritise high-confidence interactions by leveraging the activity of the downstream transcription factors (TFs). CellSign relies on a database of receptors linked to their putative downstream TFs. This is a binary table where 1 means it's a hit. In `ktplots/ktplotspy`, we convert all other values to 0.5 adn fit it to the `alpha` parameter for visualisation.

`ktplots` will support these output via inclusion into the existing `plot_cpdb` function. We will gradually enable their functionality across the other functions, as well as with in the python package eventually.

Expand Down

0 comments on commit 0c33012

Please sign in to comment.