diff --git a/R/Utils.R b/R/Utils.R index 53519abaed0773e224e4a87aa412a4bc70b4233e..d5e14535fc3839bd4564168b99a56f40d24a39b2 100644 --- a/R/Utils.R +++ b/R/Utils.R @@ -219,16 +219,41 @@ res } +.IndexOutputsModel <- function(x, i) { # '[.OutputsModel' <- function(x, i) { -# if (!inherits(x, "OutputsModel")) { -# stop("'x' must be of class 'OutputsModel'") -# } -# if (is.factor(i)) { -# i <- as.character(i) -# } -# if (is.numeric(i)) { -# .ExtractOutputsModel(x, i) -# } else { -# NextMethod() -# } -# } + if (!inherits(x, "OutputsModel")) { + stop("'x' must be of class 'OutputsModel'") + } + if (is.factor(i)) { + i <- as.character(i) + } + if (is.numeric(i)) { + .ExtractOutputsModel(x, i) + } else { + NextMethod() + } +} + + + +## ================================================================================= +## function to try to set local time in English +## ================================================================================= + +.TrySetLcTimeEN <- function() { + locale <- list("English_United Kingdom", + "en_US", + "en_US.UTF-8", + "en_US.utf8", + "en") + dateTest <- as.POSIXct("2000-02-15", tz = "UTC", format = "%Y-%m-%d") + monthTestTarget <- "February" + monthTest <- function() { + format(dateTest, format = "%B") + } + lapply(locale, function(x) { + if (monthTest() != monthTestTarget) { + Sys.setlocale(category = "LC_TIME", locale = x) + } + }) +} diff --git a/R/plot.OutputsModel.R b/R/plot.OutputsModel.R index 17a616aeef224f1fdf7b594aa4800207ea84b29a..79ff7abe474b5b2988959566b5be59abb8f76a3d 100644 --- a/R/plot.OutputsModel.R +++ b/R/plot.OutputsModel.R @@ -1,50 +1,67 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = NULL, which = "synth", log_scale = FALSE, cex.axis = 1, cex.lab = 0.9, cex.leg = 0.9, lwd = 1, + AxisTS = function(x) axis.POSIXct(side = 1, x = x$DatesR, ...), LayoutMat = NULL, LayoutWidths = rep.int(1, ncol(LayoutMat)), LayoutHeights = rep.int(1, nrow(LayoutMat)), verbose = TRUE, ...) { - - - ## save default graphical parameters and resetting on exit + + + ## save default graphical & time parameters and resetting on exit opar <- par(no.readonly = TRUE) - on.exit(par(opar)) - - + olctime <- Sys.getlocale(category = "LC_TIME") + suppressWarnings(.TrySetLcTimeEN()) + on.exit({ + par(opar) + Sys.setlocale(category = "LC_TIME", locale = olctime) + }) + + OutputsModel <- x - - - + + ## index time series + if (!is.null(IndPeriod_Plot)) { + if (length(IndPeriod_Plot) == 0) { + IndPeriod_Plot <- seq_along(OutputsModel$DatesR) + } + IndPeriod_Plot <- seq_along(IndPeriod_Plot) + OutputsModel <- .IndexOutputsModel(OutputsModel, IndPeriod_Plot) + Qobs <- Qobs[IndPeriod_Plot] + } else { + IndPeriod_Plot <- seq_along(OutputsModel$DatesR) + } + + ## ---------- check arguments - + if (!inherits(OutputsModel, "GR") & !inherits(OutputsModel, "CemaNeige")) { stop("'OutputsModel' not in the correct format for default plotting") } - + ## check 'OutputsModel' BOOL_Dates <- FALSE if ("DatesR" %in% names(OutputsModel)) { BOOL_Dates <- TRUE } - + BOOL_Pobs <- FALSE if ("Precip" %in% names(OutputsModel)) { BOOL_Pobs <- TRUE } - + BOOL_EPobs <- FALSE if ("PotEvap" %in% names(OutputsModel)) { BOOL_EPobs <- TRUE } - + BOOL_EAobs <- FALSE if ("AE" %in% names(OutputsModel)) { BOOL_EAobs <- TRUE } - + BOOL_Qsim <- FALSE if ("Qsim" %in% names(OutputsModel)) { BOOL_Qsim <- TRUE } - + BOOL_Qobs <- FALSE if (BOOL_Qsim & length(Qobs) == length(OutputsModel$Qsim)) { if (sum(is.na(Qobs)) != length(Qobs)) { @@ -53,27 +70,27 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } else if (inherits(OutputsModel, "GR") & !is.null(Qobs)) { warning("incorrect length of 'Qobs'. Time series of observed flow not drawn") } - + BOOL_Error <- FALSE if (BOOL_Qsim & BOOL_Qobs) { BOOL_Error <- TRUE } - + BOOL_Snow <- FALSE if ("CemaNeigeLayers" %in% names(OutputsModel)) { if ("SnowPack" %in% names(OutputsModel$CemaNeigeLayers[[1]])) { BOOL_Snow <- TRUE } } - + BOOL_Psol <- FALSE if ("CemaNeigeLayers" %in% names(OutputsModel)) { if ("Psol" %in% names(OutputsModel$CemaNeigeLayers[[1]])) { BOOL_Psol <- TRUE } } - - + + ## check 'which' whichNeedQobs <- c("Error", "CorQQ") whichDashboard <- c("all", "synth", "ts", "perf") @@ -139,7 +156,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } } - + ## check dates if (!BOOL_Dates) { stop("'OutputsModel' must contain at least 'DatesR' to allow plotting") @@ -147,7 +164,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = if (inherits(OutputsModel, "GR") & !BOOL_Qsim) { stop("'OutputsModel' must contain at least 'Qsim' to allow plotting") } - + if (BOOL_Dates) { # MyRollMean1 <- function(x, n) { # return(filter(x, rep(1 / n, n), sides = 2)) @@ -157,42 +174,29 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = # } MyRollMean3 <- function(x, n) { return(filter(x, filter = rep(1 / n, n), sides = 2, circular = TRUE)) - } + } BOOL_TS <- FALSE if (inherits(OutputsModel, "hourly")) { BOOL_TS <- TRUE NameTS <- "hour" plotunit <- "[mm/h]" - formatAxis <- "%m/%Y" - } - if (inherits(OutputsModel, "daily")) { + } else if (inherits(OutputsModel, "daily")) { BOOL_TS <- TRUE NameTS <- "day" plotunit <- "[mm/d]" - formatAxis <- "%m/%Y" - } - if (inherits(OutputsModel, "monthly")) { + } else if (inherits(OutputsModel, "monthly")) { BOOL_TS <- TRUE NameTS <- "month" plotunit <- "[mm/month]" - formatAxis <- "%m/%Y" - if (format(OutputsModel$DatesR[1L], format = "%d") != "01") { - OutputsModel$DatesR <- as.POSIXlt(format(OutputsModel$DatesR, format = "%Y-%m-01"), tz = "UTC", format = "%Y-%m-%d") - } - } - if (inherits(OutputsModel, "yearly")) { + } else if (inherits(OutputsModel, "yearly")) { BOOL_TS <- TRUE NameTS <- "year" plotunit <- "[mm/y]" - formatAxis <- "%Y" } # if (!BOOL_TS) { # stop("the time step of the model inputs could not be found") # } } - if (length(IndPeriod_Plot) == 0) { - IndPeriod_Plot <- 1:length(OutputsModel$DatesR) - } if (inherits(OutputsModel, "CemaNeige")) { NLayers <- length(OutputsModel$CemaNeigeLayers) } @@ -208,12 +212,12 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } BOOL_QobsZero <- FALSE if (BOOL_Qobs) { - SelectQobsNotZero <- round(Qobs[IndPeriod_Plot], 4) != 0 + SelectQobsNotZero <- round(Qobs, 4) != 0 BOOL_QobsZero <- sum(!SelectQobsNotZero, na.rm = TRUE) > 0 } BOOL_QsimZero <- FALSE if (BOOL_Qsim) { - SelectQsimNotZero <- round(OutputsModel$Qsim[IndPeriod_Plot], 4) != 0 + SelectQsimNotZero <- round(OutputsModel$Qsim, 4) != 0 BOOL_QsimZero <- sum(!SelectQsimNotZero, na.rm = TRUE) > 0 } if ( BOOL_Qobs & !BOOL_Qsim) { @@ -232,11 +236,11 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = warning("zeroes detected in 'Qsim': some plots in the log space will not be created using all time-steps") } BOOL_FilterZero <- TRUE - - - + + + ## ---------- plot - + ## plot choices BOOLPLOT_Precip <- "Precip" %in% which & BOOL_Pobs BOOLPLOT_PotEvap <- "PotEvap" %in% which & BOOL_EPobs @@ -248,30 +252,30 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = BOOLPLOT_Regime <- "Regime" %in% which & BOOL_Qsim & BOOL_TS & (NameTS %in% c("hour", "day", "month")) BOOLPLOT_CumFreq <- "CumFreq" %in% which & (BOOL_Qsim | BOOL_Qobs) & BOOL_FilterZero BOOLPLOT_CorQQ <- "CorQQ" %in% which & (BOOL_Qsim & BOOL_Qobs) & BOOL_FilterZero - - + + ## options BLOC <- TRUE if (BLOC) { lwdk <- 1.8 line <- 2.6 bg <- NA - + ## Set plot arrangement - if (is.null(LayoutMat)) { + if (is.null(LayoutMat)) { matlayout <- NULL iPlot <- 0 iHght <- NULL - + listBOOLPLOT1 <- c(Precip = BOOLPLOT_Precip, - PotEvap = BOOLPLOT_PotEvap | BOOLPLOT_ActuEvap, + PotEvap = BOOLPLOT_PotEvap | BOOLPLOT_ActuEvap, Temp = BOOLPLOT_Temp , SnowPack = BOOLPLOT_SnowPack, Flows = BOOLPLOT_Flows , Error = BOOLPLOT_Error) listBOOLPLOT2 <- c(Regime = BOOLPLOT_Regime, CumFreq = BOOLPLOT_CumFreq, CorQQ = BOOLPLOT_CorQQ) Sum1 <- sum(listBOOLPLOT1) Sum2 <- sum(listBOOLPLOT2) - + for (k in seq_len(Sum1)) { matlayout <- rbind(matlayout, iPlot + c(1, 1, 1)) iPlot <- iPlot + 1 @@ -305,24 +309,12 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = matlayout <- LayoutMat } layout(matlayout, widths = LayoutWidths, heights = LayoutHeights) - - - - Xaxis <- 1:length(IndPeriod_Plot) - if (BOOL_Dates) { - if (NameTS %in% c("hour", "day", "month")) { - Seq1 <- which(OutputsModel$DatesR[IndPeriod_Plot]$mday == 1 & OutputsModel$DatesR[IndPeriod_Plot]$mon %in% c(0, 3, 6, 9)) - Seq2 <- which(OutputsModel$DatesR[IndPeriod_Plot]$mday == 1 & OutputsModel$DatesR[IndPeriod_Plot]$mon == 0) - Labels2 <- format(OutputsModel$DatesR[IndPeriod_Plot], format = formatAxis)[Seq2] - } - if (NameTS %in% c("year")) { - Seq1 <- 1:length(OutputsModel$DatesR[IndPeriod_Plot]) - Seq2 <- 1:length(OutputsModel$DatesR[IndPeriod_Plot]) - Labels2 <- format(OutputsModel$DatesR[IndPeriod_Plot], format = formatAxis)[Seq2] - } - } - + + + + Xaxis <- as.POSIXct(OutputsModel$DatesR) + if (!is.null(BasinArea)) { Factor_UNIT_M3S <- switch(NameTS, hour = 60 * 60, @@ -332,9 +324,9 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = Factor_UNIT_M3S <- BasinArea / (Factor_UNIT_M3S / 1000) } } - + kPlot <- 0 - + ## vector of Q values for the y-axis when it is expressed in Factor <- ifelse(!is.null(BasinArea), Factor_UNIT_M3S, 1) seqDATA0 <- c(0.01, 0.02, 0.05, 0.1, 0.2, 0.5, 1, 2, 5, 10, 20, 50, 100, 200, 500, 1000, 2000, 5000, 10000) @@ -344,115 +336,106 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = seqDATA1ba <- log(seqDATA0 * Factor_UNIT_M3S) seqDATA2ba <- round(exp(seqDATA1ba), digits = 2) } - + ## Precip if (BOOLPLOT_Precip) { kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) - + par(new = FALSE, mar = mar) - ylim1 <- range(OutputsModel$Precip[IndPeriod_Plot], na.rm = TRUE) + ylim1 <- range(OutputsModel$Precip, na.rm = TRUE) ylim2 <- ylim1 * c(1.0, 1.1) ylim2 <- rev(ylim2) - + lwdP <- lwd * 0.7 if (NameTS %in% c("month", "year")) { lwdP <- lwd * 2 } - plot(Xaxis, OutputsModel$Precip[IndPeriod_Plot], + plot(Xaxis, OutputsModel$Precip, type = "h", xaxt = "n", yaxt = "n", yaxs = "i", ylim = ylim2, col = "royalblue", lwd = lwdP * lwdk, lend = 1, xlab = "", ylab = "", ...) axis(side = 2, at = pretty(ylim1), labels = pretty(ylim1), cex.axis = cex.axis, ...) mtext(side = 2, paste("precip.", plotunit), cex = cex.lab, adj = 1, line = line) - + if (BOOL_Psol) { legend("bottomright", legend = c("solid","liquid"), col = c("lightblue", "royalblue"), lty = c(1, 1), lwd = c(lwd, lwd), bty = "o", bg = bg, box.col = bg, cex = cex.leg) - par(new = TRUE) - plot(Xaxis, PsolLayerMean[IndPeriod_Plot], - type = "h", xaxt = "n", yaxt = "n", yaxs = "i", ylim = ylim2, - col = "lightblue", lwd = lwdP * lwdk, lend = 1, - xlab = "", ylab = "", ...) - } - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) + points(Xaxis, PsolLayerMean, + type = "h", xaxt = "n", yaxt = "n", yaxs = "i", ylim = ylim2, + col = "lightblue", lwd = lwdP * lwdk, lend = 1, + xlab = "", ylab = "", ...) } + + AxisTS(OutputsModel) + + box() } - - + + ## PotEvap if (BOOLPLOT_PotEvap) { kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) - + par(new = FALSE, mar = mar) if (!BOOLPLOT_ActuEvap) { - ylim1 <- range(OutputsModel$PotEvap[IndPeriod_Plot], na.rm = TRUE) + ylim1 <- range(OutputsModel$PotEvap, na.rm = TRUE) xlabE <- "pot. evap." } else { - ylim1 <- range(c(OutputsModel$PotEvap[IndPeriod_Plot], - OutputsModel$AE[IndPeriod_Plot]), + ylim1 <- range(c(OutputsModel$PotEvap, + OutputsModel$AE), na.rm = TRUE) xlabE <- "evap." } ylim2 <- ylim1 #* c(1.0, 1.1) - - - plot(Xaxis, OutputsModel$PotEvap[IndPeriod_Plot], + + + plot(Xaxis, OutputsModel$PotEvap, type = "l", xaxt = "n", yaxt = "n", ylim = ylim2, col = "green3", lwd = lwd * lwdk, xlab = "", ylab = "", ...) if (BOOLPLOT_ActuEvap) { - lines(Xaxis, OutputsModel$AE[IndPeriod_Plot], - type = "l", xaxt = "n", yaxt = "n", ylim = ylim2, - col = "green4", lwd = lwd * lwdk, lty = 3) + lines(Xaxis, OutputsModel$AE, + type = "l", xaxt = "n", yaxt = "n", ylim = ylim2, + col = "green4", lwd = lwd * lwdk, lty = 3) legend("topright", legend = c("pot.", "actu."), col = c("green3", "green4"), - lty = c(1, 3), lwd = c(lwd*1.0, lwd*0.8), + lty = c(1, 3), lwd = c(lwd * 1.0, lwd * 0.8), bty = "o", bg = bg, box.col = bg, cex = cex.leg) } axis(side = 2, at = pretty(ylim1), labels = pretty(ylim1), cex.axis = cex.axis, ...) - + mtext(side = 2, paste(xlabE, plotunit), cex = cex.lab, line = line) - - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } + + AxisTS(OutputsModel) + + box() } - + ## ActuEvap if (BOOLPLOT_ActuEvap & !BOOLPLOT_PotEvap) { kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) - + par(new = FALSE, mar = mar) - ylim1 <- range(OutputsModel$AE[IndPeriod_Plot], na.rm = TRUE) + ylim1 <- range(OutputsModel$AE, na.rm = TRUE) ylim2 <- ylim1 #* c(1.0, 1.1) - - plot(Xaxis, OutputsModel$AE[IndPeriod_Plot], + + plot(Xaxis, OutputsModel$AE, type = "l", xaxt = "n", yaxt = "n", ylim = ylim2, col = "green4", lwd = lwd * lwdk, xlab = "", ylab = "", ...) axis(side = 2, at = pretty(ylim1), labels = pretty(ylim1), cex.axis = cex.axis, ...) - + mtext(side = 2, paste("actu. evap.", plotunit), cex = cex.lab, line = line) - - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } + + AxisTS(OutputsModel) + + box() } - - + + ## Temp if (BOOLPLOT_Temp) { kPlot <- kPlot + 1 @@ -468,29 +451,26 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = SnowPackLayerMean <- SnowPackLayerMean + OutputsModel$CemaNeigeLayers[[iLayer]]$Temp/NLayers } } - plot(SnowPackLayerMean[IndPeriod_Plot], type = "n", ylim = ylim1, xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) + plot(Xaxis, SnowPackLayerMean, type = "n", ylim = ylim1, xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) for (iLayer in 1:NLayers) { - lines(OutputsModel$CemaNeigeLayers[[iLayer]]$Temp[IndPeriod_Plot], lty = 3, col = "orchid", lwd = lwd * lwdk * 0.8) + lines(Xaxis, OutputsModel$CemaNeigeLayers[[iLayer]]$Temp, lty = 3, col = "orchid", lwd = lwd * lwdk * 0.8) } abline(h = 0, col = "grey", lty = 2) - lines(SnowPackLayerMean[IndPeriod_Plot], type = "l", lwd = lwd * lwdk *1.0, col = "darkorchid4") + lines(Xaxis, SnowPackLayerMean, type = "l", lwd = lwd * lwdk * 1.0, col = "darkorchid4") axis(side = 2, at = pretty(ylim1), labels = pretty(ylim1), cex.axis = cex.axis, ...) - + mtext(side = 2, expression(paste("temp. [", degree, "C]"), sep = ""), padj = 0.2, line = line, cex = cex.lab) - + legend("topright", legend = c("mean", "layers"), col = c("darkorchid4", "orchid"), - lty = c(1, 3), lwd = c(lwd*1.0, lwd*0.8), + lty = c(1, 3), lwd = c(lwd * 1.0, lwd * 0.8), bty = "o", bg = bg, box.col = bg, cex = cex.leg) + + AxisTS(OutputsModel) + box() - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } } - - + + ## SnowPack if (BOOLPLOT_SnowPack) { kPlot <- kPlot + 1 @@ -506,33 +486,30 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = SnowPackLayerMean <- SnowPackLayerMean + OutputsModel$CemaNeigeLayers[[iLayer]]$SnowPack/NLayers } } - plot(SnowPackLayerMean[IndPeriod_Plot], type = "l", ylim = ylim1, lwd = lwd * lwdk *1.2, col = "royalblue", xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) + plot(Xaxis, SnowPackLayerMean, type = "l", ylim = ylim1, lwd = lwd * lwdk * 1.2, col = "royalblue", xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) for (iLayer in 1:NLayers) { - lines(OutputsModel$CemaNeigeLayers[[iLayer]]$SnowPack[IndPeriod_Plot], lty = 3, col = "royalblue", lwd = lwd * lwdk *0.8) + lines(Xaxis, OutputsModel$CemaNeigeLayers[[iLayer]]$SnowPack, lty = 3, col = "royalblue", lwd = lwd * lwdk * 0.8) } axis(side = 2, at = pretty(ylim1), labels = pretty(ylim1), cex.axis = cex.axis, ...) - + mtext(side = 2, paste("snow pack", "[mm]"), line = line, cex = cex.lab) legend("topright", legend = c("mean", "layers"), col = c("royalblue", "royalblue"), - lty = c(1, 3), lwd = c(lwd*1.2, lwd*0.8), + lty = c(1, 3), lwd = c(lwd * 1.2, lwd * 0.8), bty = "o", bg = bg, box.col = bg, cex = cex.leg) + + AxisTS(OutputsModel) + box() - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } } - - + + ## Flows if (BOOLPLOT_Flows & log_scale) { kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) par(new = FALSE, mar = mar) - - if (BOOL_Qobs) { + + if (BOOL_Qobs) { DATA2 <- Qobs DATA2[!SelectQobsNotZero] <- mean(Qobs, na.rm = TRUE) / 10000 DATA2 <- log(DATA2) @@ -540,22 +517,22 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = DATA3 <- OutputsModel$Qsim DATA3[!SelectQsimNotZero] <- mean(OutputsModel$Qsim, na.rm = TRUE) / 10000 DATA3 <- log(DATA3) - - ylim1 <- range(DATA3[IndPeriod_Plot], na.rm = TRUE) + + ylim1 <- range(DATA3, na.rm = TRUE) if (BOOL_Qobs) { - ylim1 <- range(c(ylim1, DATA2[IndPeriod_Plot]), na.rm = TRUE) + ylim1 <- range(c(ylim1, DATA2), na.rm = TRUE) } - ylim2 <- c(ylim1[1], 1.1*ylim1[2]) + ylim2 <- c(ylim1[1], 1.1 * ylim1[2]) plot(Xaxis, rep(NA, length(Xaxis)), type = "n", ylim = ylim2, xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) txtleg <- NULL colleg <- NULL if (BOOL_Qobs) { - lines(Xaxis, DATA2[IndPeriod_Plot], lwd = lwd * lwdk , lty = 1, col = par("fg")) + lines(Xaxis, DATA2, lwd = lwd * lwdk, lty = 1, col = par("fg")) txtleg <- c(txtleg, "observed") colleg <- c(colleg, par("fg")) } if (BOOL_Qsim) { - lines(Xaxis, DATA3[IndPeriod_Plot], lwd = lwd * lwdk , lty = 1, col = "orangered") + lines(Xaxis, DATA3, lwd = lwd * lwdk, lty = 1, col = "orangered") txtleg <- c(txtleg, "simulated") colleg <- c(colleg, "orangered") } @@ -566,13 +543,8 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = axis(side = 4, at = seqDATA1ba, labels = seqDATA2ba, cex.axis = cex.axis, ...) mtext(side = 4, paste("flow", "[m3/s]"), line = line, cex = cex.lab) } - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } - legend("topright", txtleg, col = colleg, lty = 1, lwd = lwd * lwdk , bty = "o", bg = bg, box.col = bg, cex = cex.leg) + AxisTS(OutputsModel) + legend("topright", txtleg, col = colleg, lty = 1, lwd = lwd * lwdk, bty = "o", bg = bg, box.col = bg, cex = cex.leg) legend("bottomright", "log scale", lty = 1, col = NA, bty = "o", bg = bg, box.col = bg, cex = cex.leg) box() } @@ -580,21 +552,21 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) par(new = FALSE, mar = mar) - ylim1 <- range(OutputsModel$Qsim[IndPeriod_Plot], na.rm = TRUE) + ylim1 <- range(OutputsModel$Qsim, na.rm = TRUE) if (BOOL_Qobs) { - ylim1 <- range(c(ylim1, Qobs[IndPeriod_Plot]), na.rm = TRUE) + ylim1 <- range(c(ylim1, Qobs), na.rm = TRUE) } - ylim2 <- c(ylim1[1], 1.1*ylim1[2]) + ylim2 <- c(ylim1[1], 1.1 * ylim1[2]) plot(Xaxis, rep(NA, length(Xaxis)), type = "n", ylim = ylim2, xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) txtleg <- NULL colleg <- NULL if (BOOL_Qobs) { - lines(Xaxis, Qobs[IndPeriod_Plot], lwd = lwd * lwdk , lty = 1, col = par("fg")) + lines(Xaxis, Qobs, lwd = lwd * lwdk, lty = 1, col = par("fg")) txtleg <- c(txtleg, "observed") colleg <- c(colleg, par("fg")) } if (BOOL_Qsim) { - lines(Xaxis, OutputsModel$Qsim[IndPeriod_Plot], lwd = lwd * lwdk , lty = 1, col = "orangered") + lines(Xaxis, OutputsModel$Qsim, lwd = lwd * lwdk, lty = 1, col = "orangered") txtleg <- c(txtleg, "simulated") colleg <- c(colleg, "orangered") } @@ -602,29 +574,24 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = mtext(side = 2, paste("flow", plotunit), line = line, cex = cex.lab) if (!is.null(BasinArea)) { Factor <- Factor_UNIT_M3S - axis(side = 4, at = pretty(ylim1*Factor)/Factor, labels = pretty(ylim1*Factor), cex.axis = cex.axis, ...) + axis(side = 4, at = pretty(ylim1 * Factor)/Factor, labels = pretty(ylim1 * Factor), cex.axis = cex.axis, ...) mtext(side = 4, paste("flow", "[m3/s]"), line = line, cex = cex.lab) } - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } - legend("topright", txtleg, col = colleg, lty = 1, lwd = lwd * lwdk , bty = "o", bg = bg, box.col = bg, cex = cex.leg) + AxisTS(OutputsModel) + legend("topright", txtleg, col = colleg, lty = 1, lwd = lwd * lwdk, bty = "o", bg = bg, box.col = bg, cex = cex.leg) box() } - - + + ## Error if (BOOLPLOT_Error) { kPlot <- kPlot + 1 mar <- c(3, 5, 1, 5) - + if (log_scale) { - errorQ <- log(OutputsModel$Qsim[IndPeriod_Plot]) - log(Qobs[IndPeriod_Plot]) + errorQ <- log(OutputsModel$Qsim) - log(Qobs) } else { - errorQ <- OutputsModel$Qsim[IndPeriod_Plot] - Qobs[IndPeriod_Plot] + errorQ <- OutputsModel$Qsim - Qobs } par(new = FALSE, mar = mar) ylim1 <- range(errorQ[SelectNotZero], na.rm = TRUE) @@ -637,21 +604,17 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = mtext(side = 2, paste("flow error", plotunit), cex = cex.lab, line = line) if (!is.null(BasinArea)) { Factor <- Factor_UNIT_M3S - axis(side = 4, at = pretty(ylim1*Factor)/Factor, labels = pretty(ylim1*Factor), cex.axis = cex.axis, ...) + axis(side = 4, at = pretty(ylim1 * Factor)/Factor, labels = pretty(ylim1 * Factor), cex.axis = cex.axis, ...) mtext(side = 4, paste("flow error", "[m3/s]"), line = line, cex = cex.lab) } - if (BOOL_Dates) { - axis(side = 1, at = Seq1, labels = FALSE, cex.axis = cex.axis, ...) - axis(side = 1, at = Seq2, labels = Labels2, lwd.ticks = 1.5, cex.axis = cex.axis, ...) - } else { - axis(side = 1, at = pretty(Xaxis), labels = pretty(Xaxis), cex.axis = cex.axis, ...) - } + AxisTS(OutputsModel) if (log_scale) { legend("bottomright", "log scale", lty = 1, col = NA, bty = "o", bg = bg, box.col = bg, cex = cex.leg) } + box() } - - + + ## Regime if (BOOLPLOT_Regime) { kPlot <- kPlot + 1 @@ -674,18 +637,18 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } else { ## Data_formating_as_table DataModel <- as.data.frame(matrix(as.numeric(NA), nrow = length(IndPeriod_Plot), ncol = 5)) - DataModel[, 1] <- as.numeric(format(OutputsModel$DatesR[IndPeriod_Plot], format = "%Y%m%d%H")) + DataModel[, 1] <- as.numeric(format(OutputsModel$DatesR, format = "%Y%m%d%H")) if (BOOL_Pobs) { - DataModel[, 2] <- OutputsModel$Precip[IndPeriod_Plot] + DataModel[, 2] <- OutputsModel$Precip } if (BOOL_Psol) { - DataModel[, 3] <- PsolLayerMean[IndPeriod_Plot] + DataModel[, 3] <- PsolLayerMean } if (BOOL_Qobs) { - DataModel[, 4] <- Qobs[IndPeriod_Plot] + DataModel[, 4] <- Qobs } if (BOOL_Qsim) { - DataModel[, 5] <- OutputsModel$Qsim[IndPeriod_Plot] + DataModel[, 5] <- OutputsModel$Qsim } colnames(DataModel) <- c("Dates", "Precip", "Psol", "Qobs", "Qsim") TxtDatesDataModel <- formatC(DataModel$Dates, format = "d", width = 8, flag = "0") @@ -720,22 +683,22 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = SeqY <- data.frame(Dates = as.numeric(format(seq(as.Date("1970-01-01", tz = "UTC"), as.Date("1970-12-31", tz = "UTC"), "day"), format = "%m%d"))) - DataDailyInterAn <- as.data.frame(aggregate(DataDaily[, 2:5], by = list(as.numeric(substr(TxtDatesDataDaily , 5, 8))), FUN = mean, na.rm = TRUE)) + DataDailyInterAn <- as.data.frame(aggregate(DataDaily[, 2:5], by = list(as.numeric(substr(TxtDatesDataDaily, 5, 8))), FUN = mean, na.rm = TRUE)) colnames(DataDailyInterAn) <- c("Dates", "Precip", "Psol", "Qobs", "Qsim") - DataDailyInterAn <- merge(SeqY, DataDailyInterAn, by = "Dates", all.x = TRUE, all.y = FALSE) + DataDailyInterAn <- merge(SeqY, DataDailyInterAn, by = "Dates", all.x = TRUE, all.y = FALSE) } if (!is.null(DataMonthly)) { SeqM <- data.frame(Dates = 1:12) DataMonthlyInterAn <- as.data.frame(aggregate(DataMonthly[, 2:5], by = list(as.numeric(substr(TxtDatesDataMonthly, 5, 6))), FUN = mean, na.rm = TRUE)) colnames(DataMonthlyInterAn) <- c("Dates", "Precip", "Psol", "Qobs", "Qsim") - DataMonthlyInterAn <- merge(SeqM, DataMonthlyInterAn, by = "Dates", all.x = TRUE, all.y = FALSE) + DataMonthlyInterAn <- merge(SeqM, DataMonthlyInterAn, by = "Dates", all.x = TRUE, all.y = FALSE) } ## Smoothing_of_daily_series_and_scale_conversion_to_make_them_become_a_monthly_regime if (!is.null(DataDaily)) { ## Smoothing NDaysWindow <- 30 - DataDailyInterAn <- as.data.frame(cbind(DataDailyInterAn$Dates, - MyRollMean3(DataDailyInterAn$Precip, NDaysWindow), MyRollMean3(DataDailyInterAn$Psol, NDaysWindow), + DataDailyInterAn <- as.data.frame(cbind(DataDailyInterAn$Dates, + MyRollMean3(DataDailyInterAn$Precip, NDaysWindow), MyRollMean3(DataDailyInterAn$Psol, NDaysWindow), MyRollMean3(DataDailyInterAn$Qobs , NDaysWindow), MyRollMean3(DataDailyInterAn$Qsim, NDaysWindow))) colnames(DataDailyInterAn) <- c("Dates", "Precip", "Psol", "Qobs", "Qsim") ## Scale_conversion_to_make_them_become_a_monthly_regime @@ -770,17 +733,17 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = ## Plot_forcings if (BOOL_Pobs) { plot(SeqX2[DataMonthlyInterAn$Dates], DataPlotP$Precip, type = "h", - xlim = range(SeqX1), ylim = c(3*ylimP[1], ylimP[2]), lwd = lwdP, lend = 1, lty = 1, col = "royalblue", + xlim = range(SeqX1), ylim = c(3 * ylimP[1], ylimP[2]), lwd = lwdP, lend = 1, lty = 1, col = "royalblue", xlab = "", ylab = "", xaxt = "n", yaxt = "n", yaxs = "i", bty = "n", ...) txtleg <- c(txtleg, "Ptot" ) colleg <- c(colleg, "royalblue") lwdleg <- c(lwdleg, lwdP/3) - axis(side = 2, at = pretty(0.8*ylimP, n = 3), labels = pretty(0.8*ylimP, n = 3), col.axis = "royalblue", col.ticks = "royalblue", cex.axis = cex.axis, ...) + axis(side = 2, at = pretty(0.8 * ylimP, n = 3), labels = pretty(0.8 * ylimP, n = 3), col.axis = "royalblue", col.ticks = "royalblue", cex.axis = cex.axis, ...) par(new = TRUE) } if (BOOL_Psol) { plot(SeqX2, DataPlotP$Psol[DataMonthlyInterAn$Dates], type = "h", xlim = range(SeqX1), - ylim = c(3*ylimP[1], ylimP[2]), lwd = lwdP, lend = 1, lty = 1, col = "lightblue", + ylim = c(3 * ylimP[1], ylimP[2]), lwd = lwdP, lend = 1, lty = 1, col = "lightblue", xlab = "", ylab = "", xaxt = "n", yaxt = "n", yaxs = "i", bty = "n", ...) txtleg <- c(txtleg, "Psol" ) colleg <- c(colleg, "lightblue") @@ -788,15 +751,15 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = par(new = TRUE) } ## Plot_flows - plot(NULL, type = "n", xlim = range(SeqX1), ylim = c(ylimQ[1], 2*ylimQ[2]), xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) + plot(NULL, type = "n", xlim = range(SeqX1), ylim = c(ylimQ[1], 2 * ylimQ[2]), xlab = "", ylab = "", xaxt = "n", yaxt = "n", ...) if (BOOL_Qobs) { - lines(1:nrow(DataPlotQ), DataPlotQ$Qobs, lwd = lwd * lwdk , lty = 1, col = par("fg") ) + lines(1:nrow(DataPlotQ), DataPlotQ$Qobs, lwd = lwd * lwdk, lty = 1, col = par("fg") ) txtleg <- c(txtleg, "Qobs" ) colleg <- c(colleg, par("fg") ) lwdleg <- c(lwdleg, lwd) } if (BOOL_Qsim) { - lines(1:nrow(DataPlotQ), DataPlotQ$Qsim, lwd = lwd * lwdk , lty = 1, col = "orangered") + lines(1:nrow(DataPlotQ), DataPlotQ$Qsim, lwd = lwd * lwdk, lty = 1, col = "orangered") txtleg <- c(txtleg, "Qsim") colleg <- c(colleg, "orangered") lwdleg <- c(lwdleg, lwd) @@ -815,16 +778,14 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = mtext(side = 2, paste(txtlab, plotunitregime), line = line, cex = cex.lab) if (!is.null(BasinArea)) { Factor <- Factor_UNIT_M3S / (365.25 / 12) - axis(side = 4, at = pretty(ylimQ*Factor)/Factor, labels = pretty(ylimQ*Factor), cex.axis = cex.axis, ...) + axis(side = 4, at = pretty(ylimQ * Factor)/Factor, labels = pretty(ylimQ * Factor), cex.axis = cex.axis, ...) mtext(side = 4, paste("flow", "[m3/s]"), line = line, cex = cex.lab) } - ### posleg <- "topright"; if (BOOL_Pobs) {posleg <- "right";} - ### legend(posleg, txtleg, col = colleg, lty = 1, lwd = lwdleg, bty = "o", bg = bg, box.col = bg, cex = cex.leg) box() } } - - + + ## Cumulative_frequency if (BOOLPLOT_CumFreq) { kPlot <- kPlot + 1 @@ -833,15 +794,15 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = xlim <- c(0, 1) if ( BOOL_Qobs & !BOOL_Qsim) { # SelectNotZero <- SelectQobsNotZero - ylim <- range(log(Qobs[IndPeriod_Plot][SelectNotZero]), na.rm = TRUE) + ylim <- range(log(Qobs[SelectNotZero]), na.rm = TRUE) } if (!BOOL_Qobs & BOOL_Qsim) { # SelectNotZero <- SelectQsimNotZero - ylim <- range(log(OutputsModel$Qsim[IndPeriod_Plot][SelectNotZero]), na.rm = TRUE) + ylim <- range(log(OutputsModel$Qsim[SelectNotZero]), na.rm = TRUE) } if ( BOOL_Qobs & BOOL_Qsim) { # SelectNotZero <- SelectQobsNotZero & SelectQsimNotZero - ylim <- range(log(c(Qobs[IndPeriod_Plot][SelectNotZero], OutputsModel$Qsim[IndPeriod_Plot][SelectNotZero])), na.rm = TRUE) + ylim <- range(log(c(Qobs[SelectNotZero], OutputsModel$Qsim[SelectNotZero])), na.rm = TRUE) } SelectNotZero <- ifelse(is.na(SelectNotZero), FALSE, SelectNotZero) if (any(SelectNotZero)) { @@ -851,12 +812,12 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = xlab = "", ylab = "", ...) axis(side = 1, at = pretty(xlim), labels = pretty(xlim), cex.axis = cex.axis, ...) mtext(side = 1, text = "non-exceedance prob. [-]", line = line, cex = cex.lab) - axis(side = 2, at = seqDATA1, labels = seqDATA2, cex.axis = cex.axis, ...) + axis(side = 2, at = seqDATA1, labels = seqDATA2, cex.axis = cex.axis, ...) mtext(side = 2, text = paste("flow", plotunit), line = line, cex = cex.lab) txtleg <- NULL colleg <- NULL if (BOOL_Qobs) { - DATA2 <- log(Qobs[IndPeriod_Plot][SelectNotZero]) + DATA2 <- log(Qobs[SelectNotZero]) SeqQuant <- seq(0, 1, by = 1/(length(DATA2))) Quant <- as.numeric(quantile(DATA2, SeqQuant, na.rm = TRUE)) Fn <- ecdf(DATA2) @@ -869,7 +830,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = colleg <- c(colleg, par("fg")) } if (BOOL_Qsim) { - DATA2 <- log(OutputsModel$Qsim[IndPeriod_Plot][SelectNotZero]) + DATA2 <- log(OutputsModel$Qsim[SelectNotZero]) SeqQuant <- seq(0, 1, by = 1/(length(DATA2))) Quant <- as.numeric(quantile(DATA2, SeqQuant, na.rm = TRUE)) Fn <- ecdf(DATA2) @@ -883,7 +844,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } if (!is.null(BasinArea)) { Factor <- Factor_UNIT_M3S - axis(side = 4, at = seqDATA1, labels = round(seqDATA2*Factor, digits = 2), cex.axis = cex.axis, ...) + axis(side = 4, at = seqDATA1, labels = round(seqDATA2 * Factor, digits = 2), cex.axis = cex.axis, ...) mtext(side = 4, paste("flow", "[m3/s]"), line = line, cex = cex.lab) } legend("topleft", txtleg, col = colleg, lty = 1, lwd = lwd, bty = "o", bg = bg, box.col = bg, cex = cex.leg) @@ -896,17 +857,17 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } box() } - - + + ## Correlation_QQ if (BOOLPLOT_CorQQ) { kPlot <- kPlot + 1 mar <- c(6, 5, 1, 5) par(new = FALSE, mar = mar) if (any(SelectNotZero)) { - ylim <- log(range(c(Qobs[IndPeriod_Plot][SelectQobsNotZero & SelectQsimNotZero], OutputsModel$Qsim[IndPeriod_Plot][SelectQobsNotZero & SelectQsimNotZero]), na.rm = TRUE)) - plot(log(Qobs[IndPeriod_Plot][SelectQobsNotZero & SelectQsimNotZero]), - log(OutputsModel$Qsim[IndPeriod_Plot][SelectQobsNotZero & SelectQsimNotZero]), + ylim <- log(range(c(Qobs[SelectQobsNotZero & SelectQsimNotZero], OutputsModel$Qsim[SelectQobsNotZero & SelectQsimNotZero]), na.rm = TRUE)) + plot(log(Qobs[SelectQobsNotZero & SelectQsimNotZero]), + log(OutputsModel$Qsim[SelectQobsNotZero & SelectQsimNotZero]), type = "p", pch = 1, cex = 0.9, col = par("fg"), lwd = lwd, xlim = ylim, ylim = ylim, xaxt = "n", yaxt = "n", xlab = "", ylab = "", ...) abline(a = 0, b = 1, col = "royalblue", lwd = lwd) @@ -916,7 +877,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = mtext(side = 2, paste("simulated flow", plotunit), line = line, cex = cex.lab) if (!is.null(BasinArea)) { Factor <- Factor_UNIT_M3S - axis(side = 4, at = seqDATA1, labels = round(seqDATA2*Factor, digits = 2), cex.axis = cex.axis, ...) + axis(side = 4, at = seqDATA1, labels = round(seqDATA2 * Factor, digits = 2), cex.axis = cex.axis, ...) mtext(side = 4, paste("simulated flow", "[m3/s]"), line = line, cex = cex.lab) } legend("bottomright", "log scale", lty = 1, col = NA, bty = "o", bg = bg, box.col = bg, cex = cex.leg) @@ -928,7 +889,7 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = } box() } - + ## Empty_plots if (exists("iPlotMax")) { while (kPlot < iPlotMax) { @@ -937,8 +898,6 @@ plot.OutputsModel <- function(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = plot(0, 0, type = "n", xlab = "", ylab = "", axes = FALSE, ...) } } - - ## Restoring_layout_options - # layout(1) - + + } diff --git a/man/plot.OutputsModel.Rd b/man/plot.OutputsModel.Rd index e9a9042a7279fce9baa7bc6a3492a9489d5ec046..10c033c9dffe48498a9a36c06c842031454aefc5 100644 --- a/man/plot.OutputsModel.Rd +++ b/man/plot.OutputsModel.Rd @@ -21,6 +21,7 @@ Function which creates a screen plot giving an overview of the model outputs. \method{plot}{OutputsModel}(x, Qobs = NULL, IndPeriod_Plot = NULL, BasinArea = NULL, which = "synth", log_scale = FALSE, cex.axis = 1, cex.lab = 0.9, cex.leg = 0.9, lwd = 1, + AxisTS = function(x) axis.POSIXct(side = 1, x = x$DatesR, ...), LayoutMat = NULL, LayoutWidths = rep.int(1, ncol(LayoutMat)), LayoutHeights = rep.int(1, nrow(LayoutMat)), @@ -49,6 +50,8 @@ Function which creates a screen plot giving an overview of the model outputs. \item{lwd}{(optional) [numeric] the line width (a positive number)} +\item{AxisTS}{(optional) [function] to manage x-axis representing calendar dates and times on time series plots (see \code{\link{axis}} and \code{\link{axis.POSIXct}})} + \item{LayoutMat}{(optional) [numeric] a matrix object specifying the location of the next N figures on the output device. Each value in the matrix must be 0 or a positive integer. If N is the largest positive integer in the matrix, then the integers {1, \dots, N-1} must also appear at least once in the matrix (see \code{\link{layout}})} \item{LayoutWidths}{(optional) [numeric] a vector of values for the widths of columns on the device (see \code{\link{layout}})}