Skip to content

Commit

Permalink
simulate dataset with 2 factors.
Browse files Browse the repository at this point in the history
  • Loading branch information
wolski committed Apr 25, 2024
1 parent ff00032 commit 728829e
Show file tree
Hide file tree
Showing 5 changed files with 79 additions and 3 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -157,6 +157,7 @@ export(separate_hierarchy)
export(setup_analysis)
export(sim_lfq_data)
export(sim_lfq_data_peptide_config)
export(sim_lfq_data_protein_2Factor_config)
export(sim_lfq_data_protein_config)
export(spread_response_by_IsotopeLabel)
export(squeezeVarRob)
Expand Down
47 changes: 46 additions & 1 deletion R/simulate_LFQ_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,10 @@
#' @param prop proportion of down (D), up (U) and not regulated (N)
#' @examples
#'
#' sim_lfq_data(Nprot = 10)
#' res <- sim_lfq_data(Nprot = 10)
#' res <- sim_lfq_data(Nprot = 10, PEPTIDE = TRUE)
#'

sim_lfq_data <- function(
Nprot = 20,
N = 4,
Expand Down Expand Up @@ -208,3 +210,46 @@ sim_lfq_data_protein_config <- function(Nprot = 10, with_missing = TRUE, weight_
return(list(data = adata, config = config))
}


#' Simulate data, protein, with config with 2 factros Treatment and Background
#' @param description Nprot number of proteins
#' @param with_missing add missing values, default TRUE
#' @param seed seed for reproducibility, if NULL no seed is set.
#' @export
#' @examples
#' x <- sim_lfq_data_protein_2Factor_config()
#' stopifnot("data.frame" %in% class(x$data))
#' stopifnot("AnalysisConfiguration" %in% class(x$config))
#'
sim_lfq_data_protein_2Factor_config <- function(Nprot = 10,
with_missing = TRUE,
weight_missing = 0.2,
seed = 1234){
if (!is.null(seed)) {
set.seed(seed)
}
res <- sim_lfq_data(Nprot = 10, PEPTIDE = FALSE,
fc = list(A = c(D = -2, U = 2, N = 0), B = c(D = 1, U = -4), C = c(D = -1, U = -4)),
prop = list(A = c(D = 10, U = 10), B = c(D = 5, U = 20), C = c(D = 15, U = 25)))
res <- res |> mutate(Treatment = case_when(group %in% c("Ctrl", "A") ~ "A", TRUE ~ "B"))
res <- res |> mutate(Background = case_when(group %in% c("Ctrl", "C") ~ "Z", TRUE ~ "X"))
if (with_missing) {
data <- data[!which_missing(data$abundance,weight_missing = weight_missing),]
}
data$isotopeLabel <- "light"
data$qValue <- 0

atable <- AnalysisTableAnnotation$new()
atable$fileName = "sample"
atable$nr_children = "nr_peptides"
atable$factors["Treatment"] = "Treatment"
atable$factors["Background"] = "Background"
atable$hierarchy[["protein_Id"]] = c("proteinID", "idtype2")
atable$set_response("abundance")

config <- AnalysisConfiguration$new(atable)
adata <- setup_analysis(data, config)
return(list(data = adata, config = config))
}


2 changes: 1 addition & 1 deletion R/tidyMS_missigness_V2.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ MissingHelpers <- R6::R6Class(
get_stats = function(){
if (is.null(self$stats)) {
self$stats = prolfqua::summarize_stats(self$data, self$config)
self$stats = prolfqua::make_interaction_column(self$stats, columns = self$config$table$factor_keys_depth())
self$stats = prolfqua::make_interaction_column(self$stats, columns = self$config$table$factor_keys_depth(), sep = ":")
}
return(self$stats)
},
Expand Down
3 changes: 2 additions & 1 deletion man/sim_lfq_data.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

29 changes: 29 additions & 0 deletions man/sim_lfq_data_protein_2Factor_config.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 728829e

Please sign in to comment.