Skip to content
Snippets Groups Projects
Commit 997bb902 authored by Mauricio Zambrano-Bigiarini's avatar Mauricio Zambrano-Bigiarini
Browse files

plot\_particles.R: aarguments 'beh.thr', 'MinMax' and 'gofs' are now passed to 'params2ecdf'

parent d0a08f22
No related branches found
No related tags found
No related merge requests found
......@@ -101,6 +101,7 @@ NEWS/ChangeLog for hydroPSO
o 'plot_particles' : -) new argument 'do.pairs' (by default 'do.pairs=FALSE'), to control if the correlation matrix among parameters has to be plotted or not
(up to hydroPSO <=0.1.58 it was always plotted)
-) arguments 'MinMax' and 'beh.thr' are now passed to 'plot_NparOF'
-) arguments 'gofs', 'MinMax' and 'beh.thr' are now passed to 'params2ecdf'
o 'plot_results' : -) new argument 'do.pairs' (by default 'do.pairs=FALSE'), to control if the correlation matrix among parameters has to be plotted or not
(up to hydroPSO <=0.1.58 it was always plotted)
......
......@@ -68,17 +68,34 @@ params2ecdf.default <- function(params,
# number of parameters
nparam <- NCOL(params)
if (nparam==1) params <- matrix(params, ncol=1)
# Number of parameter sets
n <- NROW(params)
# Checking 'param.names'
if (length(param.names) != nparam)
stop("Invalid argument: 'length(param.names) = ", length(param.names), " != ", nparam, " = nparam'")
# Checking 'beh.thr'
if ( !is.na(beh.thr) ) {
if ( is.null(MinMax) )
stop("Missing argument: 'MinMax' has to be provided before using 'beh.thr' !!")
if ( missing(gofs) ) {
stop("Missing argument: 'gofs' has to be provided before using 'beh.thr' !!")
} else if (length(gofs) != n)
stop("Invalid argument: 'length(gofs) != nrow(params)' (", length(gofs), "!=", n, ") !!" )
} # IF end
# Checking 'MinMax'
if ( !is.null(MinMax) ) {
if ( !(MinMax %in% c("min", "max")) )
stop("Invalid argument: 'MinMax' must be in c('min', 'max')")
} # IF end
# checking that the user provided 1 weight for each behavioural parameter set
if ( !is.null(weights) ) {
if (length(weights) != NROW(params) )
stop("Invalid argument: 'length(w) != nrow(params)' (", length(weights), "!=", nrow(params), ")" )
if (length(weights) != n )
stop("Invalid argument: 'length(w) != nrow(params)' (", length(weights), "!=", n, ")" )
} # IF end
# creating the final output, a list with the ECDFs
......@@ -87,6 +104,28 @@ params2ecdf.default <- function(params,
# Checking 'do.png' and 'plot'
if (do.png==TRUE & plot==FALSE)
stop("Invalid argument: 'plot=FALSE' & 'do.png=TRUE' is not possible !!")
if (nparam==1) params <- matrix(params, ncol=1)
# Filtering out those parameter sets above/below a certain threshold
if (!is.na(beh.thr)) {
# Checking 'beh.thr'
mx <- max(gofs, na.rm=TRUE)
if (beh.thr > mx)
stop("Invalid argument: 'beh.thr' must be lower than ", mx ,"!!")
# Computing the row index of the behavioural parameter sets
ifelse(MinMax=="min", beh.row.index <- which(gofs <= beh.thr),
beh.row.index <- which(gofs >= beh.thr) )
# Removing non-behavioural parameter sets & gofs
params <- params[beh.row.index, ]
gofs <- gofs[beh.row.index]
# Amount of behavioural parameter sets
nbeh <- nrow(params)
if (verbose) message( "[ Number of behavioural parameter sets: ", nbeh, " ]" )
} # IF end
######################## Plotting Preliminars ########################
# If there are too many parameters to plot,more than 1 plot is produced
......
......@@ -133,7 +133,7 @@ plot_params.default <- function(params,
params <- params[, param.cols]
# computing the number of parameters
nparams <- ncol(params)
nparams <- NCOL(params)
# Filtering out those parameter sets above/below a certain threshold
if (!is.na(beh.thr)) {
......
......@@ -278,7 +278,10 @@ plot_particles <- function(#####################################################
if (!do.png) x11()
params2ecdf(params=params,
param.names=param.names,
param.names=param.names,
gofs= gofs,
MinMax=MinMax,
beh.thr=beh.thr,
weights=weights,
byrow=byrow,
plot=TRUE,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment