Skip to content

Commit

Permalink
stability greyscale, font size, panel labels
Browse files Browse the repository at this point in the history
  • Loading branch information
timokelder committed May 26, 2021
1 parent 131e3fc commit 6f008e7
Show file tree
Hide file tree
Showing 4 changed files with 53 additions and 30 deletions.
63 changes: 37 additions & 26 deletions R/stability_test.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,33 +7,39 @@
#' @param var_name The column name containing the variable to be analyzed. Defaults to "tprate".
#' @param ld_name The column name containing the leadtimes. Defaults to "leadtime".
#' @param lab The x-label. Defaults to the variable name (var_name).
#' @param fontsize The font size. Defaults to 11.
#' @param greyscale Boolean. Use grey scale? Defaults to TRUE.
#'
#' @return a plot showing the empirical probability density distribution for each leadtime
#' @source Evaluation explained in more detail in Kelder et al. 2020
#' @source Colorblind friendly palette http://www.cookbook-r.com/Graphs/Colors_(ggplot2)/#a-colorblind-friendly-palette
#' @export
Model_stability_density <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name) {
# I select five colors and put black at the end.
cbPalette <- c("#E69F00", "#56B4E9", "#009E73", "#F0E442", "#D55E00", "#000000") # , "#0072B2", "#CC79A7")
### The Leadtime column has to be a factor for a grouped plot
Model_stability_density <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name, fontsize = 11, greyscale = TRUE) {
# I select colors of grey scale, n= number of lead times
ensemble_length <- length(ensemble[[ld_name]])
leadtime_length <- sum(ensemble[[ld_name]] == 2)
if (greyscale == TRUE) {
cbPalette <- grey.colors(n = ensemble_length/leadtime_length)
}else{
cbPalette <- c("#E69F00", "#56B4E9", "#009E73", "#F0E442", "#D55E00", "#000000") # , "#0072B2", "#CC79A7")
}

### Change the leadtime column into a factor for a grouped plot
ensemble[[ld_name]] <- as.factor(ensemble[[ld_name]])

p1 <-
ggplot2::ggplot(
data = ensemble,
mapping = ggplot2::aes_(
x = as.name(var_name), colour = as.name(ld_name))) +
# ggplot2::ggtitle("UK") +
ggplot2::labs(x = lab, y = "Density") +
ggplot2::geom_line(stat = "density") +
ggplot2::theme_classic() +
ggplot2::theme(legend.position = "none") +
ggplot2::scale_colour_manual(values = cbPalette) #+
# theme(
# text = element_text(size = 11),
# axis.text = element_text(size = 11),
# plot.title = element_text(hjust = 0.5)
# )
ggplot2::scale_colour_manual(values = cbPalette) +
ggplot2::theme(text = ggplot2::element_text(size = fontsize),
axis.text = ggplot2::element_text(size = fontsize)
)

return(p1)
}
Expand All @@ -50,13 +56,15 @@ Model_stability_density <- function(ensemble, var_name = "tprate", ld_name = "le
#' @param var_name The column name containing the variable to be analyzed. Defaults to "tprate".
#' @param ld_name The column name containing the leadtimes. Defaults to "leadtime".
#' @param lab The y-label. Defaults to the variable name (var_name).
#' @param fontsize The font size. Defaults to 11.
#' @param greyscale Boolean. Use grey scale? Defaults to TRUE.
#'
#' @return a plot with the empirical return values of the pooled ensemble including confidence intervals.
#' Individual lead times are plotted on top.
#' @source Evaluation explaned in more detail in Kelder et al. 2020
#' @source Colorblind friendly palette http://www.cookbook-r.com/Graphs/Colors_(ggplot2)/#a-colorblind-friendly-palette
#' @export
Model_stability_boot <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name) {
Model_stability_boot <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name, fontsize = 11, greyscale = TRUE) {
#Define necessary global variables
ci_2.5 <- ci_97.5 <- quantiles_all <- rps_all <- NULL

Expand Down Expand Up @@ -97,24 +105,24 @@ Model_stability_boot <- function(ensemble, var_name = "tprate", ld_name = "leadt
df_quantiles$ci_97.5 <- ci_rvs[2, ]

# And plot
cbPalette <- c("#E69F00", "#56B4E9", "#009E73", "#F0E442", "#D55E00", "#000000") # , "#0072B2", "#CC79A7")
cols <- c("95 % CI" = "black")
if (greyscale == TRUE) {
cbPalette <- grey.colors(n = ensemble_length/leadtime_length)
}else{
cbPalette <- c("#E69F00", "#56B4E9", "#009E73", "#F0E442", "#D55E00", "#000000") # , "#0072B2", "#CC79A7")
}
p2 <-
ggplot2::ggplot(df_quantiles) +
ggplot2::geom_line(ggplot2::aes(x = rps_all, y = quantiles_all)) +
ggplot2::geom_line(ggplot2::aes_(x = ~rps_ld, y = ~quantiles_ld, col = as.name(ld_name))) +
ggplot2::geom_ribbon(ggplot2::aes(x = rps_all, ymin = ci_2.5, ymax = ci_97.5, fill = "95 % CI"), alpha = 0.1) +
# xlim(NA,875)+
ggplot2::geom_ribbon(ggplot2::aes(x = rps_all, ymin = ci_2.5, ymax = ci_97.5, fill = "black"), alpha = 0.1) +
ggplot2::scale_x_log10(limits = c(NA, leadtime_length)) +
# scale_x_continuous(trans='log10') +
ggplot2::scale_fill_manual(name = "Pooled data", values = cols) +
ggplot2::scale_colour_manual(values = cbPalette) +
ggplot2::xlab("Return period (years)") +
ggplot2::ylab(lab) +
ggplot2::theme_classic() +
ggplot2::theme(legend.position = "none",
text = ggplot2::element_text(size = 11),
axis.text = ggplot2::element_text(size = 11)
text = ggplot2::element_text(size = fontsize),
axis.text = ggplot2::element_text(size = fontsize)
)
return(p2)
}
Expand All @@ -124,21 +132,24 @@ Model_stability_boot <- function(ensemble, var_name = "tprate", ld_name = "leadt
#' @param ensemble The UNSEEN ensemble. This function expects an dataframe with variables leadtime, precipitation.
#' @param var_name The column name containing the variable to be analyzed. Defaults to "tprate".
#' @param ld_name The column name containing the leadtimes. Defaults to "leadtime".
#' @param lab The label. Defaults to the variable name (var_name).
#' @param lab The variable name plotted as x-label (first panel) and y-label (second panel). Defaults to the variable name (var_name).
#' @param panel_labels The panel labels. Defaults to c("a", "b").
#' @param fontsize The font size. Defaults to 11.
#' @param greyscale Boolean. Use grey scale? Defaults to TRUE.
#'
#' @return a plot with the empirical return values of the pooled ensemble including confidence intervals.
#' Individual lead times are plotted on top.
#' @seealso [Model_stability_density()] [Model_stability_boot()]d
#' @source Evaluation explaned in more detail in Kelder et al. 2020
#' @source Colorblind friendly palette http://www.cookbook-r.com/Graphs/Colors_(ggplot2)/#a-colorblind-friendly-palette
#' @export
stability_test <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name) {
stability_test <- function(ensemble, var_name = "tprate", ld_name = "leadtime", lab = var_name, fontsize = 11, greyscale = TRUE, panel_labels = c("a", "b")) {
#combine plots from function 1 and 2
p1 <- Model_stability_density(ensemble = ensemble, var_name = var_name, ld_name = ld_name, lab = lab)
p2 <- Model_stability_boot(ensemble = ensemble, var_name = var_name, ld_name = ld_name, lab = lab)
p1 <- Model_stability_density(ensemble = ensemble, var_name = var_name, ld_name = ld_name, lab = lab, fontsize = fontsize, greyscale = greyscale)
p2 <- Model_stability_boot(ensemble = ensemble, var_name = var_name, ld_name = ld_name, lab = lab, fontsize = fontsize, greyscale = greyscale)
p_combined <- ggpubr::ggarrange(p1, p2,
labels = c("a", "b"), # , "c", "d"),
hjust = c(-0.5, 1, -0.5, 1),
labels = panel_labels,
# hjust = c(-0.5, 1, -0.5, 1),
ncol = 1, nrow = 2,
font.label = list(size = 11, color = "black", face = "bold", family = NULL),
common.legend = TRUE
Expand Down
5 changes: 4 additions & 1 deletion man/Model_stability_boot.Rd

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

5 changes: 4 additions & 1 deletion man/Model_stability_density.Rd

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

10 changes: 8 additions & 2 deletions man/stability_test.Rd

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

0 comments on commit 6f008e7

Please sign in to comment.