Skip to content

Commit

Permalink
separate observes #106
Browse files Browse the repository at this point in the history
  • Loading branch information
werpuc committed May 18, 2022
1 parent 5418f82 commit b53fadb
Show file tree
Hide file tree
Showing 17 changed files with 197 additions and 63 deletions.
4 changes: 2 additions & 2 deletions R/kinetics.R
Original file line number Diff line number Diff line change
Expand Up @@ -500,7 +500,7 @@ plot_kinetics <- function(kin_dat,

}

kin_plot
return(HaDeXify(kin_plot))
}

#' Plot differential uptake curve
Expand Down Expand Up @@ -684,6 +684,6 @@ plot_differential_uptake_curve <- function(diff_uptake_dat = NULL,

}

diff_kin_plot
return(HaDeXify(diff_kin_plot))

}
4 changes: 2 additions & 2 deletions R/p_plots.R
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ plot_volcano <- function(p_dat,

}

return(volcano_plot)
return(HaDeXify(volcano_plot))

}

Expand Down Expand Up @@ -242,6 +242,6 @@ plot_manhattan <- function(p_dat,
geom_hline(yintercept = confidence_limit, linetype = "dashed")
}

manhattan_plot
return(HaDeXify(manhattan_plot))

}
4 changes: 3 additions & 1 deletion R/plot_coverage.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ plot_coverage <- function(dat,
protein = dat[["Protein"]][1],
states = dat[["State"]][1]){

dat %>%
cov_plot <- dat %>%
filter(Protein == protein) %>%
select(Start, End, State) %>%
filter(State %in% states) %>%
Expand All @@ -54,4 +54,6 @@ plot_coverage <- function(dat,
theme(axis.ticks.y = element_blank(),
axis.text.y = element_blank())

return(HaDeXify(cov_plot))

}
4 changes: 3 additions & 1 deletion R/plot_position_frequency.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,8 +46,10 @@ plot_position_frequency <- function(dat,
group_by(x) %>%
summarise(coverage = length(x))

ggplot(coverage_df, aes(x = x, y = coverage)) +
pos_freq_plot <- ggplot(coverage_df, aes(x = x, y = coverage)) +
geom_col(width = 1) +
labs(x = 'Position', y = 'Position frequency in peptides') +
theme(legend.position = "none")

return(HaDeXify(pos_freq_plot))
}
8 changes: 5 additions & 3 deletions R/uptake_plots.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ plot_state_comparison <- function(dat,
value = dat[[value]],
err_value = dat[[err_value]])

ggplot(data = plot_dat) +
state_comp_plot <- ggplot(data = plot_dat) +
geom_segment(data = plot_dat, aes(x = Start, y = value, xend = End, yend = value, color = State)) +
geom_errorbar(data = plot_dat, aes(x = Med_Sequence, ymin = value - err_value, ymax = value + err_value, color = State)) +
labs(title = title,
Expand All @@ -89,6 +89,8 @@ plot_state_comparison <- function(dat,
theme(legend.position = "bottom",
legend.title = element_blank())

return(HaDeXify(state_comp_plot))

}

#' Butterfly plot
Expand Down Expand Up @@ -201,7 +203,7 @@ plot_butterfly <- function(butterfly_dat,

}

return(butterfly_plot)
return(HaDeXify(butterfly_plot))

}

Expand Down Expand Up @@ -312,6 +314,6 @@ plot_chiclet <- function(chiclet_dat,

}

return(chiclet_plot)
return(HaDeXify(chiclet_plot))

}
34 changes: 25 additions & 9 deletions inst/HaDeX/server/tab_butterfly.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,12 @@ observe({
inputId = "butt_state",
choices = states_chosen_protein(),
selected = states_chosen_protein()[1])

})

##

