I can't reproduce the more complex version. But the package on CRAN
fails in the same way on 3.2.3 and 3.3.0.

The problem is that your sysdata.rda includes a function that is
generating this error. If you do

f <- getFromNamespace(".RMXE", ns ="RobAStRDA")[["GEVFamily"]][["fun.N"]][[1]]
g <- get("fct", environment(f))

and look at the byte code for g with compiler::disassemble or the
utility I'll paste in below you get

getbc(g)
list(8L, BCMISMATCH.OP)

The only way you can get a file like this is to byte compile and save
in a version of R with a newer byte code version (the 8L) and then
load and resave in an older version of R. If you load and run this
code in an older (or newer) version of R it will revert to the
standard interpeter using eval but will issue a warning once per
session. If you try to run it in an R with byte code version 8L you
get this error.

I can make a small change to that this becomes a once-per-session
warning, but even then you won't actually be running compiled code.

So I think your task is to figure out how you are ended up with a
sysdata.rda file created in this incompatible way. Something to look
for might be whether a call from within your R-devel somehow manages
to run an R process with an older R version.

Let me know what you find out.

luke

Here is the little utility, adapted from compiler::disassemble:

getbc <- function (code) {
    .CodeSym <- as.name(".Code")
    disasm.const <- function(x) if (typeof(x) == "list" && length(x) >
        0 && identical(x[[1]], .CodeSym))
        disasm(x)
    else x
    disasm <- function(code) {
        code[[2]] <- compiler:::bcDecode(code[[2]])
        code[[3]] <- lapply(code[[3]], disasm.const)
        code
    }
    if (typeof(code) == "closure") {
        code <- .Internal(bodyCode(code))
        if (typeof(code) != "bytecode")
            stop("function is not compiled")
    }
    invisible(dput(disasm(.Internal(disassemble(code)))[[2]]))
}

On Sun, 1 May 2016, Peter Ruckdeschel wrote:

Thanks, Luke, for having a look to it.

Sure, I can give you some reproducible example -- even in two degrees of
completeness ;-): see below.

Thanks again, Peter

%-----------------------------------
(I) first example
%-----------------------------------
Just to reproduce the error, on r-devel, try:

install.packages("RobAStRDA")
require(RobAStRDA)
getFromNamespace(".RMXE", ns = "RobAStRDA")[["GEVFamily"]][["fun.N"]][[1]](1.3)

%-----------------------------------
(II) an example also giving the context
%-----------------------------------
For the "complete" story, not only the R-code needs to be given, but also the
preparation steps to produce the packages on the right R version;

so please follow steps (1)--(6) below; I am not 100% sure whether this already 
gives
you all information needed for this, but if not so please let me know.

(1) create a minimal R-package "InterpolTry"
     with byte-compilation on in the DESCRIPTION file
     and with stats::approxfun imported in the NAMESPACE file

(2) in an R session on R-devel do

require(InterpolTry)
x <- 1:100
y <- 1:100
fun <- approxfun(x,y)
## revise the next line accordingly to your local settings
SrcRPathInterpolTry <- <path_to_(source-)R-folder_of_InterpolTry>
RdaFile <- file.path(SrcRPathInterpolTry, "sysdata.rda")
save(fun, file = RdaFile)
tools::resaveRdaFiles(RdaFile)

(3) re-build package InterpolTry and re-install it

(4) create a minimal R package "UseInterpolTry", again
     with byte-compilation on in the DESCRIPTION file
     and with stats::approxfun and package "InterpolTry"
     imported in the NAMESPACE file

(5) in the R folder of R package "UseInterpolTry" write a function
     useInterpolFct()  which goes like this

     useInterpolFct <- function(x){
              fun <- getFromNamespace("fun", ns = "InterpolTry")
              fun(x)
     }

    export this function in the namespace and create an .Rd file to it

(6) (re-)build package "UseInterpolTry" and (re-)install it and try

require(UseInterpolTry)
useInterpolFct(5)

Steps (1)--(6) work with R-3.1.3, but no longer with R-devel.



Am 01.05.2016 um 14:12 schrieb Tierney, Luke:
Can you provide a complete reproducible example?

Sent from my iPhone

On May 1, 2016, at 6:51 AM, Peter Ruckdeschel <peter.ruckdesc...@web.de> wrote:

Hi r-devels,

we are seeing a new problem with our packages RobAStRDA (just new on CRAN, 
thanks
to Uwe and Kurt!) and RobExtremes (to be submitted).

It must be something recent with the way you internally treat/store byte-code 
compiled
functions, as we have no problems with R-3.1.3, but do see an "Error in fct(x) 
: byte code
version mismatch" with R-devel SVNrev r70532.

Background:
Starting from several x-y grids, in the sysdata.rda file of RobAStRDA, we store 
the results
of calls to approxfun/splinefun to these grids from within a session with pkg 
RobAStRDA
require()d.  From pkg RobExtremes we then call these interpolating functions by 
means of
a call (essentially) as:

getFromNamespace(".RMXE", ns = "RobAStRDA")[["GEVFamily"]][["fun.N"]][[1]](1.3)

upon which we get the announced "Error in fct(x) : byte code version mismatch" 
while the same
code does work for R-3.1.3.

The list element "fun.N" in the above call already accounts for a different 
behaviour for
pre R-3.0.0 (would have given "fun.O") and post R-3.0.0 ("fun.N") results of 
approxfun/
splinefun, but the interpolating functions in branch "fun.N" have been produced 
in
R-devel SVNrev r70532, so we would have expected our code 
getFromNamespace(.....) above to
work in R-devel as well.

Could you give us any hints how to

(a) store the interpolating functions resulting from approxfun/splinefun in pkg 
RobAStRDA
   correctly in recent R-versions and
(b) call these functions in pkg RobExtremes ?

We already did import stats::approxfun and stats::splinefun into the NAMESPACEs 
of pkgs
RobAStRDA and RobExtremes.

Thanks for your help already,
Peter


---
Diese E-Mail wurde von Avast Antivirus-Software auf Viren geprüft.
https://www.avast.com/antivirus

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


---
Diese E-Mail wurde von Avast Antivirus-Software auf Viren geprüft.
https://www.avast.com/antivirus



--
Luke Tierney
Ralph E. Wareham Professor of Mathematical Sciences
University of Iowa                  Phone:             319-335-3386
Department of Statistics and        Fax:               319-335-3017
   Actuarial Science
241 Schaeffer Hall                  email:   luke-tier...@uiowa.edu
Iowa City, IA 52242                 WWW:  http://www.stat.uiowa.edu
______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to