From 0a90ec94e61b33674d714450f1c6eabf7dd27bef Mon Sep 17 00:00:00 2001 From: Raimon Tolosana <r.tolosana@hzdr.de> Date: Mon, 17 Apr 2023 18:46:25 +0200 Subject: [PATCH] minor changes towards v. 0.11.3 for CRAN --- .Rbuildignore | 1 + DESCRIPTION | 6 +- NAMESPACE | 5 + NEWS.md | 1 + R/Anamorphosis.R | 3 +- R/accuracy.R | 17 ++- R/compositionsCompatibility.R | 14 ++- R/data.R | 2 +- R/exploratools.R | 15 +-- R/gmSimulation.R | 4 +- R/gmSpatialModel.R | 10 +- R/grids.R | 3 + R/gstatCompatibility.R | 5 +- R/mask.R | 5 +- R/variograms.R | 50 +++++--- cran-comments.md | 151 +++++++++++++++++------- vignettes/SimulatingMicrostructures.Rmd | 2 +- 17 files changed, 199 insertions(+), 95 deletions(-) diff --git a/.Rbuildignore b/.Rbuildignore index f083d49..a4a7560 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -15,3 +15,4 @@ jurapred ^README\.Rmd$ ^.*\.vscode$ ^revdep$ +^\./vignettes/SimulatingMicrostructures\.Rmd$ diff --git a/DESCRIPTION b/DESCRIPTION index c6be49b..56e030c 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: gmGeostats Version: 0.11.3 -Date: 2023-04-13 +Date: 2023-04-17 Title: Geostatistics for Compositional Analysis Authors@R: c(person(given = "Raimon", family = "Tolosana-Delgado", @@ -43,8 +43,8 @@ Imports: utils, RColorBrewer Description: Support for geostatistical analysis of multivariate data, - in particular data with restrictions, e.g. positive amounts data, - compositional data, distributional data, microstructural data, etc. + in particular data with restrictions, e.g. positive amounts, + compositions, distributional data, microstructural data, etc. It includes descriptive analysis and modelling for such data, both from a two-point Gaussian perspective and multipoint perspective. The methods mainly follow Tolosana-Delgado, Mueller and van den diff --git a/NAMESPACE b/NAMESPACE index 7dc1d88..70940ac 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -41,11 +41,15 @@ S3method(as.LMCAnisCompo,gmCgram) S3method(as.LMCAnisCompo,gstat) S3method(as.LMCAnisCompo,variogramModelList) S3method(as.array,DataFrameStack) +S3method(as.directorVector,azimuth) +S3method(as.directorVector,azimuthInterval) +S3method(as.directorVector,default) S3method(as.function,gmCgram) S3method(as.gmCgram,LMCAnisCompo) S3method(as.gmCgram,default) S3method(as.gmCgram,variogramModel) S3method(as.gmCgram,variogramModelList) +S3method(as.gmEVario,default) S3method(as.gmEVario,gstatVariogram) S3method(as.gmEVario,logratioVariogram) S3method(as.gmEVario,logratioVariogramAnisotropy) @@ -184,6 +188,7 @@ export(as.AnisotropyScaling) export(as.CompLinModCoReg) export(as.DataFrameStack) export(as.LMCAnisCompo) +export(as.directorVector) export(as.gmCgram) export(as.gmEVario) export(as.gmSpatialModel) diff --git a/NEWS.md b/NEWS.md index cf2cff7..f0a7ed0 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,6 @@ # gmGeostats 0.11.3 +* (2023-04-17) functions producing multiple plots now restore the graphical parameters to initial state if terminated; minor corrections to help files; stub vignette "Simulating microstructures with gmGeostats" is not packaged any more with gmGeostats to CRAN, but can be found here (until it is finished) * (2023-04-13) batch of hidden methods exported to the namespace (mostly for `as.*()` functions converting between different representations of empirical variograms and of geostatistical models) * (2023-04-04) C routines called as symbols and not name strings; non-ASCII characters removed diff --git a/R/Anamorphosis.R b/R/Anamorphosis.R index e6a81df..43b984e 100644 --- a/R/Anamorphosis.R +++ b/R/Anamorphosis.R @@ -268,12 +268,13 @@ anaBackward <- function(x,Y,sigma0,sigma1=1+sigma0,steps=30,plt=FALSE,sphere=TRU #' library(compositions) #' data("jura", package="gstat") #' Y = acomp(jura.pred[,c(10,12,13)]) -#' par(mfrow=c(1,1)) +#' oldpar = par(mfrow = c(1,1)) #' plot(Y) #' sph = sphTrans(Y) #' class(sph) #' z = sph(Y) #' plot(z) +#' par(oldpar) #' cor(cbind(z, ilr(Y))) #' colMeans(cbind(z, ilr(Y))) sphTrans <- function(Y,...) UseMethod("sphTrans",Y) diff --git a/R/accuracy.R b/R/accuracy.R index eb13e61..a00c171 100644 --- a/R/accuracy.R +++ b/R/accuracy.R @@ -311,6 +311,10 @@ precision.accuracy <- function(x, ...){ plot.accuracy <- function(x, xlim=c(0,1), ylim=c(0,1), xaxs="i", yaxs="i", type="o", col="red", asp=1, xlab="confidence", ylab="coverage", pty="s", main="accuracy plot", colref=col[1], ...){ + + oldpar <- par(no.readonly = TRUE) + on.exit(par(oldpar)) + par(pty=pty) plot(x$p, x$accuracy, xaxs=xaxs, yaxs=yaxs, xlim=xlim, ylim=ylim, type=type, col=col, asp=asp, xlab=xlab, ylab=ylab, main=main, ...) @@ -338,7 +342,18 @@ xvErrorMeasures <- function(x,...) UseMethod("xvErrorMeasures", x) #' @param output which output do you want? a vector of one or several of c("ME","MSE","MSDR","Mahalanobis") #' @param ... extra arguments for generic functionality #' +#' @return If just some of c("ME","MSE","MSDR") are requested, the output is a named +#' vector with the desired quantities. If only "Mahalanobis" is requested, the output is a vector +#' of Mahalanobis square errors. If you mix up things and ask for "Mahalanobis" and some of +#' the quantities mentioned above, the result will be a named list with the requested quantities. #' +#' @details "ME" stands for *mean error* (average of the differences between true values and predicted values), +#' "MSE" stands for *mean square error* (average of the square differences between true values and predicted values), +#' and "MSDR" for *mean squared deviation ratio* (average of the square between true values and predicted values +#' each normalized by its kriging variance). These quantities are classically used in evaluating +#' output results of validation exercises of one single variable. +#' For multivariate cases, see [xvErrorMeasures.data.frame()]. +#' #' @export #' @method xvErrorMeasures default #' @family accuracy functions @@ -378,7 +393,7 @@ xvErrorMeasures.default <- function(x, krigVar, observed, output="MSDR1", ...){ #' "MSE" stands for *mean square error* (average of the square differences between true values and predicted values), #' and "MSDR" for *mean squared deviation ratio* (average of the square between true values and predicted values #' each normalized by its kriging variance). These quantities are classically used in evaluating -#' output results of validation excercices of one single variable. +#' output results of validation exercises of one single variable. #' For multivariate cases, "ME" (a vector) and "MSE" (a scalar) work as well, #' while two different definitions of a multivariate #' mean squared deviation ratio can be given: diff --git a/R/compositionsCompatibility.R b/R/compositionsCompatibility.R index 7af1848..ada9ee0 100644 --- a/R/compositionsCompatibility.R +++ b/R/compositionsCompatibility.R @@ -306,7 +306,9 @@ logratioVariogram1 = function(comp, loc, maxdist=max(dist(loc))/2, #' @param ... additional arguments for generic functionality (currently ignored) #' #' @return This function is called for its effect of producing a figure. -#' Additionally, the graphical parameters active *prior to calling this function* are returned invisibly. +#' Additionally, the graphical parameters active *prior to calling this function* are +#' returned invisibly. +#' #' @export #' #' @examples @@ -323,7 +325,9 @@ image.logratioVariogramAnisotropy = function(x, jointColor=FALSE, breaks=NULL, probs = seq(0,1,0.1), col = spectralcolors, ...){ lrvg = x - o = par() + opar = par(no.readonly = TRUE) + on.exit(opar) + # construct the polar grid r = attr(lrvg, "lags") rlim = range(r) @@ -368,7 +372,7 @@ image.logratioVariogramAnisotropy = function(x, jointColor=FALSE, breaks=NULL, } } }} - invisible(o) + invisible(opar) } ################################################# @@ -480,9 +484,7 @@ plot.logratioVariogramAnisotropy = function(x, azimuths=colnames(x), } # set the matrix of figures - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) diff --git a/R/data.R b/R/data.R index 707db27..7bb5178 100644 --- a/R/data.R +++ b/R/data.R @@ -260,8 +260,8 @@ getTellus <- function(wd=".", destfile = "TellusASoil.RData" , TI = FALSE, clean success = FALSE wd0 = getwd() - setwd(wd) on.exit(setwd(wd0)) + setwd(wd) if(is.logical(TI)){ TIfile = "Tellus_TI.RData" diff --git a/R/exploratools.R b/R/exploratools.R index fb33fac..5c48d9e 100644 --- a/R/exploratools.R +++ b/R/exploratools.R @@ -89,9 +89,7 @@ pwlrmap = function(loc, # XY coordinates (matrix or data frame) ){ # set of maps where the symbols are chosen according to each possible pwlr, in # a scale given by the user - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) # dimensions D = ncol(comp) @@ -226,8 +224,7 @@ pairsmap.default <- function(data, # data to represent closeplot=TRUE, ... ){ - opar = par() - opar = par_remove_readonly(opar) + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) # dimensions D = ncol(data) @@ -427,9 +424,7 @@ swath.default <- function(data, # data (matrix, rmult, aplus, rplus or data.fra if(is(data, "Spatial")) return(swath_SpatialPointsDataFrame(data=data, loc=loc, pch=pch, xlab=xlab, mfrow=mfrow, withLoess=withLoess, commonScale=commonScale, ...)) # preparations - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) on.exit(par(opar)) col0 = spectralcolors(10)[10] @@ -498,9 +493,7 @@ swath.acomp <- function(data, # composition (rcomp, acomp, ccomp) # set of swath plots for each possible pwlr, eventually with a loess line # preparations - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) on.exit(par(opar)) col0 = spectralcolors(10)[10] comp = data diff --git a/R/gmSimulation.R b/R/gmSimulation.R index 6762513..63d12bb 100644 --- a/R/gmSimulation.R +++ b/R/gmSimulation.R @@ -96,7 +96,7 @@ gsi.DS4CoDa <- function(n, f, t, n_realiz, nx_TI, ny_TI, nx_SimGrid, ny_SimGrid, #pb = list() #myfun = function(ii){ for(ii in 1:n_realiz){ - cat(paste("\n Realization number #",ii, "\n")) + message(paste("\n Realization number #",ii)) # Defining a fully random path for simulation list_sim <- which(maskArray[,,1] & is.na(SimGrid_ilr_list[[ii]][,,1]), arr.ind = TRUE) @@ -330,7 +330,7 @@ gsi.DS <- function(n, f, t, n_realiz, #pb = list() #myfun = function(ii){ for(ii in 1:n_realiz){ - cat(paste("\n Realization number #",ii, "\n")) + message(paste("\n Realization number #",ii)) # Defining a fully random path for simulation list_sim <- which(mask_array[,,,drop=T] & is.na(SimGrid_list[[ii]][,,,1]), arr.ind = TRUE) diff --git a/R/gmSpatialModel.R b/R/gmSpatialModel.R index c5a1d38..bf38581 100644 --- a/R/gmSpatialModel.R +++ b/R/gmSpatialModel.R @@ -455,7 +455,7 @@ setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY"), #' @export setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmNeighbourhoodSpecification"), function(object, newdata, pars, ...){ - cat("starting cokriging \n") + message("starting cokriging") object@parameters = pars out = predict(as.gstat(object), newdata=newdata, ...) return(out) @@ -469,7 +469,7 @@ setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmNe setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmTurningBands"), function(object, newdata, pars, ...){ stop("Turning Bands method not yet interfaced here; use") - cat("starting turning bands \n") + message("starting turning bands") } ) @@ -479,7 +479,7 @@ setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmTu setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmCholeskyDecomposition"), function(object, newdata, pars, ...){ stop("Choleski decomposition method not yet implemented") - cat("starting Choleski decomposition \n") + message("starting Choleski decomposition") } ) @@ -490,7 +490,7 @@ setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmCh #' @export setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmSequentialSimulation"), function(object, newdata, pars, ...){ - cat("starting SGs \n") + message("starting SGs") object@parameters = pars$ng erg = predict(as.gstat(object), newdata=newdata, nsim=pars$nsim, debug.level=pars$debug.level, ...) Dg = ncol(object@coords) @@ -512,7 +512,7 @@ setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmSe setMethod("Predict",signature(object="gmSpatialModel", newdata="ANY", pars="gmDirectSamplingParameters"), function(object, newdata, pars, ...){ - cat("starting direct sampling \n") + message("starting direct sampling") # extract training image gt.ti = sp::getGridTopology(object@model) dt.ti = as(object@model,"SpatialGridDataFrame")@data diff --git a/R/grids.R b/R/grids.R index c5aa3c3..14c00b8 100644 --- a/R/grids.R +++ b/R/grids.R @@ -467,6 +467,9 @@ image_cokriged.default <- function(x, ivar=3, if(legendPos) legendPos = "top" } if(!is.logical(legendPos)){ + oldpar <- par(no.readonly = TRUE) + on.exit(par(oldpar)) + # make sure where the color legend goes par(oma=c(1,1,1,1)) if(legendPos %in% c("top","left")){ diff --git a/R/gstatCompatibility.R b/R/gstatCompatibility.R index 7d0e6eb..59a9b5b 100644 --- a/R/gstatCompatibility.R +++ b/R/gstatCompatibility.R @@ -264,10 +264,9 @@ variogramModelPlot.gstatVariogram = } } d = length(vrnames) - # plot empirical vario! - opar = par() - opar = par_remove_readonly(opar) + # plot empirical vario! + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) if(newfig) par(mfrow=c(d,d), mar=c(1,1,1,1)+0.5, oma=c(0,3,3,0)) diff --git a/R/mask.R b/R/mask.R index c0744b0..59de4e2 100644 --- a/R/mask.R +++ b/R/mask.R @@ -28,7 +28,7 @@ #' xyz.df = data.frame(xy, z = rnorm(29*23)*ifelse(abs(xy$x-xy$y)<3, 1, NA)+(xy$x+xy$y)/2) #' mask.df = constructMask(grid = xy, method = "maxdist", maxval = 3, x=xyz.df) #' image(mask.df) -#' par(mfrow=c(1,1)) +#' oldpar = par(mfrow = c(1,1)) #' mask.df #' xyz.df.masked = setMask(xyz.df, mask.df) #' dim(xyz.df.masked) @@ -46,17 +46,20 @@ #' aux = sp::SpatialPixelsDataFrame(grid = xy.gt, data=xyz.df, points = xy.sp) #' xyz.sgdf = as(aux, "SpatialGridDataFrame") #' image_cokriged(xyz.sgdf, ivar="z") +#' ## reorder the data in the grid and plot again #' par(mfrow=c(1,1)) #' ms = function(x) sortDataInGrid(x, grid=xy.gt) #' mask.gt = constructMask(grid = xy.gt, method = "maxdist", maxval = 3, x=xyz.sgdf) #' image(x,y,matrix(ms(xyz.sgdf@data$z), nrow=23, ncol=29)) #' image(x,y,matrix(ms(mask.gt), nrow=23, ncol=29)) #' image(mask.gt) +#' ## work with the mask and plot again #' par(mfrow=c(1,1)) #' xyz.sgdf.masked = setMask(x = xyz.sgdf, mask = mask.gt) #' getMask(xyz.sgdf.masked) #' image(x,y,matrix(ms(xyz.sgdf@data$z), nrow=23, ncol=29)) #' points(xyz.sgdf.masked@coords) +#' par(oldpar) constructMask = function(grid, method="maxdist", maxval=NULL, x=NULL){ methods = c("maxdist", "sillprop", "point2poly") m = methods[pmatch(method, methods)] diff --git a/R/variograms.R b/R/variograms.R index f1c3fbd..b3a0d8b 100644 --- a/R/variograms.R +++ b/R/variograms.R @@ -389,9 +389,7 @@ plot.gmCgram = function(x, xlim.up=NULL, xlim.lo=NULL, vdir.up= NULL, vdir.lo= N xseq.lo = seq(from=xlim.lo[1], to=xlim.lo[2], length.out=xlength) }else{ xseq.lo=NULL} - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) getVdens = function(vdir, xseq){ @@ -936,9 +934,7 @@ plot.gmEVario = function(x, xlim.up=NULL, xlim.lo=NULL, vdir.up= NULL, vdir.lo= } } - opar = par() - opar = par_remove_readonly(opar) - + opar = par(no.readonly = TRUE) if(closeplot) on.exit(par(opar)) myplot = function(...) matplot(type=type, ylab="", xlab="",xaxt="n", ...) @@ -1071,13 +1067,13 @@ variogramModelPlot.gmEVario <- function(vg, model = NULL, # gstat or variogra if(is.null(model)) return(invisible(opar)) # OTHERWISE: add the curves for the model - aux = as_directorVector(attr(vg, "directions")) + aux = as.directorVector(attr(vg, "directions")) if(!is.null(vdir.lo)) vdir.lo = aux[vdir.lo,] if(!is.null(vdir.up)) vdir.up = aux[vdir.up,] opar = plot(as.gmCgram(model), vdir.up= vdir.up, vdir.lo= vdir.lo, add=TRUE, cov =FALSE, ...) #f = as.function(as.gmCgram(gg)) #Dv = dim(vg$gamma)[2] - #dirs = as_directorVector(attr(vg, "directions")) + #dirs = as.directorVector(attr(vg, "directions")) #Dg = ncol(dirs) #for(i in 1:Dv){ # for(j in 1:Dv){ @@ -1177,7 +1173,7 @@ gsi.directorVector = function(x){ } print.directionClass = function(x, complete=TRUE, ...){ - cat(paste("with",nrow(as_directorVector(x)),"directions\n")) + cat(paste("with",nrow(as.directorVector(x)),"directions\n")) if(complete){ print(unclass(x), ...) } @@ -1185,14 +1181,30 @@ print.directionClass = function(x, complete=TRUE, ...){ -# @export -as_directorVector <- function(x, ...){ UseMethod("as_directorVector",x) } +#' Express a direction as a director vector +#' +#' Internal methods to express a direction (in 2D or 3D) as director +#' vector(s). These functions are not intended for direct use. +#' +#' @param x value of the direction in a certain representation +#' @param ... extra parameters for generic functionality +#' +#' @return A 2- or 3- column matrix which rows represents the unit +#' director vector of each direction specified. +#' @export +as.directorVector <- function(x, ...) UseMethod("as.directorVector",x) + -#' @method as_directorVector default -as_directorVector.default = function(x) x +#' @describeIn as.directorVector default method +#' @method as.directorVector default +#' @export +as.directorVector.default = function(x, ...) x -#' @method as_directorVector azimuth -as_directorVector.azimuth = function(x, D=2){ +#' @describeIn as.directorVector method for azimuths +#' @method as.directorVector azimuth +#' @param D dimension currently used (D=2 default; otherwise D=3; other values are not accepted) +#' @export +as.directorVector.azimuth = function(x, D=2, ...){ res = cbind(cos(pi/2-x), sin(pi/2-x)) if(D>2){ res = cbind(res, matrix(0, ncol=D-2, nrow=nrow(res))) @@ -1201,10 +1213,12 @@ as_directorVector.azimuth = function(x, D=2){ return(gsi.directorVector(res)) } -#' @method as_directorVector azimuthInterval -as_directorVector.azimuthInterval = function(x, D=2, ...){ +#' @describeIn as.directorVector method for azimuthIntervals +#' @method as.directorVector azimuthInterval +#' @export +as.directorVector.azimuthInterval = function(x, D=2, ...){ res = (x[[1]]+x[[2]])/2 - return(as_directorVector.azimuth(res)) + return(as.directorVector.azimuth(res)) } diff --git a/cran-comments.md b/cran-comments.md index 8c004ce..033351d 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -18,67 +18,134 @@ ## This is a resubmission, after archiving on 2023-04-05 -### Changes occurring after submission on 2023-04-13 15:57 +### Comments by Victoria Wimmer on 2023-04-14 + +The following issues have been corrected or commented here inline: ``` -Dear maintainer, - -package gmGeostats_0.11.3.tar.gz does not pass the incoming checks automatically, please see the following pre-tests: -Windows: <https://win-builder.r-project.org/incoming_pretest/gmGeostats_0.11.3_20230413_155730/Windows/00check.log> -Status: 1 NOTE -Debian: <https://win-builder.r-project.org/incoming_pretest/gmGeostats_0.11.3_20230413_155730/Debian/00check.log> -Status: 2 NOTEs +Thanks, -Please fix all problems and resubmit a fixed version via the webform. +Please proof-read your description text. +Currently it reads: "... positive amounts data ..." +Probably it should rather be: "... positive amounts of data ..." +``` -(...) +ANSWER: Description proofread and slightly changed. The specific sentence was correct as it was: it is about data constituted by positive numbers, i.e. amounts. Hopefully the new description is clearer. -Flavor: r-devel-linux-x86_64-debian-gcc ``` +Please add \value to .Rd files regarding exported methods and explain the functions results in the documentation. Please write about the structure of the output (class) and also what the output means. (If a function does not return a value, please document that too, e.g. \value{No return value, called for side effects} or similar) +Missing Rd-tags: + xvErrorMeasures.default.Rd: \value +``` + +ANSWER: Done. Also a section Details has been added. -Following changes done: +``` +\dontrun{} should only be used if the example really cannot be executed (e.g. because of missing additional software, missing API keys, ...) by the user. That's why wrapping examples in \dontrun{} adds the comment ("# Not run:") as a warning for the user. +Does not seem necessary. +Please unwrap the examples if they are executable in < 5 sec, or replace \dontrun{} with \donttest{}. +``` -* Check: S3 generic/method consistency, Result: NOTE -Mismatches for apparent methods not registered: -as.directorVector: - function(x, ...) -as.directorVector.default: - function(x) -as.directorVector: - function(x, ...) -as.directorVector.azimuth: - function(x, D) +ANSWER: The following instances of \dontrun{} were found. All of them had to be preserved for the specific reasons mentioned below. Please advice specifically to other strategies if this is not acceptable. -as.directorVector renamed to as_directorVector, as it is only an internal function +noSpatCorr.test() is a very slow function, even with the small reproducible example given in the examples section;. +getTellus() downloads a data set from an internet location; \dontrun{} is necessary as to avoid writing in the user's filespace. -* Apparent methods for exported generics not registered: +validate.test() is also a very slow function. -as.gmEVario.default --> added to NAMESPACE +sortDataInGrid() and image_cokriged() examples both depend on getTellus() in order to run, and running needs to be avoided for the same reason. +write.GSLib() also generates a foreign file in the user's file space, giving problems if run (as getTellus() above). -Apologies for the repeated errors. We cannot reproduce them in our Ubuntu systems, and hence cannot check completely that they disappeared. - - -Additionally, the following words are all correct: - -Possibly misspelled words in DESCRIPTION: - Boogaart (36:10) - Geostatistics (4:8) - Tolosana (35:36) - geostatistical (30:26) - microstructural (32:51) - multipoint (34:52) - +gsi.DS() is also a very slow function. + +The overarching problem is that, dealing with spatial data, examples quickly become quite complex (and computations several minutes long) if they have to be relevant and intuitive for users to understand. + + +``` +You write information messages to the console that cannot be easily suppressed. It is more R like to generate objects that can be used to extract the information a user is interested in, and then print() that object. +Instead of print()/cat() rather use message()/warning() or if(verbose)cat(..) (or maybe stop()) if you really have to write text to the console. +(except for print, summary, interactive functions) +``` + +ANSWER: No print() usage was found outside print() or summary() methods. +Some cat() were found in print() or summary() methods, and left as they were. All other cat() messages were converted to message() as requested. + +``` +Please ensure that your functions do not write by default or in your examples/vignettes/tests in the user's home filespace (including the package directory and getwd()). This is not allowed by CRAN policies. +Please omit any default path in writing functions. In your examples/vignettes/tests you can write to tempdir(). +``` + +ANSWER: We only found two functions writing to the user homespace, write.GSLib() and getTellus(), and both are doing that at the request of the user; write.GSLib() is just a write.*() function, and getTellus() downloads an illustration data set from a server of the Geological Survey of Northern Ireland. This solution had to be adopted for licensing reasons, as the GSNI allows to use the data but not to redistribute it. We are not sure which other function/vignette might be meant here. + +``` +Please make sure that you do not change the user's options, par or working directory. If you really have to do so within functions, please ensure with an *immediate* call of on.exit() that the settings are reset when the function is exited. e.g.: +... +oldpar <- par(no.readonly = TRUE) # code line i +on.exit(par(oldpar)) # code line i + 1 +... +par(mfrow=c(2,2)) # somewhere after +... + +... +old <- options() # code line i +on.exit(options(old)) # code line i+1 +... +options(digits = 3) +... + +... +oldwd <- getwd() # code line i +on.exit(setwd(oldwd)) # code line i+1 +... +setwd(...) # somewhere after +... +If you're not familiar with the function, please check ?on.exit. This function makes it possible to restore options before exiting a function even if the function breaks. Therefore it needs to be called immediately after the option change within a function. + +Please always make sure to reset to user's options(), working directory or par() after you changed it in examples and vignettes and demos. --> man/constructMask.Rd; man/sphTrans.Rd +e.g.: +oldpar <- par(mfrow = c(1,2)) +... +par(oldpar) + +Please fix and resubmit. + +Best, +Victoria Wimmer +``` + +ANSWER: The following instances of par() or options() were found + +pwlrmap(), pairsmap.default(), plot.gmCgram(), plot.gmEVario(), variogramModelPlot.gstatVariogram(), plot.logratioVariogramAnisotropy() : these functions implement the `on.exit(par(opar))` solution, albeit conditionally on the user not wanting the device to remain open. This is achieved by a logical flag `closeplot` which default value is TRUE, hence giving the requested behavour. We have added the extra argument `no.readonly = TRUE` to `opar = par()` so that now `oldpar<-par(...)` and `on.exit(...)` are consecutive as requested. + +swath.default(), swath.acomp(), image.logratioVariogramAnisotropy(), plot.accuracy(): We have added the extra argument `no.readonly = TRUE` to `opar = par()` so that now `oldpar<-par(...)` and `on.exit(...)` are consecutive as requested. + +About options(): only a package-wide edit of options occurs. This is introduced in .onLoad() and removed on .onUnload(). Please advice if this is not the correct way to do it. + +About working directory manipulations: this only occurs at the request of the user by calling function getTellusData() (see above as well). This function now implements the proposed solution of +``` + wd0 = getwd() + on.exit(setwd(wd0)) + setwd(wd) # wd is an argument to getTellusData() provided by the user. +``` + +The occurrences in man/constructMask.Rd and man/sphTrans.Rd were also corrected. + +``` +Additionally: +Have the issues why your package was archived been fixed? +Please explain this in the submission comments. +``` + +ANSWER: Yes, these are reported in the next section, "Original request". best regards ### Original request -Request from 2023-03-19. All calls to .C() are now explicitly pointing -to symbols instead of function namestrings. Package "gmGeostats" could -not be uploaded before the archiving deadline because the main dependence -"compositions" was showing problems as well. + +ANSWER: Request from 2023-03-19. All calls to .C() are now explicitly pointing to symbols instead of function namestrings. Package "gmGeostats" could not be uploaded before the archiving deadline because the main dependence "compositions" was showing the same problems as well, and it took some time to correct it under macos ARM flavor. ``` Dear maintainer, diff --git a/vignettes/SimulatingMicrostructures.Rmd b/vignettes/SimulatingMicrostructures.Rmd index 8c49b67..24fc3de 100644 --- a/vignettes/SimulatingMicrostructures.Rmd +++ b/vignettes/SimulatingMicrostructures.Rmd @@ -2,7 +2,7 @@ title: "Simulating microstructures with gmGeostats" output: rmarkdown::html_vignette vignette: > - %\VignetteIndexEntry{my-vignette} + %\VignetteIndexEntry{Simulating microstructures with gmGeostats} %\VignetteEngine{knitr::rmarkdown} %\VignetteEncoding{UTF-8} --- -- GitLab