observe({

if(input[["butt_fractional"]]){

Expand All @@ -34,6 +40,11 @@ observe({
inputId = "butt_time_0",
choices = times_from_file()[times_from_file() < 99999],
selected = min(times_from_file()[times_from_file() > 0]))
})

##

observe({

updateSelectInput(session,
inputId = "butt_time_100",
Expand All @@ -43,6 +54,20 @@ observe({

##

observe({

max_x <- max(butterfly_dataset()[["ID"]])
min_x <- min(butterfly_dataset()[["ID"]])

updateSliderInput(session,
inputId = "butt_x_range",
min = min_x,
max = max_x,
value = c(min_x, max_x))
})

##

observe({

if(input[["butt_fractional"]]){
Expand All @@ -56,15 +81,6 @@ observe({
min_y <- floor(min(butterfly_dataset()[["deut_uptake"]], butterfly_dataset()[["theo_deut_uptake"]], na.rm = TRUE)) - 1
}

max_x <- max(butterfly_dataset()[["ID"]])
min_x <- min(butterfly_dataset()[["ID"]])

updateSliderInput(session,
inputId = "butt_x_range",
min = min_x,
max = max_x,
value = c(min_x, max_x))

updateSliderInput(session,
inputId = "butt_y_range",
min = min_y - 5,
Expand Down
48 changes: 37 additions & 11 deletions inst/HaDeX/server/tab_butterfly_differential.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,22 @@ observe({
inputId = "butt_diff_state_1",
choices = states_chosen_protein(),
selected = states_chosen_protein()[1])
})

##

observe({

updateSelectInput(session,
inputId = "butt_diff_state_2",
choices = states_chosen_protein(),
selected = states_chosen_protein()[length(states_chosen_protein())])
})

##

observe({

if(input[["butt_diff_fractional"]]){

times_t <- times_from_file()[times_from_file() > as.numeric(input[["butt_diff_time_0"]]) & times_from_file() < as.numeric(input[["butt_diff_time_100"]])]
Expand All @@ -38,7 +48,12 @@ observe({
inputId = "butt_diff_time_0",
choices = times_from_file()[times_from_file() < 99999],
selected = min(times_from_file()[times_from_file() > 0]))
})

##

observe({

updateSelectInput(session,
inputId = "butt_diff_time_100",
choices = times_with_control(),
Expand All @@ -55,7 +70,12 @@ observe({
input[["butt_diff_theory"]] ~ paste0("Thereotical butterfly differential plot between ", input[["butt_diff_state_1"]], " and ", input[["butt_diff_state_2"]]),
!input[["butt_diff_theory"]] ~ paste0("Butterfly differential plot between ", input[["butt_diff_state_1"]], " and ", input[["butt_diff_state_2"]])
))
})

##

observe({

updateTextInput(session,
inputId = "butterflyDifferential_plot_y_label",
value = case_when(
Expand All @@ -70,17 +90,6 @@ observe({

observe({

if (input[["butt_diff_fractional"]]) {

max_y <- ceiling(max(butt_diff_dataset()[["diff_frac_deut_uptake"]], butt_diff_dataset()[["diff_theo_frac_deut_uptake"]], na.rm = TRUE)) + 1
min_y <- floor(min(butt_diff_dataset()[["diff_frac_deut_uptake"]], butt_diff_dataset()[["diff_theo_frac_deut_uptake"]], na.rm = TRUE)) - 1

} else {

max_y <- ceiling(max(butt_diff_dataset()[["diff_deut_uptake"]], butt_diff_dataset()[["diff_theo_deut_uptake"]], na.rm = TRUE)) + 1
min_y <- floor(min(butt_diff_dataset()[["diff_deut_uptake"]], butt_diff_dataset()[["diff_theo_deut_uptake"]], na.rm = TRUE)) - 1
}

max_x <- max(butt_diff_dataset()[["ID"]])
min_x <- min(butt_diff_dataset()[["ID"]])

Expand All @@ -92,6 +101,23 @@ observe({
value = c(min_x, max_x)
)

})

##

observe({

if (input[["butt_diff_fractional"]]) {

max_y <- ceiling(max(butt_diff_dataset()[["diff_frac_deut_uptake"]], butt_diff_dataset()[["diff_theo_frac_deut_uptake"]], na.rm = TRUE)) + 1
min_y <- floor(min(butt_diff_dataset()[["diff_frac_deut_uptake"]], butt_diff_dataset()[["diff_theo_frac_deut_uptake"]], na.rm = TRUE)) - 1

} else {

max_y <- ceiling(max(butt_diff_dataset()[["diff_deut_uptake"]], butt_diff_dataset()[["diff_theo_deut_uptake"]], na.rm = TRUE)) + 1
min_y <- floor(min(butt_diff_dataset()[["diff_deut_uptake"]], butt_diff_dataset()[["diff_theo_deut_uptake"]], na.rm = TRUE)) - 1
}

updateSliderInput(
session,
inputId = "butt_diff_y_range",
Expand Down
5 changes: 5 additions & 0 deletions inst/HaDeX/server/tab_chiclet.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,11 @@ observe({
inputId = "chic_time_0",
choices = times_from_file()[times_from_file() < 99999],
selected = min(times_from_file()[times_from_file() > 0]))
})

##

observe({

updateSelectInput(session,
inputId = "chic_time_100",
Expand Down
15 changes: 15 additions & 0 deletions inst/HaDeX/server/tab_chiclet_differential.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,21 @@ observe({
inputId = "chic_diff_state_1",
choices = states_chosen_protein(),
selected = states_chosen_protein()[1])
})

##

observe({

updateSelectInput(session,
inputId = "chic_diff_state_2",
choices = states_chosen_protein(),
selected = states_chosen_protein()[length(states_chosen_protein())])
})

##

observe({

if(input[["chic_diff_fractional"]]){

Expand All @@ -38,6 +48,11 @@ observe({
inputId = "chic_diff_time_0",
choices = times_from_file()[times_from_file() < 99999],
selected = min(times_from_file()[times_from_file() > 0]))
})

##

observe({

updateSelectInput(session,
inputId = "chic_diff_time_100",
Expand Down
29 changes: 10 additions & 19 deletions inst/HaDeX/server/tab_comparison.R
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,12 @@ observe({
input[["theory"]] ~ paste0("Theoretical deuterium uptake in ", input[["time_t"]], " min for ", input[["chosen_protein"]]),
!input[["theory"]] ~ paste0("Deuterium uptake in ", input[["time_t"]], " min for ", input[["chosen_protein"]])
))
})

##

observe({

updateTextInput(session,
inputId = "comparison_plot_y_label",
value = case_when(
Expand Down Expand Up @@ -149,7 +154,12 @@ observe({
inputId = "plot_range",
max = max_range(),
value = c(1, max_range()))
})

##

observe({

updateSliderInput(session,
inputId = "plot_x_range",
max = max_range(),
Expand Down Expand Up @@ -208,25 +218,6 @@ comparison_plot_colors <- reactive({

output[["states_colors"]] <- renderUI({

# colorInput <- function(inputId, label, value = "", width = NULL, placeholder = NULL) {
# '%BAND%' <- function (x, y) {
# if (!is.null(x) && !is.na(x))
# if (!is.null(y) && !is.na(y))
# return(y)
# return(NULL)
# }
# value <- restoreInput(id = inputId, default = value)
# if(!is.null(value))
# div(class = "form-group shiny-input-container",
# style = paste(if (value != "") paste0("background-color=: ", validateCssUnit(width), ";"),
# if (!is.null(width)) paste0("width: ", validateCssUnit(width), ";")
# ),
# label %BAND%
# tags$label(label, `for` = inputId), tags$input(id = inputId,
# type = "text", class = "form-control", value = value,
# placeholder = placeholder))
# }

lapply(1:length(states_from_file()), function(i) {
textInput(inputId = paste0(states_from_file()[i], "_color"),
label = paste(states_from_file()[i], " color"),
Expand Down
19 changes: 16 additions & 3 deletions inst/HaDeX/server/tab_differential.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,12 @@ observe({
input[["theory"]] ~ paste0("Theoretical deuterium uptake difference in ", input[["time_t"]], " min between ", gsub("_", " ", input[["diff_state_1"]]), " and ", gsub("_", " ", input[["diff_state_2"]]), " for ", input[["chosen_protein"]]),
!input[["theory"]] ~ paste0("Deuterium uptake difference in ", input[["time_t"]], " min between ", gsub("_", " ", input[["diff_state_1"]]), " and ", gsub("_", " ", input[["diff_state_2"]]), " for ", input[["chosen_protein"]])
))

})

##

observe({

updateTextInput(session,
inputId = "woods_plot_y_label",
Expand All @@ -52,18 +58,25 @@ observe({

observe({


updateSelectInput(session,
inputId = "diff_state_1",
choices = states_chosen_protein(),
selected = states_chosen_protein()[1])
})

##

observe({

updateSelectInput(session,
inputId = "diff_state_2",
choices = states_chosen_protein(),
selected = states_chosen_protein()[length(states_chosen_protein())])


})

##

observe({

updateSelectInput(session,
inputId = "confidence_level_2",
Expand Down
Loading

0 comments on commit b53fadb

Please sign in to comment.