[Rcpp-devel] Can an Rcpp package include Fortran code?

Avraham Adler avraham.adler at gmail.com
Thu Oct 6 18:19:00 CEST 2016


Has anyone successfully created a package that uses Rcpp for C++ code
and which also has Fortran code? I'm experimenting with comparing
Fortran and C++ and if I could use Rcpp to handle the C++ portion, it
would reduce the steepness of the learning curve.

However, I haven't had success. The following C++ and Fortran snippets
compile properly separately—the C++ as part of Rcpp and the Fortran
using R CMD SHLIB and dynload—and the R snippets call them properly,
but when I put both the .cpp and .f95 files in /src, I get the huge
error posted below the files.

Am I missing something simple or will having C++ and Fortran code in
the same package prevent the use of Rcpp and require the old methods
of calling compiled code?

Thank you,

Avi

**** VecSum_C.cpp ****
#include <Rcpp.h>
using namespace Rcpp;

// [[Rcpp::export]]
double VecSum_C(NumericVector x) {
  int n = x.size();
  double VecSum = 0.0;
  for (int i = 0; i < n; ++i)
    VecSum += x[i];
  return VecSum;
}

**** VecSum_F.f95 ****
subroutine VecSum_F(x, n, x_res)
  implicit none
  integer, parameter :: dp=kind(0.d0)
  integer, intent(in) :: n
  real(dp), dimension(n), intent(in) :: x
  real(dp), intent(out) :: x_res

  integer :: i

  x_res = 0_dp
  do i = 1, n
    x_res = x_res + x(i)
  end do

end subroutine VecSum_F

**** VecSum.R ****
c_vecsum <- function(x) {
  return(VecSum_C(x))
}

f_vecsum <- function(x) {
  Z <- .Fortran('VecSum_F', x = as.double(x), n =
as.integer(length(x)), x_res = double(1L))
  return(Z$x_res)
}

