diff --git a/.gitignore b/.gitignore index d03a49e67e3dfe20903567b7051f2064fad0c506..591c822411801ca32f1fd399c37977ec724b13ad 100644 --- a/.gitignore +++ b/.gitignore @@ -13,6 +13,4 @@ merge_output.txt master_pull.txt *.eps *.ps -*.gif -*.png Rplots.pdf diff --git a/R/Plot2VarsVsLTime.R b/R/Plot2VarsVsLTime.R index ab8ebe57ad51f558df89ec0652fc28b5a9212c12..b23a25ad161ab0924b07794e330adb98c5f35b9c 100644 --- a/R/Plot2VarsVsLTime.R +++ b/R/Plot2VarsVsLTime.R @@ -2,8 +2,9 @@ Plot2VarsVsLTime <- function(var1, var2, toptitle = '', ytitle = '', monini = 1, freq = 12, nticks = NULL, limits = NULL, listexp = c('exp1', 'exp2', 'exp3'), listvars = c('var1', 'var2'), biglab = FALSE, hlines = NULL, leg = TRUE, - siglev = FALSE, sizetit = 1, fileout = - 'output_plot2varsvsltime.eps', show_conf = TRUE, ...) { + siglev = FALSE, sizetit = 1, show_conf = TRUE, + fileout = 'output_plot2varsvsltime.eps', + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "fin", "lab", "las", "lty", "lwd", "mai", "mgp", "new", "pin", "ps", "pty") @@ -12,7 +13,7 @@ Plot2VarsVsLTime <- function(var1, var2, toptitle = '', ytitle = '', monini = 1, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -97,7 +98,12 @@ Plot2VarsVsLTime <- function(var1, var2, toptitle = '', ytitle = '', monini = 1, # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/PlotACC.R b/R/PlotACC.R index 6312b876a268b187d7c0592efe391b80b9151139..3f499e7157b31e49a6a93bd8948830c33dc587c2 100644 --- a/R/PlotACC.R +++ b/R/PlotACC.R @@ -1,7 +1,8 @@ PlotACC <- function(ACC, sdates, toptitle = "", sizetit = 1, ytitle = "", limits = NULL, legends = NULL, freq = 12, biglab = FALSE, fill = FALSE, linezero = FALSE, points = TRUE, vlines = NULL, - fileout = "output_PlotACC.eps", ...) { + fileout = "output_PlotACC.eps", + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "lab", "las", "lty", "lwd", "mai", "mgp", "new", "pch", "pin", "ps", "pty") @@ -10,7 +11,7 @@ PlotACC <- function(ACC, sdates, toptitle = "", sizetit = 1, ytitle = "", # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -51,7 +52,12 @@ PlotACC <- function(ACC, sdates, toptitle = "", sizetit = 1, ytitle = "", "mediumorchid1", "olivedrab1") # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/PlotAno.R b/R/PlotAno.R index 495ad6700636063ac23773035285938506ed6ad7..450f31d8505a283431d36994c0a81307b2f7a8d0 100644 --- a/R/PlotAno.R +++ b/R/PlotAno.R @@ -5,11 +5,11 @@ PlotAno <- function(exp_ano, obs_ano = NULL, sdates, '', '', ''), limits = NULL, legends = NULL, freq = 12, biglab = FALSE, fill = TRUE, memb = TRUE, ensmean = TRUE, linezero = FALSE, - points = FALSE, vlines = NULL, + points = FALSE, vlines = NULL, sizetit = 1, fileout = c('output1_plotano.eps', 'output2_plotano.eps', 'output3_plotano.eps', 'output4_plotano.eps', 'output5_plotano.eps'), - sizetit = 1, ...) { + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "fin", "lab", "las", "lty", "lwd", "mai", "mgp", "new", "pch", "pin", "ps", "pty") @@ -18,7 +18,7 @@ PlotAno <- function(exp_ano, obs_ano = NULL, sdates, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -102,7 +102,13 @@ PlotAno <- function(exp_ano, obs_ano = NULL, sdates, # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout[jexp], width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout[jexp]) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + + # Load the user parameters par(userArgs) diff --git a/R/PlotBoxWhisker.R b/R/PlotBoxWhisker.R index 1dec73faa8a0c01e74d7859f55e76b8716b46915..1bf41ff17536b462ee81ee643f2aa08215234a8a 100644 --- a/R/PlotBoxWhisker.R +++ b/R/PlotBoxWhisker.R @@ -1,7 +1,8 @@ PlotBoxWhisker <- function(exp, obs, toptitle = '', ytitle = '', monini = 1, yearini = 0, freq = 1, expname = "exp 1", obsname = "obs 1", drawleg = TRUE, - fileout = "output_PlotBoxWhisker.ps", ...) { + fileout = "output_PlotBoxWhisker.ps", + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude @@ -11,7 +12,7 @@ PlotBoxWhisker <- function(exp, obs, toptitle = '', ytitle = '', monini = 1, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -91,7 +92,12 @@ PlotBoxWhisker <- function(exp, obs, toptitle = '', ytitle = '', monini = 1, } # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/PlotClim.R b/R/PlotClim.R index 80b45ddb65f48cb22d9308c33b36b129ff02b7cf..7ce30c0dbcb360b70eacdac85493f05dc97bfe9e 100644 --- a/R/PlotClim.R +++ b/R/PlotClim.R @@ -1,8 +1,9 @@ PlotClim <- function(exp_clim, obs_clim = NULL, toptitle = '', ytitle = '', monini = 1, freq = 12, limits = NULL, listexp = c('exp1', 'exp2', 'exp3'), - listobs = c('obs1', 'obs2', 'obs3'), biglab = FALSE, leg = TRUE, - fileout = 'output_plotclim.eps', sizetit = 1, ...) { + listobs = c('obs1', 'obs2', 'obs3'), biglab = FALSE, + leg = TRUE, sizetit = 1, fileout = 'output_plotclim.eps', + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "fin", "lab", "las", "lty", "lwd", "mai", "mgp", "new", "pin", "ps", "pty", "tcl") @@ -11,7 +12,7 @@ PlotClim <- function(exp_clim, obs_clim = NULL, toptitle = '', ytitle = '', # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -89,7 +90,12 @@ PlotClim <- function(exp_clim, obs_clim = NULL, toptitle = '', ytitle = '', # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/PlotEquiMap.R b/R/PlotEquiMap.R index bfe35716064d4088773f479238c11d412dd8c488..dea625df467a81c26fb406e476e3b3036eaf306e 100644 --- a/R/PlotEquiMap.R +++ b/R/PlotEquiMap.R @@ -23,7 +23,9 @@ PlotEquiMap <- function(var, lon, lat, varu = NULL, varv = NULL, bar_extra_margin = rep(0, 4), boxlim = NULL, boxcol = 'purple2', boxlwd = 5, margin_scale = rep(1, 4), title_scale = 1, - numbfig = NULL, fileout = NULL, ...) { + numbfig = NULL, fileout = NULL, + width = 8, height = 5, size_units = 'in', + res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "din", "fig", "fin", "lab", "las", "lty", "lwd", "mai", "mar", "mgp", "new", "oma", "ps", "tck") @@ -32,7 +34,7 @@ PlotEquiMap <- function(var, lon, lat, varu = NULL, varv = NULL, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -402,7 +404,11 @@ PlotEquiMap <- function(var, lon, lat, varu = NULL, varv = NULL, # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } # # Defining the layout diff --git a/R/PlotLayout.R b/R/PlotLayout.R index 1b04b4cde6d70007daeecbab55c2622a45c95145..36719d6d8505c16e359f22705dea0cbc6ebd0d9e 100644 --- a/R/PlotLayout.R +++ b/R/PlotLayout.R @@ -15,11 +15,11 @@ PlotLayout <- function(fun, plot_dims, var, ..., special_args = NULL, bar_left_shift_scale = 1, bar_label_digits = 4, extra_margin = rep(0, 4), fileout = NULL, width = NULL, height = NULL, - close_device = TRUE) { + size_units = 'in', res = 100, close_device = TRUE) { # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -280,12 +280,13 @@ PlotLayout <- function(fun, plot_dims, var, ..., special_args = NULL, # Open connection to graphical device if (!is.null(fileout)) { - saveToFile(fileout, width = width, height = height) + saveToFile(fileout) } else if (names(dev.cur()) == 'null device') { - dev.new(width = width, height = height) + dev.new(units = size_units, res = res, width = width, height = height) } else if (prod(par('mfrow')) > 1) { - dev.new(width = width, height = height) + dev.new(units = units, res = res, width = width, height = height) } + # Take size of device and set up layout: # --------------------------------------------- # |0000000000000000000000000000000000000000000| @@ -382,13 +383,13 @@ PlotLayout <- function(fun, plot_dims, var, ..., special_args = NULL, width_lines <- par('fin')[1] / par('csi') plot_lines <- par('pin')[1] / par('csi') plot_range <- par('xaxp')[2] - par('xaxp')[1] - plot_units_per_line <- plot_range / plot_lines + size_units_per_line <- plot_range / plot_lines if (toptitle != '') { - title_x_center <- par('xaxp')[1] - par('mar')[2] * plot_units_per_line + - ncol * width_lines * plot_units_per_line / 2 + title_x_center <- par('xaxp')[1] - par('mar')[2] * size_units_per_line + + ncol * width_lines * size_units_per_line / 2 if (length(row_titles) > 0) { title_x_center <- title_x_center - (1 - title_left_shift_scale) * - (subtitle_cex + subtitle_margin) / 2 * plot_units_per_line + (subtitle_cex + subtitle_margin) / 2 * size_units_per_line } title_y_center <- par('mar')[3] + (title_margin + title_cex) / 2 if (length(col_titles > 0)) { @@ -398,24 +399,24 @@ PlotLayout <- function(fun, plot_dims, var, ..., special_args = NULL, padj = 0.5) } if (length(col_titles) > 0) { - t_x_center <- par('xaxp')[1] - par('mar')[2] * plot_units_per_line + t_x_center <- par('xaxp')[1] - par('mar')[2] * size_units_per_line for (t in 1:ncol) { mtext(col_titles[t], cex = subtitle_cex, line = par('mar')[3] + (subtitle_margin + subtitle_cex) / 2, - at = t_x_center + (t - 0.5) * width_lines * plot_units_per_line, + at = t_x_center + (t - 0.5) * width_lines * size_units_per_line, padj = 0.5) } } height_lines <- par('fin')[2] / par('csi') plot_lines <- par('pin')[2] / par('csi') plot_range <- par('yaxp')[2] - par('yaxp')[1] - plot_units_per_line <- plot_range / plot_lines + size_units_per_line <- plot_range / plot_lines if (length(row_titles) > 0) { - t_y_center <- par('yaxp')[1] - par('mar')[1] * plot_units_per_line + t_y_center <- par('yaxp')[1] - par('mar')[1] * size_units_per_line for (t in 1:nrow) { mtext(row_titles[t], cex = subtitle_cex, line = par('mar')[2] + (subtitle_margin + subtitle_cex) / 2, - at = t_y_center - (t - 1.5) * height_lines * plot_units_per_line, + at = t_y_center - (t - 1.5) * height_lines * size_units_per_line, padj = 0.5, side = 2) } } diff --git a/R/PlotSection.R b/R/PlotSection.R index c8f4df740d067f3ff392ab78d5d818110600a3e6..acefbdd8e55b2a532c47cec3e32216465a4aa940 100644 --- a/R/PlotSection.R +++ b/R/PlotSection.R @@ -1,7 +1,8 @@ PlotSection <- function(var, horiz, depth, toptitle = '', sizetit = 1, units = '', brks = NULL, cols = NULL, axelab = TRUE, intydep = 200, intxhoriz = 20, drawleg = TRUE, - fileout = NULL, ...) { + fileout = NULL, width = 8, height = 5, + size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.main", "col", "lab", "las", "mai", "mar", "mgp", "new", "ps", "tck") @@ -10,7 +11,7 @@ PlotSection <- function(var, horiz, depth, toptitle = '', sizetit = 1, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -67,7 +68,12 @@ PlotSection <- function(var, horiz, depth, toptitle = '', sizetit = 1, # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/PlotStereoMap.R b/R/PlotStereoMap.R index 74d8707ee2e168af499a23ce231c3e1e11d795e6..656d5e1bc70077f35cdefa0115ecaff7c3da91da 100644 --- a/R/PlotStereoMap.R +++ b/R/PlotStereoMap.R @@ -15,7 +15,9 @@ PlotStereoMap <- function(var, lon, lat, latlims = c(60, 90), bar_extra_margin = rep(0, 4), boxlim = NULL, boxcol = "purple2", boxlwd = 5, margin_scale = rep(1, 4), title_scale = 1, - numbfig = NULL, fileout = NULL, ...) { + numbfig = NULL, fileout = NULL, + width = 8, height = 5, size_units = 'in', + res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.main", "col", "fin", "lab", "las", "lwd", "mai", "mar", "mgp", "new", "pch", "ps") @@ -24,7 +26,7 @@ PlotStereoMap <- function(var, lon, lat, latlims = c(60, 90), # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -256,7 +258,11 @@ PlotStereoMap <- function(var, lon, lat, latlims = c(60, 90), # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } # # Defining the layout diff --git a/R/PlotVsLTime.R b/R/PlotVsLTime.R index bd48aa7c42894274c3f5a4a244cae196e6efff63..dd068adc1dfbcad141d517e7f50a2c30f86493c1 100644 --- a/R/PlotVsLTime.R +++ b/R/PlotVsLTime.R @@ -2,8 +2,9 @@ PlotVsLTime <- function(var, toptitle = '', ytitle = '', monini = 1, freq = 12, nticks = NULL, limits = NULL, listexp = c('exp1', 'exp2', 'exp3'), listobs = c('obs1', 'obs2', 'obs3'), biglab = FALSE, hlines = NULL, - leg = TRUE, siglev = FALSE, fileout = 'output_plotvsltime.eps', - sizetit = 1, show_conf = TRUE, ...) { + leg = TRUE, siglev = FALSE, sizetit = 1, show_conf = TRUE, + fileout = 'output_plotvsltime.eps', + width = 8, height = 5, size_units = 'in', res = 100, ...) { # Process the user graphical parameters that may be passed in the call ## Graphical parameters to exclude excludedArgs <- c("cex", "cex.axis", "cex.lab", "cex.main", "col", "fin", "lab", "las", "lend", "lty", "lwd", "mai", "mgp", "new", "pin", "ps", "pty") @@ -12,7 +13,7 @@ PlotVsLTime <- function(var, toptitle = '', ytitle = '', monini = 1, freq = 12, # If there is any filenames to store the graphics, process them # to select the right device if (!is.null(fileout)) { - deviceInfo <- .SelectDevice(fileout) + deviceInfo <- .SelectDevice(fileout = fileout, width = width, height = height, units = size_units, res = res) saveToFile <- deviceInfo$fun fileout <- deviceInfo$files } @@ -23,6 +24,8 @@ PlotVsLTime <- function(var, toptitle = '', ytitle = '', monini = 1, freq = 12, # if (length(dim(var)) == 3) { var <- InsertDim(var, posdim = 2, lendim = 1) + } else if (length(dim(var)) != 4) { + stop("Parameter 'var' should have 3 or 4 dimensions: c(n. exp[, n. obs], 3/4, n. lead-times)") } nleadtime <- dim(var)[4] nexp <- dim(var)[1] @@ -86,7 +89,12 @@ PlotVsLTime <- function(var, toptitle = '', ytitle = '', monini = 1, freq = 12, # # Open connection to graphical device - if (!is.null(fileout)) saveToFile(fileout, width = 11, height = 8) + if (!is.null(fileout)) { + saveToFile(fileout) + } else if (names(dev.cur()) == 'null device') { + dev.new(units = size_units, res = res, width = width, height = height) + } + # Load the user parameters par(userArgs) diff --git a/R/Utils.R b/R/Utils.R index 9c73fa5f783d2fab507ef571d888ff3383080ca7..61ad17798fc143e9b72ae1874f15cd285fa08724 100644 --- a/R/Utils.R +++ b/R/Utils.R @@ -1116,7 +1116,7 @@ userArgs } -.SelectDevice <- function(fileout) { +.SelectDevice <- function(fileout, width, height, units, res) { # This function is used in the plot functions to check the extension of the # files where the graphics will be stored and select the right R device to # save them. @@ -1131,35 +1131,41 @@ # If there is an extension specified, select the correct device ## units of width and height set to accept inches if (ext[1] == ".png") { - saveToFile <- function(...) { - png(units = "in", res = 100, ...) + saveToFile <- function(fileout) { + png(filename = fileout, width = width, height = height, res = res, units = units) } } else if (ext[1] == ".jpeg") { - saveToFile <- function(...) { - jpeg(units = "in", res = 100, ...) - } - } else if (ext[1] == ".eps") { - saveToFile <- postscript - } else if (ext[1] == ".ps") { - saveToFile <- postscript + saveToFile <- function(fileout) { + jpeg(filename = fileout, width = width, height = height, res = res, units = units) + } + } else if (ext[1] %in% c(".eps", ".ps")) { + saveToFile <- function(fileout) { + postscript(file = fileout, width = width, height = height) + } } else if (ext[1] == ".pdf") { - saveToFile <- pdf + saveToFile <- function(fileout) { + pdf(file = fileout, width = width, height = height) + } } else if (ext[1] == ".svg") { - saveToFile <- svg + saveToFile <- function(fileout) { + svg(filename = fileout, width = width, height = height) + } } else if (ext[1] == ".bmp") { - saveToFile <- function(...) { - bmp(units = "in", res = 100, ...) - } + saveToFile <- function(fileout) { + bmp(filename = fileout, width = width, height = height, res = res, units = units) + } } else if (ext[1] == ".tiff") { - saveToFile <- function(...) { - tiff(units = "in", res = 100, ...) - } + saveToFile <- function(fileout) { + tiff(filename = fileout, width = width, height = height, res = res, units = units) + } } else { .warning("file extension not supported, it will be used '.eps' by default.") ## In case there is only one filename fileout[1] <- sub("\\.[a-zA-Z0-9]*$", ".eps", fileout[1]) ext[1] <- ".eps" - saveToFile <- postscript + saveToFile <- function(fileout) { + postscript(file = fileout, width = width, height = height) + } } # Change filenames when necessary if (any(ext != ext[1])) { diff --git a/man/Plot2VarsVsLTime.Rd b/man/Plot2VarsVsLTime.Rd index 91b57c6266af8d4fc1dcfd3def9efc9502430cf2..faeaed7961bbfb9dff754629ed460245bc3a1ae8 100644 --- a/man/Plot2VarsVsLTime.Rd +++ b/man/Plot2VarsVsLTime.Rd @@ -13,8 +13,9 @@ Plot2VarsVsLTime(var1, var2, toptitle = "", ytitle = "", monini = 1, freq = 12, nticks = NULL, limits = NULL, listexp = c("exp1", "exp2", "exp3"), listvars = c("var1", "var2"), biglab = FALSE, hlines = NULL, - leg = TRUE, siglev = FALSE, sizetit = 1, - fileout = "output_plot2varsvsltime.eps", show_conf = TRUE, ...) + leg = TRUE, siglev = FALSE, sizetit = 1, show_conf = TRUE, + fileout = "output_plot2varsvsltime.eps", + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{var1}{ @@ -63,14 +64,26 @@ Default = FALSE. } \item{sizetit}{ Multiplicative factor to change title size, optional. + } + \item{show_conf}{ +TRUE/FALSE to show/not confidence intervals for input variables. } \item{fileout}{ Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr Default = 'output_plot2varsvsltime.eps' } - \item{show_conf}{ -TRUE/FALSE to show/not confidence intervals for input variables. + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{...}{ Arguments to be passed to the method. Only accepts the following diff --git a/man/PlotACC.Rd b/man/PlotACC.Rd index 9489413abe0ea30bd225d7e49895b6f3d034612d..21cfd80a8fae8f5888976656e2956f4ed1b3fb2a 100644 --- a/man/PlotACC.Rd +++ b/man/PlotACC.Rd @@ -12,7 +12,8 @@ with the fourth dimension of length 4 containing the lower limit of the 95\% con PlotACC(ACC, sdates, toptitle = "", sizetit = 1, ytitle = "", limits = NULL, legends = NULL, freq = 12, biglab = FALSE, fill = FALSE, linezero = FALSE, points = TRUE, vlines = NULL, - fileout = "output_PlotACC.eps", ...) + fileout = "output_PlotACC.eps", + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{ACC}{ @@ -61,6 +62,18 @@ List of x location where to add vertical black lines, optional. Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr Default = 'output_PlotACC.eps' + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{...}{ Arguments to be passed to the method. Only accepts the following diff --git a/man/PlotAno.Rd b/man/PlotAno.Rd index 5699e362cff96973e4aec58126749907bfac3b1b..ec3d6de74935c5d5e458846449647f6a3de05d7a 100644 --- a/man/PlotAno.Rd +++ b/man/PlotAno.Rd @@ -14,9 +14,9 @@ PlotAno(exp_ano, obs_ano = NULL, sdates, toptitle = c("", "", "", "", "", "", "", "", "", "", "", "", "", "", "", ""), limits = NULL, legends = NULL, freq = 12, biglab = FALSE, fill = TRUE, memb = TRUE, ensmean = TRUE, linezero = FALSE, points = FALSE, vlines = NULL, - fileout = c("output1_plotano.eps", "output2_plotano.eps", + sizetit = 1, fileout = c("output1_plotano.eps", "output2_plotano.eps", "output3_plotano.eps", "output4_plotano.eps", "output5_plotano.eps"), - sizetit = 1, ...) + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{exp_ano}{ @@ -66,6 +66,9 @@ TRUE/FALSE if points instead of lines should be shown. Default = FALSE. } \item{vlines}{ List of x location where to add vertical black lines, optional. + } + \item{sizetit}{ +Multiplicative factor to scale title size, optional. } \item{fileout}{ Name of the output file for each experiment: c('',''). @@ -76,8 +79,17 @@ Default = c('output1_plotano.eps', 'output2_plotano.eps', 'output3_plotano.eps', 'output4_plotano.eps', 'output5_plotano.eps') } - \item{sizetit}{ -Multiplicative factor to scale title size, optional. + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{...}{ Arguments to be passed to the method. Only accepts the following diff --git a/man/PlotBoxWhisker.Rd b/man/PlotBoxWhisker.Rd index 304221015573853bab7402a70a5951e379c6e7a7..31d11d9e00644b84ab8dcf744b7dff4926b94a77 100644 --- a/man/PlotBoxWhisker.Rd +++ b/man/PlotBoxWhisker.Rd @@ -12,7 +12,8 @@ n-monthly to n-yearly time series. \usage{ PlotBoxWhisker(exp, obs, toptitle = '', ytitle = '', monini = 1, yearini = 0, freq = 1, expname = "exp 1", obsname = "obs 1", drawleg = TRUE, - fileout = "output_PlotBoxWhisker.ps", ...) + fileout = "output_PlotBoxWhisker.ps", + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{exp}{ @@ -58,6 +59,18 @@ TRUE/FALSE: whether to draw the legend or not. Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr Default = 'output_PlotBox.ps' + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{...}{ Arguments to be passed to the method. Only accepts the following diff --git a/man/PlotClim.Rd b/man/PlotClim.Rd index e95602d4a05159c6f9176d7bb44d1e42419d7fbd..6840386657c5fb56592d5f20d9f5a7818f4bb525 100644 --- a/man/PlotClim.Rd +++ b/man/PlotClim.Rd @@ -12,7 +12,8 @@ Plots climatologies as a function of the forecast time for any index output from PlotClim(exp_clim, obs_clim = NULL, toptitle = "", ytitle = "", monini = 1, freq = 12, limits = NULL, listexp = c("exp1", "exp2", "exp3"), listobs = c("obs1", "obs2", "obs3"), biglab = FALSE, leg = TRUE, - fileout = "output_plotclim.eps", sizetit = 1, ...) + sizetit = 1, fileout = "output_plotclim.eps", + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{exp_clim}{ @@ -50,13 +51,25 @@ TRUE/FALSE for presentation/paper plot. Default = FALSE. \item{leg}{ TRUE/FALSE to plot the legend or not. } - \item{fileout}{ + \item{sizetit}{ +Multiplicative factor to scale title size, optional. + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. + } + \item{fileout}{ Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr Default = 'output_plotclim.eps' - } - \item{sizetit}{ -Multiplicative factor to scale title size, optional. } \item{...}{ Arguments to be passed to the method. Only accepts the following diff --git a/man/PlotEquiMap.Rd b/man/PlotEquiMap.Rd index 55eec3992bd0f3843ef3d60364921f45fbdc92bb..9ba2ca4909ffdcb5da86232d6ffa99437ac14366 100644 --- a/man/PlotEquiMap.Rd +++ b/man/PlotEquiMap.Rd @@ -32,7 +32,8 @@ PlotEquiMap(var, lon, lat, varu = NULL, varv = NULL, bar_extra_margin = rep(0, 4), boxlim = NULL, boxcol = 'purple2', boxlwd = 5, margin_scale = rep(1, 4), title_scale = 1, - numbfig = NULL, fileout = NULL, ...) + numbfig = NULL, fileout = NULL, + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{var}{ @@ -169,6 +170,18 @@ Number of figures in the layout the plot will be put into. A higher numbfig will } \item{fileout}{ File where to save the plot. If not specified (default) a graphics device will pop up. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{\dots}{ Arguments to be passed to the method. Only accepts the following graphical parameters: diff --git a/man/PlotLayout.Rd b/man/PlotLayout.Rd index 54e03d3d8ffe7cd6bafedb368479cb31149e3688..c36e7fdb041462de23bf289cf18c821ded8ad264 100644 --- a/man/PlotLayout.Rd +++ b/man/PlotLayout.Rd @@ -25,7 +25,7 @@ PlotLayout(fun, plot_dims, var, ..., special_args = NULL, bar_left_shift_scale = 1, bar_label_digits = 4, extra_margin = rep(0, 4), fileout = NULL, width = NULL, height = NULL, - close_device = TRUE) + size_units = 'in', res = 100, close_device = TRUE) } \arguments{ \item{fun}{ @@ -112,6 +112,12 @@ Width in inches of the multi-pannel. 7 by default, or 11 if 'fielout' has been s } \item{height}{ Height in inches of the multi-pannel. 7 by default, or 11 if 'fileout' has been specified. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{close_device}{ Whether to close the graphics device after plotting the layout and a 'fileout' has been specified. This is useful to avoid closing the device when saving the layout into a file and willing to add extra elements or figures. Takes TRUE by default. Disregarded if no 'fileout' has been specified. diff --git a/man/PlotSection.Rd b/man/PlotSection.Rd index d02df3ece73e356988129598a31b31a5868be9aa..f7f3349f9e0d2e58e108edeb5d30229593e863ba 100644 --- a/man/PlotSection.Rd +++ b/man/PlotSection.Rd @@ -9,7 +9,8 @@ Plot a (longitude,depth) or (latitude,depth) section. \usage{ PlotSection(var, horiz, depth, toptitle = "", sizetit = 1, units = "", brks = NULL, cols = NULL, axelab = TRUE, intydep = 200, - intxhoriz = 20, drawleg = TRUE, fileout = NULL, ...) + intxhoriz = 20, drawleg = TRUE, fileout = NULL, + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{var}{ @@ -48,6 +49,18 @@ Default: 20deg. } \item{drawleg}{ Draw colorbar. Default: TRUE. + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{fileout}{ Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp diff --git a/man/PlotStereoMap.Rd b/man/PlotStereoMap.Rd index 1f6a4f6e4813130d5211f0b2d735981917bb3cbd..32478843ce5bbf8924ebe78469622465f65924a1 100644 --- a/man/PlotStereoMap.Rd +++ b/man/PlotStereoMap.Rd @@ -24,7 +24,8 @@ PlotStereoMap(var, lon, lat, latlims = c(60, 90), bar_extra_margin = rep(0, 4), boxlim = NULL, boxcol = "purple2", boxlwd = 5, margin_scale = rep(1, 4), title_scale = 1, - numbfig = NULL, fileout = NULL, ...) + numbfig = NULL, fileout = NULL, width = 8, height = 5, + size_units = 'in', res = 100, ...) } \arguments{ \item{var}{ @@ -103,6 +104,18 @@ Number of figures in the layout the plot will be put into. A higher numbfig will } \item{fileout}{ File where to save the plot. If not specified (default) a graphics device will pop up. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff. \cr + } + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. + } + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{\dots}{ Arguments to be passed to the method. Only accepts the following graphical parameters: diff --git a/man/PlotVsLTime.Rd b/man/PlotVsLTime.Rd index 6ce6edd633da8405a083ec5941e02740ba2a0788..cebb9e50f8b1069e83dfd52898e0cafa504945b2 100644 --- a/man/PlotVsLTime.Rd +++ b/man/PlotVsLTime.Rd @@ -10,8 +10,9 @@ Plots The Correlation (\code{Corr()}) or the Root Mean Square Error (\code{RMS() PlotVsLTime(var, toptitle = "", ytitle = "", monini = 1, freq = 12, nticks = NULL, limits = NULL, listexp = c("exp1", "exp2", "exp3"), listobs = c("obs1", "obs2", "obs3"), biglab = FALSE, hlines = NULL, - leg = TRUE, siglev = FALSE, fileout = "output_plotvsltime.eps", - sizetit = 1, show_conf = TRUE, ...) + leg = TRUE, siglev = FALSE, sizetit = 1, show_conf = TRUE, + fileout = "output_plotvsltime.eps", + width = 8, height = 5, size_units = 'in', res = 100, ...) } \arguments{ \item{var}{ @@ -56,17 +57,29 @@ TRUE/FALSE if legend should be added or not to the plot. Default = TRUE. \item{siglev}{ TRUE/FALSE if significance level should replace confidence interval.\cr Default = FALSE. + } + \item{sizetit}{ +Multiplicative factor to change title size, optional. + } + \item{show_conf}{ +TRUE/FALSE to show/not confidence intervals for input variables. } \item{fileout}{ Name of output file. Extensions allowed: eps/ps, jpeg, png, pdf, bmp and tiff.\cr Default = 'output_plotvsltime.eps' } - \item{sizetit}{ -Multiplicative factor to change title size, optional. + \item{width}{ +File width, in the units specified in the parameter size_units (inches by default). Takes 8 by default. } - \item{show_conf}{ -TRUE/FALSE to show/not confidence intervals for input variables. + \item{height}{ +File height, in the units specified in the parameter size_units (inches by default). Takes 5 by default. + } + \item{size_units}{ +Units of the size of the device (file or window) to plot in. Inches ('in') by default. See ?Devices and the creator function of the corresponding device. + } + \item{res}{ +Resolution of the device (file or window) to plot in. See ?Devices and the creator function of the corresponding device. } \item{...}{ Arguments to be passed to the method. Only accepts the following