Dear Duncan, On Mon, 13 Jul 2015 20:00:02 -0400 Duncan Murdoch <murdoch.dun...@gmail.com> wrote: > On 13/07/2015 7:35 PM, John Fox wrote: > > Dear Duncan, > > > >> -----Original Message----- > >> From: Duncan Murdoch [mailto:murdoch.dun...@gmail.com] > >> Sent: July-13-15 7:01 PM > >> To: John Fox; 'peter dalgaard' > >> Cc: r-package-devel@r-project.org > >> Subject: Re: [R-pkg-devel] "invalid 'envir' argument" note from R-devel > >> > >> It happened in r68597. In my example, I hadn't imported the data() > >> function from utils; when I did that, it was fixed. > >> > >> Not sure why the error is complaining about the envir argument. > > > > > > Yes, importing data works for me too! It's odd that the problem didn't show > > up as an undefined global symbol rather than as a note about the envir > > argument. (I was fixing imports from standard packages when the problem > > arose.) > > I'd guess that it's finding some other private function called data(); > that's probably worth fixing.
If you mean an unexported function named data() in the Rcmdr package, then I'm pretty sure that there is none -- and I just checked all of the many uses of the word "data" in the Rcmdr sources. Of course, I may have missed something or, more likely, misunderstood what you're suggesting. Best, John > > Duncan > > > > > Thanks for tracking this down. > > > > John > > > >> > >> Duncan Murdoch > >> > >> On 13/07/2015 6:47 PM, John Fox wrote: > >>> Dear Duncan and Peter, > >>> > >>> I've just arrived at more or less the same thing: > >>> > >>> foo <- function() data(package="MASS") > >>> > >>> bar <- function() data(package="MASS", envir=.GlobalEnv) > >>> > >>> baz <- function() data(package="MASS", envir=globalenv()) > >>> > >>> all trigger the note when included with the Rcmdr sources: > >>> > >>> * checking R code for possible problems ... NOTE > >>> bar: Error while checking: invalid 'envir' argument > >>> baz: Error while checking: invalid 'envir' argument > >>> foo: Error while checking: invalid 'envir' argument > >>> > >>> The envir argument to data() defaults to .GlobaEnv . > >>> > >>> I hope this helps, > >>> John > >>> > >>>> -----Original Message----- > >>>> From: Duncan Murdoch [mailto:murdoch.dun...@gmail.com] > >>>> Sent: July-13-15 6:32 PM > >>>> To: John Fox; 'peter dalgaard' > >>>> Cc: r-package-devel@r-project.org > >>>> Subject: Re: [R-pkg-devel] "invalid 'envir' argument" note from R- > >> devel > >>>> > >>>> On 13/07/2015 5:23 PM, John Fox wrote: > >>>>> Dear Peter, > >>>>> > >>>>>> -----Original Message----- > >>>>>> From: peter dalgaard [mailto:pda...@gmail.com] > >>>>>> Sent: July-13-15 4:52 PM > >>>>>> To: John Fox > >>>>>> Cc: r-package-devel@r-project.org > >>>>>> Subject: Re: [R-pkg-devel] "invalid 'envir' argument" note from R- > >>>> devel > >>>>>> > >>>>>> Yes, there was a similar note from Alexandra Kuznetsova a couple of > >>>> days > >>>>> > >>>>> Sorry, I didn't notice that. > >>>>> > >>>>>> ago. Look unintentional, but it is not easy to spot what triggers > >> it. > >>>> If > >>>>>> someone could cook up a minimal example, or - maybe easier given > >> the > >>>>>> relatively short timeframe - bisect their way to the exact svn > >>>> revision > >>>>>> that triggered it, it might help in getting it fixed. > >>>>> > >>>>> I'm afraid that I'm not set up to build R-devel and I'm about to > >> leave > >>>> town > >>>>> for three weeks. I'll see if I can produce a simpler example > >>>> triggering the > >>>>> error, however. > >>>> > >>>> Hana Sevcikova posted a simple example. I'll bisect on it. > >>>> > >>>> Here's her example: > >>>> > >>>> e <- new.env() > >>>> data("mydataset", envir=e) > >>>> > >>>> I've substituted USArrests for "mydataset". > >>>> > >>>> Duncan Murdoch > >>>> > >>>>> > >>>>> Thanks for this, > >>>>> John > >>>>> > >>>>>> > >>>>>> -pd > >>>>>> > >>>>>>> On 13 Jul 2015, at 22:31 , John Fox <j...@mcmaster.ca> wrote: > >>>>>>> > >>>>>>> Dear list members, > >>>>>>> > >>>>>>> I'm getting a new note from R-devel that I haven't seen before > >> when > >>>>>> checking > >>>>>>> the development version of the Rcmdr package: > >>>>>>> > >>>>>>> * checking R code for possible problems ... NOTE > >>>>>>> readDataFromPackage: Error while checking: invalid 'envir' > >> argument > >>>>>>> > >>>>>>> This note doesn't appear in R 3.2.1. > >>>>>>> > >>>>>>> My session info: > >>>>>>> > >>>>>>> -------- snip ---------- > >>>>>>> > >>>>>>> R Under development (unstable) (2015-07-12 r68650) > >>>>>>> Platform: x86_64-w64-mingw32/x64 (64-bit) > >>>>>>> Running under: Windows 7 x64 (build 7601) Service Pack 1 > >>>>>>> > >>>>>>> locale: > >>>>>>> [1] LC_COLLATE=English_Canada.1252 LC_CTYPE=English_Canada.1252 > >>>>>>> LC_MONETARY=English_Canada.1252 > >>>>>>> [4] LC_NUMERIC=C LC_TIME=English_Canada.1252 > >>>>>>> > >>>>>>> attached base packages: > >>>>>>> [1] stats graphics grDevices utils datasets methods > >> base > >>>>>>> > >>>>>>> loaded via a namespace (and not attached): > >>>>>>> [1] tools_3.3.0 > >>>>>>> > >>>>>>> -------- snip ---------- > >>>>>>> > >>>>>>> I can't even localize the problem in readDataFromPackage(). There > >>>> are > >>>>>> only > >>>>>>> two places in this function where there's a function call with an > >>>>>> envir > >>>>>>> argument, and I still get the note if I comment these out. As > >> well, > >>>>>>> readDataFromPackage() seems to work as intended -- there is no > >>>> obvious > >>>>>> error > >>>>>>> in it. > >>>>>>> > >>>>>>> FWIW, here's readDataFromPackage(). The complete sources for the > >>>>>> development > >>>>>>> version of the Rcmdr package are on R-Forge. > >>>>>>> > >>>>>>> -------- snip ---------- > >>>>>>> > >>>>>>> readDataFromPackage <- function() { > >>>>>>> env <- environment() > >>>>>>> datasets <- NULL > >>>>>>> initializeDialog(title=gettextRcmdr("Read Data From > >> Package")) > >>>>>>> dsname <- tclVar("") > >>>>>>> package <- NULL > >>>>>>> enterFrame <- tkframe(top) > >>>>>>> entryDsname <- ttkentry(enterFrame, width="20", > >>>>>> textvariable=dsname) > >>>>>>> packages <- sort(.packages()) > >>>>>>> packages <- packages[! packages %in% c("base", "stats")] > >>>>>>> packages <- packages[sapply(packages, function(package){ > >>>>>>> ds <- > >>>>>>> data(package=package)$results > >>>>>>> if (nrow(ds) == 0) > >>>>>>> return(FALSE) > >>>>>>> ds <- ds[, "Item"] > >>>>>>> valid <- sapply(ds, > >>>>>>> is.valid.name) > >>>>>>> length(ds[valid]) > > > 0 > >>>>>>> })] > >>>>>>> packageDatasetFrame <- tkframe(top) > >>>>>>> packageFrame <- tkframe(packageDatasetFrame) > >>>>>>> max.height <- getRcmdr("variable.list.height") > >>>>>>> packageBox <- tklistbox(packageFrame, height=min(max.height, > >>>>>>> length(packages)), > >>>>>>> exportselection="FALSE", > >>>>>>> selectmode="single", background="white") > >>>>>>> packageScroll <- ttkscrollbar(packageFrame, > >>>>>>> command=function(...) tkyview(packageBox, > > ...)) > >>>>>>> tkconfigure(packageBox, yscrollcommand=function(...) > >>>>>>> tkset(packageScroll, ...)) > >>>>>>> for (p in packages) tkinsert(packageBox, "end", p) > >>>>>>> datasetFrame <- tkframe(packageDatasetFrame) > >>>>>>> datasetBox <- tklistbox(datasetFrame, height=max.height, > >>>>>>> exportselection="FALSE", > >>>>>>> selectmode="single", background="white") > >>>>>>> datasetScroll <- ttkscrollbar(datasetFrame, > >>>>>>> command=function(...) tkyview(datasetBox, > > ...)) > >>>>>>> tkconfigure(datasetBox, yscrollcommand=function(...) > >>>>>>> tkset(datasetScroll, ...)) > >>>>>>> onPackageSelect <- function(){ > >>>>>>> assign("package", > >>>>>>> packages[as.numeric(tkcurselection(packageBox)) + 1], envir=env) > >>>>>>> datasets <<- data(package=package)$results[,3] > >>>>>>> valid <- sapply(datasets, is.valid.name) > >>>>>>> datasets <<- datasets[valid] > >>>>>>> tkdelete(datasetBox, "0", "end") > >>>>>>> for (dataset in datasets) tkinsert(datasetBox, > > "end", > >>>>>>> dataset) > >>>>>>> tkconfigure(datasetBox, height=min(max.height, > >>>>>>> length(datasets))) > >>>>>>> firstChar <- tolower(substr(datasets, 1, 1)) > >>>>>>> len <- length(datasets) > >>>>>>> onLetter <- function(letter){ > >>>>>>> letter <- tolower(letter) > >>>>>>> current <- 1 + > >>>>>>> round(as.numeric(unlist(strsplit(tclvalue(tkyview(datasetBox) ), " > >>>>>>> "))[1])*len) > >>>>>>> mat <- match(letter, > > firstChar[-(1:current)]) > >>>>>>> if (is.na(mat)) return() > >>>>>>> tkyview.scroll(datasetBox, mat, "units") > >>>>>>> } > >>>>>>> onA <- function() onLetter("a") > >>>>>>> onB <- function() onLetter("b") > >>>>>>> onC <- function() onLetter("c") > >>>>>>> onD <- function() onLetter("d") > >>>>>>> onE <- function() onLetter("e") > >>>>>>> onF <- function() onLetter("f") > >>>>>>> onG <- function() onLetter("g") > >>>>>>> onH <- function() onLetter("h") > >>>>>>> onI <- function() onLetter("i") > >>>>>>> onJ <- function() onLetter("j") > >>>>>>> onK <- function() onLetter("k") > >>>>>>> onL <- function() onLetter("l") > >>>>>>> onM <- function() onLetter("m") > >>>>>>> onN <- function() onLetter("n") > >>>>>>> onO <- function() onLetter("o") > >>>>>>> onP <- function() onLetter("p") > >>>>>>> onQ <- function() onLetter("q") > >>>>>>> onR <- function() onLetter("r") > >>>>>>> onS <- function() onLetter("s") > >>>>>>> onT <- function() onLetter("t") > >>>>>>> onU <- function() onLetter("u") > >>>>>>> onV <- function() onLetter("v") > >>>>>>> onW <- function() onLetter("w") > >>>>>>> onX <- function() onLetter("x") > >>>>>>> onY <- function() onLetter("y") > >>>>>>> onZ <- function() onLetter("z") > >>>>>>> for (letter in c(letters, LETTERS)){ > >>>>>>> tkbind(datasetBox, paste("<", letter, ">", > > sep=""), > >>>>>>> get(paste("on", > > toupper(letter), > >>>>>>> sep=""))) > >>>>>>> } > >>>>>>> onClick <- function() tkfocus(datasetBox) > >>>>>>> tkbind(datasetBox, "<ButtonPress-1>", onClick) > >>>>>>> } > >>>>>>> onDatasetSelect <- function(){ > >>>>>>> tclvalue(dsname) <- > >>>>>>> datasets[as.numeric(tkcurselection(datasetBox)) + 1] > >>>>>>> } > >>>>>>> firstChar <- tolower(substr(packages, 1, 1)) > >>>>>>> len <- length(packages) > >>>>>>> onLetter <- function(letter){ > >>>>>>> letter <- tolower(letter) > >>>>>>> current <- 1 + > >>>>>>> round(as.numeric(unlist(strsplit(tclvalue(tkyview(packageBox) ), " > >>>>>>> "))[1])*len) > >>>>>>> mat <- match(letter, firstChar[-(1:current)]) > >>>>>>> if (is.na(mat)) return() > >>>>>>> tkyview.scroll(packageBox, mat, "units") > >>>>>>> } > >>>>>>> onA <- function() onLetter("a") > >>>>>>> onB <- function() onLetter("b") > >>>>>>> onC <- function() onLetter("c") > >>>>>>> onD <- function() onLetter("d") > >>>>>>> onE <- function() onLetter("e") > >>>>>>> onF <- function() onLetter("f") > >>>>>>> onG <- function() onLetter("g") > >>>>>>> onH <- function() onLetter("h") > >>>>>>> onI <- function() onLetter("i") > >>>>>>> onJ <- function() onLetter("j") > >>>>>>> onK <- function() onLetter("k") > >>>>>>> onL <- function() onLetter("l") > >>>>>>> onM <- function() onLetter("m") > >>>>>>> onN <- function() onLetter("n") > >>>>>>> onO <- function() onLetter("o") > >>>>>>> onP <- function() onLetter("p") > >>>>>>> onQ <- function() onLetter("q") > >>>>>>> onR <- function() onLetter("r") > >>>>>>> onS <- function() onLetter("s") > >>>>>>> onT <- function() onLetter("t") > >>>>>>> onU <- function() onLetter("u") > >>>>>>> onV <- function() onLetter("v") > >>>>>>> onW <- function() onLetter("w") > >>>>>>> onX <- function() onLetter("x") > >>>>>>> onY <- function() onLetter("y") > >>>>>>> onZ <- function() onLetter("z") > >>>>>>> for (letter in c(letters, LETTERS)){ > >>>>>>> tkbind(packageBox, paste("<", letter, ">", sep=""), > >>>>>>> get(paste("on", toupper(letter), > > sep=""))) > >>>>>>> } > >>>>>>> onClick <- function() tkfocus(packageBox) > >>>>>>> tkbind(packageBox, "<ButtonPress-1>", onClick) > >>>>>>> onOK <- function(){ > >>>>>>> datasetName <- > >>>>>>> datasets[as.numeric(tkcurselection(datasetBox)) + 1] > >>>>>>> dsnameValue <- tclvalue(dsname) > >>>>>>> if (dsnameValue != "" && is.null(package)){ > >>>>>>> closeDialog() > >>>>>>> if (is.element(dsnameValue, listDataSets())) > > { > >>>>>>> if ("no" == > >>>>>>> tclvalue(checkReplace(dsnameValue, gettextRcmdr("Data set")))){ > >>>>>>> if (GrabFocus()) > > tkgrab.release(top) > >>>>>>> tkdestroy(top) > >>>>>>> readDataFromPackage() > >>>>>>> return() > >>>>>>> } > >>>>>>> } > >>>>>>> save.options <- options(warn=2) > >>>>>>> check <- > > try(eval(parse(text=logger(paste("data(", > >>>>>>> dsnameValue, ")", sep=""))), > >>>>>>> > > envir=.GlobalEnv), > >>>>>>> silent=TRUE) > >>>>>>> options(save.options) > >>>>>>> if (class(check) == "try-error"){ > >>>>>>> > > errorCondition(recall=readDataFromPackage, > >>>>>>> > >>>>>>> message=sprintf(gettextRcmdr("Data set %s does not exit"), > >>>>>> dsnameValue)) > >>>>>>> return() > >>>>>>> } > >>>>>>> activeDataSet(dsnameValue) > >>>>>>> tkfocus(CommanderWindow()) > >>>>>>> } > >>>>>>> else{ > >>>>>>> if (is.null(package)) { > >>>>>>> > > errorCondition(recall=readDataFromPackage, > >>>>>>> message=gettextRcmdr("You must select a package.")) > >>>>>>> return() > >>>>>>> } > >>>>>>> if (length(datasetName) == 0) { > >>>>>>> > > errorCondition(recall=readDataFromPackage, > >>>>>>> message=gettextRcmdr("You must select a data set.") ) > >>>>>>> return() > >>>>>>> } > >>>>>>> if (is.element(datasetName, listDataSets())) > > { > >>>>>>> if ("no" == > >>>>>>> tclvalue(checkReplace(datasetName, gettextRcmdr("Data set")))){ > >>>>>>> if (GrabFocus()) > > tkgrab.release(top) > >>>>>>> tkdestroy(top) > >>>>>>> readDataFromPackage() > >>>>>>> return() > >>>>>>> } > >>>>>>> } > >>>>>>> closeDialog() > >>>>>>> command <- paste("data(", datasetName, ', > >>>>>>> package="', package, '")', sep="") > >>>>>>> result <- justDoIt(command) > >>>>>>> logger(command) > >>>>>>> if (class(result)[1] != "try-error") > >>>>>>> activeDataSet(datasetName) > >>>>>>> tkfocus(CommanderWindow()) > >>>>>>> } > >>>>>>> } > >>>>>>> onDataHelp <- function(){ > >>>>>>> datasetName <- datasets[as.numeric(tkcurselection(datasetBox)) > >> + > >>>> 1] > >>>>>>> dsnameValue <- tclvalue(dsname) > >>>>>>> if (dsnameValue == "") dsnameValue <- datasetName > >>>>>>> if (length(dsnameValue) == 0) > > Message(gettextRcmdr("No > >> data > >>>>>>> set selected."), type="warning") > >>>>>>> else if (is.null(package)) > > doItAndPrint(paste('help("', > >>>>>>> dsnameValue, '")', sep="")) > >>>>>>> else doItAndPrint(paste('help("', dsnameValue, '", > >>>>>>> package="', package, '")', sep="")) > >>>>>>> } > >>>>>>> OKCancelHelp(helpSubject="data") > >>>>>>> dataHelpButton <- buttonRcmdr(top, text=gettextRcmdr("Help > > on > >>>>>>> selected data set"), command=onDataHelp) > >>>>>>> tkgrid(labelRcmdr(packageDatasetFrame, > >> text=gettextRcmdr("Package > >>>>>>> (Double-click to select)"), fg=getRcmdr("title.color"), > >>>>>>> font="RcmdrTitleFont"), > >>>>>>> labelRcmdr(packageDatasetFrame, text=" "), > >>>>>>> labelRcmdr(packageDatasetFrame, text=gettextRcmdr("Data set > >> (Double- > >>>>>> click to > >>>>>>> select)"), > >>>>>>> fg=getRcmdr("title.color"), > >>>>>>> font="RcmdrTitleFont"), sticky="w") > >>>>>>> tkgrid(packageBox, packageScroll, sticky="nw") > >>>>>>> tkgrid(datasetBox, datasetScroll, sticky="nw") > >>>>>>> tkgrid(packageFrame, labelRcmdr(packageDatasetFrame, text=" > >> "), > >>>>>>> datasetFrame, sticky="nw") > >>>>>>> tkgrid(packageDatasetFrame, sticky="w") > >>>>>>> tkgrid(labelRcmdr(top, text=gettextRcmdr("OR"), fg="red"), > >>>>>>> sticky="w") > >>>>>>> tkgrid(labelRcmdr(enterFrame, text=gettextRcmdr("Enter name > >> of data > >>>>>>> set: "), fg=getRcmdr("title.color"), font="RcmdrTitleFont"), > >>>>>> entryDsname, > >>>>>>> sticky="w") > >>>>>>> tkgrid(enterFrame, sticky="w") > >>>>>>> tkgrid(dataHelpButton, sticky="w") > >>>>>>> tkgrid(buttonsFrame, sticky="ew") > >>>>>>> tkgrid.configure(packageScroll, sticky="ns") > >>>>>>> tkgrid.configure(datasetScroll, sticky="ns") > >>>>>>> tkbind(packageBox, "<Double-ButtonPress-1>", > > onPackageSelect) > >>>>>>> tkbind(datasetBox, "<Double-ButtonPress-1>", > > onDatasetSelect) > >>>>>>> dialogSuffix(focus=entryDsname) > >>>>>>> } > >>>>>>> > >>>>>>> -------- snip ---------- > >>>>>>> > >>>>>>> Any insight into the problem would be appreciated. > >>>>>>> > >>>>>>> Thanks, > >>>>>>> John > >>>>>>> > >>>>>>> ----------------------------------------------- > >>>>>>> John Fox, Professor > >>>>>>> McMaster University > >>>>>>> Hamilton, Ontario, Canada > >>>>>>> http://socserv.socsci.mcmaster.ca/jfox/ > >>>>>>> > >>>>>>> > >>>>>>> > >>>>>>> > >>>>>>> --- > >>>>>>> This email has been checked for viruses by Avast antivirus > >> software. > >>>>>>> https://www.avast.com/antivirus > >>>>>>> > >>>>>>> ______________________________________________ > >>>>>>> R-package-devel@r-project.org mailing list > >>>>>>> https://stat.ethz.ch/mailman/listinfo/r-package-devel > >>>>>> > >>>>>> -- > >>>>>> Peter Dalgaard, Professor, > >>>>>> Center for Statistics, Copenhagen Business School > >>>>>> Solbjerg Plads 3, 2000 Frederiksberg, Denmark > >>>>>> Phone: (+45)38153501 > >>>>>> Email: pd....@cbs.dk Priv: pda...@gmail.com > >>>>>> > >>>>>> > >>>>>> > >>>>>> > >>>>>> > >>>>>> > >>>>> > >>>>> > >>>>> > >>>>> --- > >>>>> This email has been checked for viruses by Avast antivirus software. > >>>>> https://www.avast.com/antivirus > >>>>> > >>>>> ______________________________________________ > >>>>> R-package-devel@r-project.org mailing list > >>>>> https://stat.ethz.ch/mailman/listinfo/r-package-devel > >>>>> > >>> > >>> > >>> --- > >>> This email has been checked for viruses by Avast antivirus software. > >>> https://www.avast.com/antivirus > >>> > > > > > > --- > > This email has been checked for viruses by Avast antivirus software. > > https://www.avast.com/antivirus > > > ------------------------------------------------ John Fox, Professor McMaster University Hamilton, Ontario, Canada http://socserv.mcmaster.ca/jfox/ ______________________________________________ R-package-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-package-devel