R/plot_results.R

Defines functions plot_results

Documented in plot_results

################################################################################
##                               plot_results                                 ##
################################################################################
# Author : Rodrigo Marinao Rivas                                              ##
################################################################################
# Created: 2024/08/31                                                         ##
################################################################################
# Function: plot_results
# Description: A master function that consolidates plotting of hydrological 
#              model outputs, Pareto-optimal front solutions, and parameter 
#              sensitivity analyses. It calls three subordinate functions 
#              (plot_out, plot_pof, plot_param) to generate the required plots.
################################################################################

plot_results <- function(
    # Arguments for plot_out
    Results = NULL,          # (list) Object containing preprocessed 
                             # hydrological results.
    model.out = NULL,        # (list or NULL) Output from the 
                             # hydrological model used for evaluation.
    analysis.period = NULL,  # (character or NULL) Time period for analysis 
                             # (e.g., "calibration" or "verification").
    model.out.bcs = NULL,    # (list or NULL) Model output representing 
                             # the "Best Compromise Solution" (BCS).
    bcs = NULL,              # (matrix or NULL) Parameters or results 
                             # corresponding to the best compromise solution 
                             # (BCS).
    obs.var = NULL,          # (list or NULL) Observed variables to be 
                             # compared against the model outputs.
    dimensions = NULL,       # (matrix or NULL) Dimensions of the modeled 
                             # problem, typically a vector indicating the 
                             # number of objectives and variables.
    obj.names = NULL,        # (character or NULL) Names of the objectives.
    dates.cal = NULL,        # (Date or NULL) Dates of the calibration period.
    dates.warmup = NULL,     # (Date or NULL) Dates of the model's warm-up 
                             # period.
    var.names = NULL,        # (character or NULL) Names of the modeled and 
                             # observed variables.
    var.units = NULL,        # (character or NULL) Units of the modeled and 
                             # observed variables.
    xlim = NULL,             # (numeric or NULL) Limits for the 
                             # x-axis in the plots.
    ylim = NULL,             # (numeric or NULL) Limits for the 
                             # y-axis in the plots.
    digits = 4,              # (integer) Number of digits to use for rounding 
                             # values in plots and legends.
    col.band = "skyblue",    # (character) Color used for the model uncertainty 
                             # bands in the plots.
    col.bcs = "mediumblue",  # (character) Color used for the line representing 
                             # the best compromise solution (BCS).
    col.obs = "black",       # (character) Color used for the observed variable 
                             # lines in the plots.
    lwd = 0.75,              # (numeric) Line width used in the plots for 
                             # model and observation lines.
    pch.bcs = 15,            # (integer) Symbol type for points in the plot 
                             # representing the best compromise solution (BCS).
    pch.obs = 15,            # (integer) Symbol type for points in the plot 
                             # representing the observations.
    main = "study case #1",  # (character) Main title for the plot.
    drty.out = "MOPSO.out",  # (character) Output directory where plots will 
                             # be saved if specified to save as PNG files.
    cex.pt.out = 0.25,       # (numeric) Size of points in the "out" plots.
    cex.pt.pof = 1.25,       # (numeric) Size of points in the "pof" plots.
    cex.pt.param = 1,        # (numeric) Size of points in the "param" plots.
    cex.main = 1,            # (numeric) Size of the main title text in plot.
    cex.lab = 1,             # (numeric) Size of the axis label text in plots.
    cex.axis = 1,            # (numeric) Size of the axis values text in plots.
    do.png = FALSE,          # (logical) Boolean value indicating whether the 
                             # plots should be saved as PNG files.
    legend.obs = "Observation",
                             # (character) Legend text for observations.
    legend.bcs = "Best compromise solution",
                             # (character) Legend text for the best 
                             # compromise solution (BCS).
    legend.band = "Pareto front bands",
                             # (character) Legend text for Pareto 
                             # front bands.
    
    # Arguments for plot_pof
    pof = NULL,              # (matrix) Dataset representing the 
                             # filled Pareto-optimal front (POF) solutions.
    maxmin = NULL,           # (character) Indicator of whether objectives 
                             # are to be maximized ("max") or minimized ("min").
    obj.thr = NULL,          # (numeric) Objective thresholds.
    pch.pof = 21,            # (integer) Symbol type for points in the plot 
                             # representing the Pareto-optimal front solutions.
    col.pof = "#f21b1b",     # (character) Color used for the points
                             # representing the Pareto-optimal front solutions
                             # in the plots.
    legend.pof = c("Pareto-optimal front solutions", 
                   "Best compromise solution"),
                             # (character) Legend text for the Pareto-optimal
                             # front and best compromise solution.
    
    # Arguments for plot_param
    legend.param = NULL,     # (character) Legend text for the parameters in the
                             # plots.
    col = NULL,              # (character) Colors used for points in the  
                             # parameter dotty plots.
    col.param = NULL,        # (character) Specific colors for lines or points 
                             # representing parameters in the parameter 
                             # boxplots.
    col.lines = NULL,        # (character) Specific colors for lines in the
                             # parameter boxplots.
    name.param = NULL,       # (character vector) Custom names for the 
                             # parameters to be plotted.
    cex.leg = 1              # (numeric) Size of the legend text in the plots.
){
    if (is.null(Results)) {
        candidates <- ls(envir = .GlobalEnv)
        found <- FALSE
        for (obj in candidates) {
            x <- get(obj, envir = .GlobalEnv)
            if (is.list(x) && all(c("Rep", "MOPSOResults", "hydroDetails", "hydroResults") %in% names(x))) {
                Results <- x
                found <- TRUE
                message(sprintf("Using '%s' as default Results object.", obj))
                break
            }
        }
        if (!found) stop("No suitable 'Results' object found in the environment.")
    }
    # Call to plot_out
    plot_out(
        Results = Results,
        model.out = model.out,
        analysis.period = analysis.period,
        model.out.bcs = model.out.bcs,
        bcs = bcs,
        obs.var = obs.var,
        dimensions = dimensions,
        obj.names = obj.names,
        dates.cal = dates.cal,
        dates.warmup = dates.warmup,
        var.names = var.names,
        var.units = var.units,
        xlim = xlim,
        ylim = ylim,
        digits = digits,
        col.band = col.band,
        col.bcs = col.bcs,
        col.obs = col.obs,
        lwd = lwd,
        pch.bcs = pch.bcs,
        pch.obs = pch.obs,
        main = main,
        drty.out = drty.out,
        cex.pt = cex.pt.out,
        cex.main = cex.main,
        cex.lab = cex.lab,
        cex.axis = cex.axis,
        do.png = do.png,
        legend.obs = legend.obs,
        legend.bcs = legend.bcs,
        legend.band = legend.band
    )
    
    # Call to plot_pof
    plot_pof(
        Results = Results,
        pof = pof,
        bcs = bcs,
        analysis.period = analysis.period,
        dimensions = dimensions,
        maxmin = maxmin,
        obj.thr = obj.thr,
        obj.names = obj.names,
        main = main,
        drty.out = drty.out,
        pch.pof = pch.pof,
        pch.bcs = pch.bcs,
        col.pof = col.pof,
        col.bcs = col.bcs,
        legend.pof = legend.pof,
        cex.pt = cex.pt.pof,
        cex.main = cex.main,
        cex.lab = cex.lab,
        cex.axis = cex.axis,
        do.png = do.png
    )
    
    # Call to plot_param
    plot_param(
        Results = Results,
        legend.param = legend.param,
        col = col,
        col.param = col.param,
        col.lines = col.lines,
        name.param = name.param,
        lwd = lwd,
        main = main,
        drty.out = drty.out,
        cex.pt = cex.pt.param,
        cex.main = cex.main,
        cex.lab = cex.lab,
        cex.axis = cex.axis,
        cex.leg = cex.leg,
        do.png = do.png
    )
}

Try the hydroMOPSO package in your browser

Any scripts or data that you put into this service are public.

hydroMOPSO documentation built on June 18, 2025, 9:15 a.m.