I have an R package, cladoRcpp, which is up on CRAN. After a minor update, which compiled without errors on R CMD check on my machine, I submitted the update.

Brian Ripley got an error that I didn't get:


==================================================================
We still see

> Rcpp_combn_zerostart(n_to_choose_from=4, k_to_choose=2, maxlim=1e+07)
=================================================================
==14369== ERROR: AddressSanitizer: attempting free on address which was not malloc()-ed: 0x0000040541d0
    #0 0x7fe61090caca in ?? ??:0
#1 0x7fe6138ba858 in _ZN9__gnu_cxx13new_allocatorIiE10deallocateEPim /usr/local/gcc48x/include/c++/4.8.1/ext/new_allocator.h:110 #2 0x7fe613896fd4 in cpp_combn_zerostart /data/gannet2/ripley/R/packages/incoming/cladoRcpp.Rcheck/00_pkg_src/cladoRcpp/src/calc_anclikes_sp.cpp:75 #3 0x472b5f in do_dotcall /data/gannet/ripley/R/svn/R-devel/src/main/dotcode.c:587

using AddressSanitizer, as before.
==================================================================


I gather that this is from him using the new gcc4.8 and the AddressSanitizer option on compile:

http://r.789695.n4.nabble.com/Linux-distribution-with-gcc-4-8-and-AddressSanitizer-td4664629.html

http://cran.r-project.org/doc/manuals/r-devel/R-exts.html#Using-gctorture-and-memory-access


I will attempt to download/install gcc48 and reproduce the error, although this is a somewhat major project.


The C++ function, though, is quite simple -- I wonder if anyone might be able to spot easily what is going on?





R function which calls C++ function:

======================================
Rcpp_combn_zerostart <- function(n_to_choose_from, k_to_choose, maxlim=1e+07)
        {
        n = n_to_choose_from
        m = k_to_choose
        
        # HEAD OFF ERROR
        predicted_number_of_cells_to_fill = choose(n,m)
        
        if (predicted_number_of_cells_to_fill > maxlim)
                {
txt = paste("ERROR: n=", n_to_choose_from, ", k=", k_to_choose, ", n choose k=", predicted_number_of_cells_to_fill, " > maxlim=", maxlim, "\nCalculating something this big may crash your computer!", sep="")
                stop(txt)
                }
        
        
outarray = .Call("cpp_combn_zerostart", as.integer(n), as.integer(m), as.double(maxlim))

        #R_states_list <- matrix(out$res,nrow=m,byrow=F)

        return(outarray)
        }
======================================



C++ function:
======================================

RcppExport SEXP cpp_combn_zerostart(SEXP R_n, SEXP R_m, SEXP R_maxval)
        {
        using namespace std;
        
        // Convert to plain C++
        int cpp_nval = Rcpp::as<int>(R_n);
        int cpp_mval = Rcpp::as<int>(R_m);
        double cpp_maxval = Rcpp::as<double>(R_maxval);
        
        // Create pointer variables to hold the addresses to each
        int* n = &cpp_nval;
        int* m = &cpp_mval;
        
// Choose n by m; calculate from the values stored at addresses n and m
        double Cnm;
        Cnm = nChoosek(*n, *m);
        
        // Error check
        if (Cnm > cpp_maxval)
                {
//cout << "\nERROR: n=" << cpp_nval << ", k=" << cpp_mval << ", n choose k=" << Cnm << " > maxval=", cpp_maxval; //cout << "\nCalculating something this big may crash your computer! Returning 0.";
                return 0;
                }
        
        
// Declare and populate empty array of addresses to hold the combn results
        // Addresses for a 10x3 array; 30 total
        int* combmat;
        combmat = new int[(int)Cnm**(m+0)];
        
// Run moncombn_zerostart; this will update the stuff in the addresses
        // stored in combmat
        moncombn_zerostart(combmat,n,m);
        
// Write the contents of each of the Cnm times *m addresses to cout
        // convert double (float) Cnm to int
        int nrows;
        int ncols;
        nrows = *m;
        ncols = (int)Cnm;
        int vecsize;
        vecsize = nrows * ncols;
        //int combmat_vals[nrows * ncols];
        
//Rcpp::NumericVector combmat_vals(vecsize); // vector of size vecsize filled with 0s Rcpp::NumericMatrix combmat_vals(nrows,ncols); // vector of size vecsize filled with 0s

        // initialize row & column numbers, and the temporary number        
        int rownum = 0;
        int colnum = 0;
        int tmpnum = 0;
        
        //cout << nrows << " rows, " << ncols << "cols...\n";
        
        for (int j = 1; j <= Cnm**(m+0); j++)
                {
                //cout << "\n";
                //cout << *(combmat+j-1) << " ";
                //combmat_vals[rownum][colnum] = *(combmat+j-1);
                //tmpnum = Rcpp::as<int>(*(combmat+j-1));
                tmpnum = *(combmat+j-1);
                //combmat_vals[j-1] = tmpnum;

//cout << "\n" << rownum << "," << colnum << ", ncols=" << ncols << ": " << tmpnum;
                combmat_vals(rownum, colnum) = tmpnum;
                
                // Increment column
                rownum++;
                
                // Reset column when you reach the end; increment the row.
                // Reset of rows is not necessary
                if (rownum >= (nrows))
                        {
                        rownum = 0;
                        colnum++;
                        }
                } // end forloop

        // Convert to an int
        //Rcpp::Matrix outcombs(combmat_vals);
        
        // example use Armadillo matrix
        // http://dirk.eddelbuettel.com/blog/2011/04/23/
        //arma::mat outcombs = Rcpp::as<arma::mat>(combmat_vals);
        
        return Rcpp::wrap(combmat_vals);
        }
======================================
        

Thanks for any and all help! These memory errors are tough for us biologists!!

Cheers, Nick




--
====================================================
Nicholas J. Matzke
Ph.D. Candidate, Graduate Student Researcher

Huelsenbeck Lab
Center for Theoretical Evolutionary Genomics
4151 VLSB (Valley Life Sciences Building)
Department of Integrative Biology
University of California, Berkeley

Graduate Student Instructor, IB200B
Principles of Phylogenetics: Ecology and Evolution
http://ib.berkeley.edu/courses/ib200b/
http://phylo.wikidot.com/


Lab websites:
http://ib.berkeley.edu/people/lab_detail.php?lab=54
http://fisher.berkeley.edu/cteg/hlab.html
Dept. personal page: http://ib.berkeley.edu/people/students/person_detail.php?person=370 Lab personal page: http://fisher.berkeley.edu/cteg/members/matzke.html
Lab phone: 510-643-6299
Dept. fax: 510-643-6264

Cell phone: 510-301-0179
Email: mat...@berkeley.edu

Mailing address:
Department of Integrative Biology
1005 Valley Life Sciences Building #3140
Berkeley, CA 94720-3140

-----------------------------------------------------
"[W]hen people thought the earth was flat, they were wrong. When people thought the earth was spherical, they were wrong. But if you think that thinking the earth is spherical is just as wrong as thinking the earth is flat, then your view is wronger than both of them put together."

Isaac Asimov (1989). "The Relativity of Wrong." The Skeptical Inquirer, 14(1), 35-44. Fall 1989.
http://chem.tufts.edu/AnswersInScience/RelativityofWrong.htm

______________________________________________
R-help@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.

Reply via email to