[Rd] Package install problem on Windows (PR#13284)

Martin Maechler maechler at stat.math.ethz.ch
Fri Nov 14 09:48:51 CET 2008


>>>>> "SU" == Simon Urbanek <simon.urbanek at r-project.org>
>>>>>     on Thu, 13 Nov 2008 18:47:38 -0500 writes:

    SU> On Nov 13, 2008, at 6:11 PM, Tony Plate wrote:

    >> Thanks for the response.
    >> 
    >> Are the problems with versioned installs fundamental, or
    >> are they just a case of incomplete implementation and
    >> rough edges?  If the latter, would fixes be considered?
    >> 
    >> I ask because we would find versioned installs very
    >> useful in maintaining stable production systems, each of
    >> which might run with different versions of various
    >> packages, while making it easy to continually develop and
    >> refine our packages.  As a point of info, our primary use
    >> for versioning would be with our own packages, so we
    >> could probably get away without using versioned installs
    >> for base or contributed packages.
    >> 

    SU> I find it more useful to work with multiple library paths  
    SU> (.libPaths()) than versioning packages in the above
    SU> scenario. We usually maintain "stable" package library
    SU> which is individually overridden by additional paths
    SU> added by the user (e.g. developer library for testing)
    SU> and/or subsystems. The override can also be revertive,
    SU> i.e. a subsystem is free to use older packages in its
    SU> library than the stable library when desired.

We use the same "technique",
both using the R_LIBS environment variable, and also amending it
in an .Rprofile equivalent depending on the version of R (or the
user), i.e., something like

        libPIns <- function(nlib, beforeLib, msgTxt) {
          ## Purpose: Insert a directory into .libPaths() *before* another one
          ## ----------------------------------------------------------------
          ## Arguments: nlib:  The library directory to insert
          ##       beforeLib:  (grep-pattern of an) entry in current .libPaths()
          ##          msgTxt:  optional message text about the insertion
          ## ----------------------------------------------------------------
          ## Author: Martin Maechler, 2006

          if(file.exists(nlib)) {
            if(length({fl <- list.files(nlib); fl[fl != "R.css"]})) {
              ## only if the library contains any packages :
              if(!missing(msgTxt) && is.character(msgTxt))
                cat("extending .libPaths()", msgTxt,"...\n")
              ni <- length(iL <- grep(beforeLib, lp <- .libPaths()))
              if(ni != 1) {
                warning(".libPaths() contains ",
                        if(ni>1) "more" else "no",
                        " entries matching ",sQuote(beforeLib))
                iL <- if(ni > 1) iL[1] else length(lp)
                cat("Inserting before position", iL,"..\n")
              }
              ii <- 1:length(lp)
              .libPaths(c(lp[ii < iL], nlib, lp[ii >= iL]))
            }
          } else warning(nlib, " is not an existing directory")
        }

and then somewhere


        RVersion <- paste(R.version$major, R.version$minor, sep=".")
        Rstat <- R.version$status
        is.Rdevel <- ## Rstat == "beta" ||
          length(grep("devel", Rstat)) > 0
        if(is.Rdevel)
            libPIns(nlib =      file.path(RrootDir,"library-R-devel"),
                    beforeLib = file.path(RrootDir,"library"),
                    msgTxt = "for 'R-devel'")
and other such

        if(.....)
	    libPIns(....)

calls.

Martin Maechler, ETH Zurich






    >> However, if the problems with versioned installs are not
    >> amenable to the kinds of fixes that users can contribute,
    >> then I guess we should look for a different approach.
    >> 
    >> Suggestions and comments are welcome!  Do many people use
    >> versioned installs?
    >> 
    >> -- Tony Plate (coworker of Lars @ blackmesacapital.com)
    >> 
    >> Prof Brian Ripley wrote:
    >>> Installing versioned packages is not supported with
    >>> namespaces.  I have suggested from time to time that
    >>> versioned installs be removed because of this and other
    >>> known issues, and recommend that you do not attempt to
    >>> use them.
    >>> 
    >>> On Thu, 13 Nov 2008, lhansen at blackmesacapital.com wrote:
    >>> 
    >>>> Full_Name: Lars Hansen Version: 2.8.0 OS: Windows XP
    >>>> Pro x64 SP2 Submission from: (NULL) (71.39.177.36)
    >>>> 
    >>>> 
    >>>> Hi,
    >>>> 
    >>>> I have run into a problem using "R CMD INSTALL" with
    >>>> the "--with-package-versions" option under Windows. It
    >>>> is a bit obscure, which could explain why other people
    >>>> have not run into it.
    >>>> 
    >>>> We happen to have two packages with almost the same
    >>>> name. One name is a subset of the other. The names are
    >>>> "RtTests" and "RtTestsEG1".  I have no problem
    >>>> installing "RtTests" and many other packages, but run
    >>>> into problems installing "RtTestsEG1". The "RtTestsEG1"
    >>>> package happens to be a simple example of how to use
    >>>> the "RtTests" package, so it depends on "RtTests"
    >>>> (which is probably the problem).
    >>>> 
    >>>> OK, so this is what happens when I attempt to install
    >>>> "RtTestsEG1":
    >>>> 
    >>>> $ R CMD INSTALL --with-package-versions
    >>>> --library=$R_LIBS RtTestsEG1
    >>>> 
    >>>> installing RtTestsEG1 package
    >>>> 
    >>>> ---------- Making package RtTestsEG1 ------------
    >>>> adding build stamp to DESCRIPTION installing R files
    >>>> preparing package RtTestsEG1 for lazy loading Loading
    >>>> required package: RtTests ... [lost of lines removed]
    >>>> Loading required package: RtTests Error: evaluation
    >>>> nested too deeply: infinite recursion /
    >>>> options(expressions=)?  Execution halted make[2]: ***
    >>>> [lazyload] Error 1 make[1]: *** [all] Error 2 make: ***
    >>>> [pkg-RtTestsEG1] Error 2 *** Installation of RtTestsEG1
    >>>> failed ***
    >>>> 
    >>>> After some digging in the Windows makefiles, I found
    >>>> out that changing the locale from "C" to "us" in the
    >>>> "lazyload" target of $R_HOME/src/gnuwin32/MakePkg,
    >>>> i.e. using "LC_ALL=us" instead of "LC_ALL=C", solves
    >>>> the infinite recursion problem and give an useful
    >>>> message.  It still fails but now says:
    >>>> 
    >>>> Loading required package: RtTests Warning: S3 methods
    >>>> 'summary.RtTestSetResults', 'print.RtTestSetResults',
    >>>> 'print.RtTestSetResults.summary' were declared in
    >>>> NAMESPACE but not found Error in namespaceExport(ns,
    >>>> exports) : undefined exports: parseTranscriptFile,
    >>>> compareTranscriptAndOutput Error: package 'RtTests'
    >>>> could not be loaded Execution halted
    >>>> 
    >>>> It is true that RtTests declares the various functions
    >>>> in its name space, but why can they suddenly not be
    >>>> found? If I load RtTests by itself, i.e.
    >>>> library(RtTests), there is no problem.
    >>>> 
    >>>> I happen to have all this working under Linux, so I
    >>>> tracked down the difference.  Turns out that under
    >>>> Linux the equivalent to the "lazyload" target is in
    >>>> "/usr/lib/R/bin/INSTALL" and the difference is in the
    >>>> argument passed to "tools:::makeLazyLoading". Under
    >>>> Linux the full package name with version number is
    >>>> used, i.e. "RtTests_0.1-1". Windows just uses
    >>>> "RtTests".
    >>>> 
    >>>> So I managed to fix the problem by making Windows use
    >>>> the full package name in the "lazyload" target. I
    >>>> replaced tools:::makeLazyLoading(\"$(PKG)\" with
    >>>> tools:::makeLazyLoading(\"$(notdir $(DPKG))\"
    >>>> 
    >>>> If I now reinstall "RtTests", I can finally install
    >>>> "RtTestsEG1".
    >>>> 
    >>>> I must confess, that I do not fully understand exactly
    >>>> what it takes to reproduce this problem. I am guessing
    >>>> that all it takes is a package depending on a versioned
    >>>> package. Maybe the similarity in names introduces a
    >>>> problem because of partial matching. I am guessing that
    >>>> has nothing to do with it.
    >>>> 
    >>>> To sum up the report. I see two problems:
    >>>> 
    >>>> 1) LC_ALL=C causes infinite recursion. It is as if the
    >>>> C locale does not work under Windows. I do not know
    >>>> what the fix is. It is used many places in install
    >>>> scripts and makefiles. Fixing it in the "lazyload"
    >>>> target is not enough. Even with my change I still get
    >>>> "infinite recursion" and no error message if I try to
    >>>> install "RtTestsEG1" without first installing
    >>>> "RtTests".
    >>>> 
    >>>> 2) "makeLazyLoading()" in "lazyload" target needs to be
    >>>> called with full package name with embedded version
    >>>> number. I think this is bug under Windows and my fix
    >>>> takes care of it.
    >>>> 
    >>>> It took some time to figure this out. I am hoping this
    >>>> report will save other people time. I am note sure if I
    >>>> succeeded in describing the problem clearly.  Please do
    >>>> not hesitate to ask for clarification.
    >>>> 
    >>>> Thanks, Lars Hansen
    >>>> 
    >>>> P.S.
    >>>>> sessionInfo()
    >>>> R version 2.8.0 Patched (2008-10-22 r46776)
    >>>> i386-pc-mingw32
    >>>> 
    >>>> locale: LC_COLLATE=English_United
    >>>> States.1252;LC_CTYPE=English_United
    >>>> States.1252;LC_MONETARY=English_United
    >>>> States.1252;LC_NUMERIC=C;LC_TIME=English_United
    >>>> States.1252
    >>>> 
    >>>> attached base packages: [1] stats graphics grDevices
    >>>> utils datasets methods base
    >>>> 
    >>>> ______________________________________________
    >>>> R-devel at r-project.org mailing list
    >>>> https://stat.ethz.ch/mailman/listinfo/r-devel
    >>>> 
    >>> 
>
> ______________________________________________
    >> R-devel at r-project.org mailing list
    >> https://stat.ethz.ch/mailman/listinfo/r-devel
    >> 
    >> 

______________________________________________
    SU> R-devel at r-project.org mailing list
    SU> https://stat.ethz.ch/mailman/listinfo/r-devel



More information about the R-devel mailing list