**** ERROR MESSAGE ****
* installing to library 'C:/R/RCurrent/R-3.3.1patched/library'
* installing *source* package 'ForTest' ...
** libs
c:/Rtools/mingw_64/bin/g++  -I"C:/R/RCurrent/R-33~1.1PA/include"
-DNDEBUG    -I"C:/R/RCurrent/R-3.3.1patched/library/Rcpp/include"
-I"C:/R/RLocalSoft/include"     -O3 -Wall  -std=gnu++11 -march=native
-pipe -c RcppExports.cpp -o RcppExports.o
c:/Rtools/mingw_64/bin/g++  -I"C:/R/RCurrent/R-33~1.1PA/include"
-DNDEBUG    -I"C:/R/RCurrent/R-3.3.1patched/library/Rcpp/include"
-I"C:/R/RLocalSoft/include"     -O3 -Wall  -std=gnu++11 -march=native
-pipe -c VecSum_C.cpp -o VecSum_C.o
c:/Rtools/mingw_64/bin/gfortran     -O3  -march=native -pipe
-std=f2003 -c  VecSum_F.f95 -o VecSum_F.o
c:/Rtools/mingw_64/bin/gfortran -shared -s
-Wl,--allow-multiple-definition -static-libgcc -o ForTest.dll tmp.def
RcppExports.o VecSum_C.o VecSum_F.o -LC:/R/RLocalSoft/lib/x64
-LC:/R/RLocalSoft/lib -LC:/R/RCurrent/R-33~1.1PA/bin/x64 -lR
RcppExports.o:RcppExports.cpp:(.text+0x110): undefined reference to
`__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text+0x16b): undefined reference to
`__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text+0x1c4): undefined reference to
`__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text+0x229): undefined reference to
`__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text+0x294): undefined reference to
`__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text+0x2f2): undefined reference to
`__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text+0x322): undefined reference to
`__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text+0x352): undefined reference to
`__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text+0x382): undefined reference to
`__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text+0x472): undefined reference to
`__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text+0x4e7): undefined reference to
`__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text+0x537): undefined reference to
`__cxa_begin_catch'
RcppExports.o:RcppExports.cpp:(.text+0x54f): undefined reference to
`__cxa_end_catch'
RcppExports.o:RcppExports.cpp:(.text+0x5d4): undefined reference to
`__cxa_end_catch'
RcppExports.o:RcppExports.cpp:(.text+0x5e4): undefined reference to
`__cxa_begin_catch'
RcppExports.o:RcppExports.cpp:(.text+0x5fd): undefined reference to
`std::basic_string<char, std::char_traits<char>, std::allocator<char>
>::basic_string(char const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text+0x623): undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text+0x628): undefined reference to
`__cxa_end_catch'
RcppExports.o:RcppExports.cpp:(.text+0x635): undefined reference to
`__cxa_begin_catch'
RcppExports.o:RcppExports.cpp:(.text+0x63a): undefined reference to
`__cxa_end_catch'
RcppExports.o:RcppExports.cpp:(.text+0x65d): undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text+0x662): undefined reference to
`__cxa_end_catch'
RcppExports.o:RcppExports.cpp:(.text+0x6b6): undefined reference to
`__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text+0x6d3): undefined reference to
`__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text+0x6e7): undefined reference to
`__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text+0x6ec): undefined reference to
`std::terminate()'
RcppExports.o:RcppExports.cpp:(.text+0x701): undefined reference to
`__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text+0x18): undefined reference to
`std::ios_base::Init::~Init()'
RcppExports.o:RcppExports.cpp:(.text+0x7b): undefined reference to
`std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text+0xdb): undefined reference to
`std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.xdata+0x30): undefined reference to
`__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb0EED1Ev[_ZN4Rcpp10RstreambufILb0EED1Ev]+0x13):
undefined reference to `std::locale::~locale()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb0EED0Ev[_ZN4Rcpp10RstreambufILb0EED0Ev]+0x1b):
undefined reference to `std::locale::~locale()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb0EED0Ev[_ZN4Rcpp10RstreambufILb0EED0Ev]+0x28):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb1EED1Ev[_ZN4Rcpp10RstreambufILb1EED1Ev]+0x13):
undefined reference to `std::locale::~locale()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb1EED0Ev[_ZN4Rcpp10RstreambufILb1EED0Ev]+0x1b):
undefined reference to `std::locale::~locale()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10RstreambufILb1EED0Ev[_ZN4Rcpp10RstreambufILb1EED0Ev]+0x28):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb0EED1Ev[_ZN4Rcpp8RostreamILb0EED1Ev]+0x4d):
undefined reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb1EED1Ev[_ZN4Rcpp8RostreamILb1EED1Ev]+0x4d):
undefined reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb1EED0Ev[_ZN4Rcpp8RostreamILb1EED0Ev]+0x48):
undefined reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb1EED0Ev[_ZN4Rcpp8RostreamILb1EED0Ev]+0x55):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb0EED0Ev[_ZN4Rcpp8RostreamILb0EED0Ev]+0x48):
undefined reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8RostreamILb0EED0Ev[_ZN4Rcpp8RostreamILb0EED0Ev]+0x55):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD1Ev[_ZN4Rcpp10eval_errorD1Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD1Ev[_ZN4Rcpp10eval_errorD1Ev]+0x3d):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD1Ev[_ZN4Rcpp10eval_errorD1Ev]+0x45):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD1Ev[_ZN4Rcpp9exceptionD1Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD1Ev[_ZN4Rcpp9exceptionD1Ev]+0x3d):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD1Ev[_ZN4Rcpp9exceptionD1Ev]+0x45):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD1Ev[_ZN4Rcpp14not_compatibleD1Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD1Ev[_ZN4Rcpp14not_compatibleD1Ev]+0x3d):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD1Ev[_ZN4Rcpp14not_compatibleD1Ev]+0x45):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD0Ev[_ZN4Rcpp9exceptionD0Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD0Ev[_ZN4Rcpp9exceptionD0Ev]+0x30):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp9exceptionD0Ev[_ZN4Rcpp9exceptionD0Ev]+0x4a):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD0Ev[_ZN4Rcpp10eval_errorD0Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD0Ev[_ZN4Rcpp10eval_errorD0Ev]+0x30):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp10eval_errorD0Ev[_ZN4Rcpp10eval_errorD0Ev]+0x4a):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD0Ev[_ZN4Rcpp14not_compatibleD0Ev]+0x28):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD0Ev[_ZN4Rcpp14not_compatibleD0Ev]+0x30):
undefined reference to `operator delete(void*)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp14not_compatibleD0Ev[_ZN4Rcpp14not_compatibleD0Ev]+0x4a):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal12exitRNGScopeEv[_ZN4Rcpp8internal12exitRNGScopeEv]+0x16):
undefined reference to `__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal12exitRNGScopeEv[_ZN4Rcpp8internal12exitRNGScopeEv]+0x52):
undefined reference to `__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal12exitRNGScopeEv[_ZN4Rcpp8internal12exitRNGScopeEv]+0x73):
undefined reference to `__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.xdata$_ZN4Rcpp8internal12exitRNGScopeEv+0x8):
undefined reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.xdata$_Z19string_to_try_errorRKSs+0x10):
undefined reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp4stopERKSs[_ZN4Rcpp4stopERKSs]+0xf):
undefined reference to `__cxa_allocate_exception'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp4stopERKSs[_ZN4Rcpp4stopERKSs]+0x2d):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp4stopERKSs[_ZN4Rcpp4stopERKSs]+0x43):
undefined reference to `__cxa_throw'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp4stopERKSs[_ZN4Rcpp4stopERKSs]+0x51):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp4stopERKSs[_ZN4Rcpp4stopERKSs]+0x59):
undefined reference to `__cxa_free_exception'
RcppExports.o:RcppExports.cpp:(.xdata$_ZN4Rcpp4stopERKSs+0xc):
undefined reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x3d):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x52):
undefined reference to `__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x96):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0xab):
undefined reference to `__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x499):
undefined reference to `__cxa_guard_acquire'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x55d):
undefined reference to `__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x588):
undefined reference to `__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x5b3):
undefined reference to `__cxa_guard_release'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x621):
undefined reference to `__cxa_allocate_exception'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x64e):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x664):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char>
>::basic_string(std::string const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x691):
undefined reference to `__cxa_throw'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x6b2):
undefined reference to `__cxa_allocate_exception'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x6c4):
undefined reference to `__cxa_throw'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x6da):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x6eb):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x6fc):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x7d7):
undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x7e8):
undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x7fe):
undefined reference to
`std::string::_Rep::_M_destroy(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x814):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x830):
undefined reference to `__cxa_free_exception'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x83a):
undefined reference to `__cxa_call_unexpected'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x961):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x987):
undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x9c8):
undefined reference to `__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x9df):
undefined reference to `__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0x9f2):
undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_Z24exception_to_r_conditionRKSt9exception[_Z24exception_to_r_conditionRKSt9exception]+0xab6):
undefined reference to `__cxa_guard_abort'
RcppExports.o:RcppExports.cpp:(.xdata$_Z24exception_to_r_conditionRKSt9exception+0x18):
undefined reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0x66):
undefined reference to `__cxa_allocate_exception'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0x7d):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char> >::basic_string(char
const*, std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0x93):
undefined reference to `std::basic_string<char,
std::char_traits<char>, std::allocator<char>
>::basic_string(std::string const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0xa6):
undefined reference to
`std::string::_Rep::_M_dispose(std::allocator<char> const&)'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0xbc):
undefined reference to `__cxa_throw'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0xca):
undefined reference to `__cxa_free_exception'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0xe3):
undefined reference to `std::exception::~exception()'
RcppExports.o:RcppExports.cpp:(.text$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_[_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_]+0xf1):
undefined reference to `__cxa_call_unexpected'
RcppExports.o:RcppExports.cpp:(.xdata$_ZN4Rcpp8internal10basic_castILi14EEEP7SEXPRECS3_+0xc):
undefined reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.text.startup+0xf): undefined reference
to `std::ios_base::Init::Init()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x33): undefined
reference to `std::ios_base::ios_base()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x94): undefined
reference to `operator new(unsigned long long)'
RcppExports.o:RcppExports.cpp:(.text.startup+0xde): undefined
reference to `std::locale::locale()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x113): undefined
reference to `std::basic_ios<char, std::char_traits<char>
>::init(std::basic_streambuf<char, std::char_traits<char> >*)'
RcppExports.o:RcppExports.cpp:(.text.startup+0x155): undefined
reference to `std::ios_base::ios_base()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x1af): undefined
reference to `operator new(unsigned long long)'
RcppExports.o:RcppExports.cpp:(.text.startup+0x1f2): undefined
reference to `std::locale::locale()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x227): undefined
reference to `std::basic_ios<char, std::char_traits<char>
>::init(std::basic_streambuf<char, std::char_traits<char> >*)'
RcppExports.o:RcppExports.cpp:(.text.startup+0x281): undefined
reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.text.startup+0x2a6): undefined
reference to `std::ios_base::~ios_base()'
RcppExports.o:RcppExports.cpp:(.xdata.startup+0xc): undefined
reference to `__gxx_personality_seh0'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTISt9exception[_ZTISt9exception]+0x0):
undefined reference to `vtable for __cxxabiv1::__class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp9exceptionE[_ZTIN4Rcpp9exceptionE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp14not_compatibleE[_ZTIN4Rcpp14not_compatibleE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp10eval_errorE[_ZTIN4Rcpp10eval_errorE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp8internal20InterruptedExceptionE[_ZTIN4Rcpp8internal20InterruptedExceptionE]+0x0):
undefined reference to `vtable for __cxxabiv1::__class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp10RstreambufILb1EEE[_ZTIN4Rcpp10RstreambufILb1EEE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp10RstreambufILb1EEE[_ZTIN4Rcpp10RstreambufILb1EEE]+0x10):
undefined reference to `typeinfo for std::basic_streambuf<char,
std::char_traits<char> >'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp10RstreambufILb0EEE[_ZTIN4Rcpp10RstreambufILb0EEE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp10RstreambufILb0EEE[_ZTIN4Rcpp10RstreambufILb0EEE]+0x10):
undefined reference to `typeinfo for std::basic_streambuf<char,
std::char_traits<char> >'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp8RostreamILb1EEE[_ZTIN4Rcpp8RostreamILb1EEE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp8RostreamILb1EEE[_ZTIN4Rcpp8RostreamILb1EEE]+0x10):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp8RostreamILb0EEE[_ZTIN4Rcpp8RostreamILb0EEE]+0x0):
undefined reference to `vtable for __cxxabiv1::__si_class_type_info'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTIN4Rcpp8RostreamILb0EEE[_ZTIN4Rcpp8RostreamILb0EEE]+0x10):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x20):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::imbue(std::locale const&)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x28):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::setbuf(char*, long long)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x30):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::seekoff(long long, std::_Ios_Seekdir,
std::_Ios_Openmode)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x38):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::seekpos(std::fpos<int>, std::_Ios_Openmode)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x48):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::showmanyc()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x50):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::xsgetn(char*, long long)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x58):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::underflow()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x60):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::uflow()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb1EEE[_ZTVN4Rcpp10RstreambufILb1EEE]+0x68):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::pbackfail(int)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x20):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::imbue(std::locale const&)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x28):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::setbuf(char*, long long)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x30):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::seekoff(long long, std::_Ios_Seekdir,
std::_Ios_Openmode)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x38):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::seekpos(std::fpos<int>, std::_Ios_Openmode)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x48):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::showmanyc()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x50):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::xsgetn(char*, long long)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x58):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::underflow()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x60):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::uflow()'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTVN4Rcpp10RstreambufILb0EEE[_ZTVN4Rcpp10RstreambufILb0EEE]+0x68):
undefined reference to `std::basic_streambuf<char,
std::char_traits<char> >::pbackfail(int)'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTCN4Rcpp8RostreamILb1EEE0_So[_ZTCN4Rcpp8RostreamILb1EEE0_So]+0x10):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTCN4Rcpp8RostreamILb1EEE0_So[_ZTCN4Rcpp8RostreamILb1EEE0_So]+0x38):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTCN4Rcpp8RostreamILb0EEE0_So[_ZTCN4Rcpp8RostreamILb0EEE0_So]+0x10):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$_ZTCN4Rcpp8RostreamILb0EEE0_So[_ZTCN4Rcpp8RostreamILb0EEE0_So]+0x38):
undefined reference to `typeinfo for std::ostream'
RcppExports.o:RcppExports.cpp:(.rdata$.refptr._ZTVSt9basic_iosIcSt11char_traitsIcEE[.refptr._ZTVSt9basic_iosIcSt11char_traitsIcEE]+0x0):
undefined reference to `vtable for std::basic_ios<char,
std::char_traits<char> >'
RcppExports.o:RcppExports.cpp:(.rdata$.refptr._ZTVSt15basic_streambufIcSt11char_traitsIcEE[.refptr._ZTVSt15basic_streambufIcSt11char_traitsIcEE]+0x0):
undefined reference to `vtable for std::basic_streambuf<char,
std::char_traits<char> >'
VecSum_C.o:VecSum_C.cpp:(.text+0x18): undefined reference to
`std::ios_base::Init::~Init()'
VecSum_C.o:VecSum_C.cpp:(.text+0x7b): undefined reference to
`std::ios_base::~ios_base()'
VecSum_C.o:VecSum_C.cpp:(.text+0xdb): undefined reference to
`std::ios_base::~ios_base()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0xf): undefined reference to
`std::ios_base::Init::Init()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x33): undefined reference to
`std::ios_base::ios_base()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x94): undefined reference to
`operator new(unsigned long long)'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0xde): undefined reference to
`std::locale::locale()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x113): undefined reference to
`std::basic_ios<char, std::char_traits<char>
>::init(std::basic_streambuf<char, std::char_traits<char> >*)'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x155): undefined reference to
`std::ios_base::ios_base()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x1af): undefined reference to
`operator new(unsigned long long)'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x1f2): undefined reference to
`std::locale::locale()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x227): undefined reference to
`std::basic_ios<char, std::char_traits<char>
>::init(std::basic_streambuf<char, std::char_traits<char> >*)'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x281): undefined reference to
`std::ios_base::~ios_base()'
VecSum_C.o:VecSum_C.cpp:(.text.startup+0x2a6): undefined reference to
`std::ios_base::~ios_base()'
VecSum_C.o:VecSum_C.cpp:(.xdata.startup+0xc): undefined reference to
`__gxx_personality_seh0'
collect2.exe: error: ld returned 1 exit status
no DLL was created
ERROR: compilation failed for package 'ForTest'
* removing 'C:/R/RCurrent/R-3.3.1patched/library/ForTest'
* restoring previous 'C:/R/RCurrent/R-3.3.1patched/library/ForTest'
Warning in file.copy(lp, dirname(pkgdir), recursive = TRUE, copy.date = TRUE) :
  problem copying
C:\R\RCurrent\R-3.3.1patched\library\00LOCK-ForTest\ForTest\libs\x64\ForTest.dll
to C:\R\RCurrent\R-3.3.1patched\library\ForTest\libs\x64\ForTest.dll:
Permission denied

Exited with status 1.


More information about the Rcpp-devel mailing list