Skip to content

Commit

Permalink
Merge pull request #1 from hadexversum/revs
Browse files Browse the repository at this point in the history
Revs
  • Loading branch information
werpuc authored Nov 18, 2024
2 parents 0a1dd0d + 4fb40e9 commit e4b693f
Show file tree
Hide file tree
Showing 9 changed files with 70 additions and 12 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ export(fit_3_exp)
export(fix_class_result)
export(get_example_control)
export(get_example_fit_k_params)
export(get_example_fit_k_params_2)
export(get_fit_results)
export(get_fit_values_info)
export(get_params_summary_image)
Expand Down
15 changes: 8 additions & 7 deletions R/calculate_hires.R
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ calculate_hires <- function(fit_values,
}

tmp_params <- tmp_params %>%
filter(!class_name %in% c("invalid", "invalid_uc")) %>%
arrange(nchar(sequence), class_name) %>%
.[1, ]

Expand Down Expand Up @@ -119,13 +120,13 @@ calculate_hires <- function(fit_values,
res <- data.frame(Protein = Protein,
State = State,
position = pos,
n_1 = NA,
k_1 = NA,
n_2 = NA,
k_2 = NA,
n_3 = NA,
k_3 = NA,
k_est = NA,
n_1 = class_example[["n_1"]],
k_1 = class_example[["k_1"]],
n_2 = class_example[["n_2"]],
k_2 = class_example[["k_3"]],
n_3 = class_example[["n_3"]],
k_3 = class_example[["k_3"]],
k_est = class_example[["k_est"]],
class_name = class_example[["class_name"]],
color = class_example[["color"]])

Expand Down
2 changes: 2 additions & 0 deletions R/create_fit_dataset.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ create_fit_dataset <- function(kin_dat,
control = list(maxiter = 1000, scale = "levenberg"),
trace = FALSE,
fractional = FALSE,
omit_t_100 = FALSE,
workflow = 321){

peptide_list <- kin_dat %>%
Expand All @@ -47,6 +48,7 @@ create_fit_dataset <- function(kin_dat,
trace = trace,
workflow = workflow,
fractional = fractional,
omit_t_100 = omit_t_100,
edge_times = edge_times)
}) %>% bind_rows() %>% mutate(id = 1:nrow(.)) %>% remove_rownames(.) %>%
select(id, everything())
Expand Down
11 changes: 10 additions & 1 deletion R/get_fit_results.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ get_fit_results <- function(fit_dat,
trace = FALSE,
workflow = 31,
fractional = TRUE,
omit_t_100 = FALSE,
edge_times = c(min(fit_dat[["Exposure"]]), max(fit_dat[["Exposure"]]))){

workflow <- match.arg(as.character(workflow), choices = c(31, 21, 321))
Expand All @@ -27,6 +28,11 @@ get_fit_results <- function(fit_dat,
fit_k_params))
}

if(omit_t_100){
time_100 <- attr(fit_dat, "time_100")
fit_dat <- filter(fit_dat, Exposure < time_100)
}

if(workflow == 31){

fit_3 <- fit_3_exp(fit_dat,
Expand Down Expand Up @@ -145,7 +151,7 @@ fix_class_result <- function(fit_dat,
color = "#000000"
}

if(class_name == "invalid"){
if(class_name %in% c("invalid", "invalid_uc")){
k_1 = n_1 = k_2 = n_2 = k_3 = n_3 = NA
color = "#808080"
}
Expand Down Expand Up @@ -200,6 +206,9 @@ detect_class <- function(fit_dat, edge_times = NULL){
if(du_100/ max_uptake < threshold & du_100 < 1) return("none")
# if((du_100 - du_1)/max_uptake < threshold & du_1 / du_100 > 1 - threshold) return("immediate")

accepted_fluctuation = 0.5 ## 0.5 Da doesnt significate exchange
if(du_100 < du_1 & !all(fit_dat[["deut_uptake"]] - du_100 < 0.5)) return("invalid_uc")

class_name

}
19 changes: 16 additions & 3 deletions R/getters.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,19 @@ get_example_fit_k_params <- function(){

}

#' Example k parameters
#'
#' @export

get_example_fit_k_params_2 <- function(){

return(data.frame(
start = c(k_1 = 2, k_2 = 0.2, k_3 = 0.02),
lower = c(k_1 = 1, k_2 = 0.1, k_3 = 0.0001),
upper = c(k_1 = 30, k_2 = 1, k_3 = 0.1)))

}

#' Example control
#'
#' @export
Expand Down Expand Up @@ -76,7 +89,7 @@ get_3_n_params <- function(MaxUptake = NA){

data.frame(
start = c(n_1 = MaxUptake/3, n_2 = MaxUptake/3, n_3 = MaxUptake/3),
lower = c(n_1 = 0, n_2 = 0, n_3 = 0),
lower = c(n_1 = 1, n_2 = 1, n_3 = 1),
upper = c(n_1 = MaxUptake, n_2 = MaxUptake, n_3 = MaxUptake)
)

Expand All @@ -97,7 +110,7 @@ get_2_n_params <- function(MaxUptake = NA){
} else {
data.frame(
start = c(n_1 = MaxUptake/2, n_2 = MaxUptake/2),
lower = c(n_1 = 0, n_2 = 0),
lower = c(n_1 = 1, n_2 = 1),
upper = c(n_1 = MaxUptake, n_2 = MaxUptake)
)
}
Expand All @@ -116,7 +129,7 @@ get_1_n_params <- function(MaxUptake = NA){
} else {
data.frame(
start = c(n_1 = MaxUptake*0.7),
lower = c(n_1 = 0),
lower = c(n_1 = 1),
upper = c(n_1 = MaxUptake)
)
}
Expand Down
11 changes: 10 additions & 1 deletion R/recreate_uc.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,16 @@
#' @description This function recovers fractional deuterium uptake from high-resolution level
#' back to the peptide level. First, the values are aggregated into high-resolution
#' level using selected aggregation method.
#' If there are no calculated recovered values, probably the peptide was calssified as
#' invalid - check that in fit_values_all param to be sure.
#'
#' @examples
#' kin_dat <- prepare_kin_dat(alpha_dat)
#' fit_values_all <- create_fit_dataset(kin_dat, control = get_example_control(),
#' fit_k_params = get_example_fit_k_params_2(),
#' fractional = TRUE)
#' fit_dat <- kin_dat[kin_dat[["ID"]] == 54, ]
#' calculate_uc_from_hires_peptide(fit_dat, fit_values_all, hires_method = "weighted")
#'
#' @seealso
#' \code{\link{create_uc_from_hires_dataset}}
Expand Down Expand Up @@ -59,7 +69,6 @@ calculate_uc_from_hires_peptide <- function(fit_dat, ## uc filtered dat
hr_diff = deut_uptake - hr_deut_uptake)
}


return(res)
}

Expand Down
11 changes: 11 additions & 0 deletions man/calculate_uc_from_hires_peptide.Rd

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

1 change: 1 addition & 0 deletions man/create_fit_dataset.Rd

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

11 changes: 11 additions & 0 deletions man/get_example_fit_k_params_2.Rd

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

0 comments on commit e4b693f

Please sign in to comment.