Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 7 additions & 0 deletions ChangeLog
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,13 @@

* inst/include/Rcpp/date_datetime/newDatetimeVector.h: Added constructor
to instantiate newDatetimeVector from VectorBase.
2016-11-11 Jim Hester <james.f.hester@gmail.com>
* inst/include/rcpp/exceptions.h: Return stack trace even if no file
or line is specified. Fix R calls when using Rcpp_eval.
* inst/include/rcpp/routines.h:allow getting a cppstack without specifying a file and line.
* src/api.cpp: Add cppstack support for clang.
* r/exceptions.r:Add a str method for Rcpp_stack_trace objects.
* NAMESPACE: Idem

2016-11-04 Nathan Russell <russell.nr2012@gmail.com>

Expand Down
5 changes: 4 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,13 @@ export(Module,
demangle,
sizeof,
cpp_object_initializer,
cpp_object_dummy,
cpp_object_dummy,
Rcpp.plugin.maker
)
S3method(print, bytes)
S3method(format, Rcpp_stack_trace)
S3method(str, Rcpp_stack_trace)
S3method(print, Rcpp_stack_trace)
exportClass(RcppClass)


12 changes: 12 additions & 0 deletions R/exceptions.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,4 +33,16 @@
warnings
}

print.Rcpp_stack_trace <- function(x, ...) {
cat(format(x, ...))
}

str.Rcpp_stack_trace <- function(object, ...) {
cat(format(object, ...))
}

format.Rcpp_stack_trace <- function(x, ...) {
paste0(
if (nzchar(x$file)) paste0(x$file, ":", x$line),
"\n ", paste(collapse = "\n ", seq_along(x$stack), ":", x$stack), "\n")
}
78 changes: 58 additions & 20 deletions inst/include/Rcpp/exceptions.h
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ namespace Rcpp{

class exception : public std::exception {
public:
explicit exception(const char* message_) : message(message_){}
explicit exception(const char* message_) : message(message_){ rcpp_set_stack_trace(stack_trace()); }
exception(const char* message_, const char* file, int line ) : message(message_){
rcpp_set_stack_trace( stack_trace(file,line) ) ;
}
Expand Down Expand Up @@ -124,20 +124,58 @@ namespace Rcpp{
#undef RCPP_SIMPLE_EXCEPTION_CLASS


namespace internal {
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Looks like this accidentally was left outside of the outer namespace Rcpp bombing compilation:

https://travis-ci.org/RcppCore/Rcpp#L2618

na.cpp:27:12: error: reference to ‘internal’ is ambiguous
     return internal::Rcpp_IsNA(x);
            ^
In file included from /home/travis/build/RcppCore/Rcpp/Rcpp.Rcheck/Rcpp/include/RcppCommon.h:122:0,
                 from /home/travis/build/RcppCore/Rcpp/Rcpp.Rcheck/Rcpp/include/Rcpp.h:27,
                 from na.cpp:22:
/home/travis/build/RcppCore/Rcpp/Rcpp.Rcheck/Rcpp/include/Rcpp/exceptions.h:129:20: note: candidates are: namespace internal { }
 namespace internal {
                    ^
In file included from /home/travis/build/RcppCore/Rcpp/Rcpp.Rcheck/Rcpp/include/Rcpp.h:27:0,
                 from na.cpp:22:
/home/travis/build/RcppCore/Rcpp/Rcpp.Rcheck/Rcpp/include/RcppCommon.h:45:24: note:                 namespace Rcpp::internal { }
     namespace internal {
                        ^


inline SEXP nth(SEXP s, int n) {
return Rf_length(s) > n ? (n == 0 ? CAR(s) : CAR(Rf_nthcdr(s, n))) : R_NilValue;
}

// We want the call just prior to the call from Rcpp_eval
// This conditional matches
// tryCatch(evalq(sys.calls(), .GlobalEnv), error = identity, interrupt = identity)
inline bool is_Rcpp_eval_call(SEXP expr) {
SEXP sys_calls_symbol = Rf_install("sys.calls");
SEXP identity_symbol = Rf_install("identity");
SEXP identity_fun = Rf_findFun(identity_symbol, R_BaseEnv);
SEXP tryCatch_symbol = Rf_install("tryCatch");
SEXP evalq_symbol = Rf_install("evalq");

return TYPEOF(expr) == LANGSXP &&
Rf_length(expr) == 4 &&
nth(expr, 0) == tryCatch_symbol &&
CAR(nth(expr, 1)) == evalq_symbol &&
CAR(nth(nth(expr, 1), 1)) == sys_calls_symbol &&
nth(nth(expr, 1), 2) == R_GlobalEnv &&
nth(expr, 2) == identity_fun &&
nth(expr, 3) == identity_fun;
}
}

} // namespace Rcpp

inline SEXP get_last_call(){
SEXP sys_calls_symbol = Rf_install( "sys.calls" ) ;
Rcpp::Shield<SEXP> sys_calls_expr( Rf_lang1(sys_calls_symbol) );
Rcpp::Shield<SEXP> calls( Rcpp_eval( sys_calls_expr, R_GlobalEnv ) );
SEXP res = calls ;
while( !Rf_isNull(CDR(res)) ) res = CDR(res);
return CAR(res) ;
SEXP sys_calls_symbol = Rf_install("sys.calls");

Rcpp::Shield<SEXP> sys_calls_expr(Rf_lang1(sys_calls_symbol));
Rcpp::Shield<SEXP> calls(Rcpp_eval(sys_calls_expr, R_GlobalEnv));

SEXP cur, prev;
prev = cur = calls;
while(CDR(cur) != R_NilValue) {
SEXP expr = CAR(cur);

if (Rcpp::internal::is_Rcpp_eval_call(expr)) {
break;
}
prev = cur;
cur = CDR(cur);
}
return CAR(prev);
}

inline SEXP get_exception_classes( const std::string& ex_class) {
Rcpp::Shield<SEXP> res( Rf_allocVector( STRSXP, 4 ) );

#ifndef RCPP_USING_UTF8_ERROR_STRING
SET_STRING_ELT( res, 0, Rf_mkChar( ex_class.c_str() ) ) ;
#else
Expand Down Expand Up @@ -184,7 +222,7 @@ inline SEXP exception_to_r_condition( const std::exception& ex){

inline SEXP string_to_try_error( const std::string& str){
using namespace Rcpp;

#ifndef RCPP_USING_UTF8_ERROR_STRING
Rcpp::Shield<SEXP> simpleErrorExpr( Rf_lang2(::Rf_install("simpleError"), Rf_mkString(str.c_str())) );
Rcpp::Shield<SEXP> tryError( Rf_mkString( str.c_str() ) );
Expand All @@ -193,7 +231,7 @@ inline SEXP string_to_try_error( const std::string& str){
SET_STRING_ELT( tryError, 0, Rf_mkCharLenCE( str.c_str(), str.size(), CE_UTF8 ) );
Rcpp::Shield<SEXP> simpleErrorExpr( Rf_lang2(::Rf_install("simpleError"), tryError ));
#endif

Rcpp::Shield<SEXP> simpleError( Rf_eval(simpleErrorExpr, R_GlobalEnv) );
Rf_setAttrib( tryError, R_ClassSymbol, Rf_mkString("try-error") ) ;
Rf_setAttrib( tryError, Rf_install( "condition") , simpleError ) ;
Expand Down Expand Up @@ -267,52 +305,52 @@ namespace Rcpp{
inline void NORET stop(const std::string& message) {
throw Rcpp::exception(message.c_str());
}

template <typename T1>
inline void NORET stop(const char* fmt, const T1& arg1) {
throw Rcpp::exception( tfm::format(fmt, arg1 ).c_str() );
}

template <typename T1, typename T2>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2 ).c_str() );
}

template <typename T1, typename T2, typename T3>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5, typename T6>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5, const T6& arg6) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5, arg6).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5, typename T6, typename T7>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5, const T6& arg6, const T7& arg7) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5, arg6, arg7).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5, typename T6, typename T7, typename T8>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5, const T6& arg6, const T7& arg7, const T8& arg8) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5, arg6, arg7, arg8).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5, typename T6, typename T7, typename T8, typename T9>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5, const T6& arg6, const T7& arg7, const T8& arg8, const T9& arg9) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5, arg6, arg7, arg8, arg9).c_str() );
}

template <typename T1, typename T2, typename T3, typename T4, typename T5, typename T6, typename T7, typename T8, typename T9, typename T10>
inline void NORET stop(const char* fmt, const T1& arg1, const T2& arg2, const T3& arg3, const T4& arg4, const T5& arg5, const T6& arg6, const T7& arg7, const T8& arg8, const T9& arg9, const T10& arg10) {
throw Rcpp::exception( tfm::format(fmt, arg1, arg2, arg3, arg4, arg5, arg6, arg7, arg8, arg9, arg10).c_str() );
Expand Down
4 changes: 2 additions & 2 deletions inst/include/Rcpp/routines.h
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ SEXP rcpp_set_stack_trace(SEXP);
std::string demangle(const std::string& name);
const char* short_file_name(const char* );
int* get_cache(int n);
SEXP stack_trace( const char *file, int line);
SEXP stack_trace( const char *file = "", int line = -1);
SEXP get_string_elt(SEXP s, R_xlen_t i);
const char* char_get_string_elt(SEXP s, R_xlen_t i);
void set_string_elt(SEXP s, R_xlen_t i, SEXP v);
Expand Down Expand Up @@ -143,7 +143,7 @@ inline attribute_hidden const char* short_file_name(const char* file) {
return fun(file);
}

inline attribute_hidden SEXP stack_trace( const char *file, int line){
inline attribute_hidden SEXP stack_trace( const char *file = "", int line = -1){
typedef SEXP (*Fun)(const char*, int);
static Fun fun = GET_CALLABLE("stack_trace");
return fun(file, line);
Expand Down
56 changes: 56 additions & 0 deletions inst/unitTests/cpp/exceptions.cpp
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
// -*- mode: C++; c-indent-level: 4; c-basic-offset: 4; indent-tabs-mode: nil; -*-
//
// dates.cpp: Rcpp R/C++ interface class library -- Date + Datetime tests
//
// Copyright (C) 2010 - 2013 Dirk Eddelbuettel and Romain Francois
//
// This file is part of Rcpp.
//
// Rcpp is free software: you can redistribute it and/or modify it
// under the terms of the GNU General Public License as published by
// the Free Software Foundation, either version 2 of the License, or
// (at your option) any later version.
//
// Rcpp is distributed in the hope that it will be useful, but
// WITHOUT ANY WARRANTY; without even the implied warranty of
// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
// GNU General Public License for more details.
//
// You should have received a copy of the GNU General Public License
// along with Rcpp. If not, see <http://www.gnu.org/licenses/>.

#include <Rcpp.h>
using namespace Rcpp;

// [[Rcpp::export]]
double takeLog(double val) {
if (val <= 0.0) {
throw std::range_error("Inadmissible value");
}
return log(val);
}

// [[Rcpp::export]]
double takeLogRcpp(double val) {
if (val <= 0.0) {
throw Rcpp::exception("Inadmissible value");
}
return log(val);
}

// [[Rcpp::export]]
double takeLogRcppLocation(double val) {
if (val <= 0.0) {
throw Rcpp::exception("Inadmissible value", "exceptions.cpp", 44);
}
return log(val);
}

double f1(double val) {
return takeLogRcppLocation(val);
}

// [[Rcpp::export]]
double takeLogNested(double val) {
return f1(val);
}
95 changes: 95 additions & 0 deletions inst/unitTests/runit.exceptions.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,95 @@
#!/usr/bin/env r
# -*- mode: R; tab-width: 4; -*-
#
# Copyright (C) 2010 - 2013 Dirk Eddelbuettel and Romain Francois
#
# This file is part of Rcpp.
#
# Rcpp is free software: you can redistribute it and/or modify it
# under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 of the License, or
# (at your option) any later version.
#
# Rcpp is distributed in the hope that it will be useful, but
# WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with Rcpp. If not, see <http://www.gnu.org/licenses/>.
.runThisTest <- Sys.getenv("RunAllRcppTests") == "yes"

if (.runThisTest) {
.setUp <- Rcpp:::unitTestSetup("exceptions.cpp")

test.stdException <- function() {

# Code works normally without an exception
checkIdentical(takeLog(1L), log(1L))

# C++ exceptions are converted to R conditions
condition <- tryCatch(takeLog(-1L), error = identity)

checkIdentical(condition$message, "Inadmissible value")
checkIdentical(class(condition), c("std::range_error", "C++Error", "error", "condition"))

# C++ stack only available for Rcpp::exceptions
checkTrue(is.null(condition$cppstack))

checkIdentical(condition$call, quote(takeLog(-1L)))
}


test.rcppException <- function() {

# Code works normally without an exception
checkIdentical(takeLog(1L), log(1L))

# C++ exceptions are converted to R conditions
condition <- tryCatch(takeLogRcpp(-1L), error = identity)

checkIdentical(condition$message, "Inadmissible value")
checkIdentical(class(condition), c("Rcpp::exception", "C++Error", "error", "condition"))

checkTrue(!is.null(condition$cppstack))

checkIdentical(class(condition$cppstack), "Rcpp_stack_trace")

checkEquals(condition$call, quote(takeLogRcpp(-1L)))
}

test.rcppExceptionLocation <- function() {

# Code works normally without an exception
checkIdentical(takeLog(1L), log(1L))

# C++ exceptions are converted to R conditions
condition <- tryCatch(takeLogRcppLocation(-1L), error = identity)

checkIdentical(condition$message, "Inadmissible value")
checkIdentical(class(condition), c("Rcpp::exception", "C++Error", "error", "condition"))

checkTrue(!is.null(condition$cppstack))
checkIdentical(class(condition$cppstack), "Rcpp_stack_trace")

checkIdentical(condition$cppstack$file, "exceptions.cpp")
checkIdentical(condition$cppstack$line, 44L)

checkEquals(condition$call, quote(takeLogRcppLocation(-1L)))
}

test.rcppExceptionLocation <- function() {

# Nested exceptions work the same way
normal <- tryCatch(takeLogRcppLocation(-1L), error = identity)
f1 <- function(x) takeLogNested(x)

nested <- tryCatch(f1(-1), error = identity)

# Message the same
checkIdentical(normal$message, nested$message)

checkEquals(nested$call, quote(takeLogNested(x)))
}

}
4 changes: 2 additions & 2 deletions src/api.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ using namespace Rcpp;
#include <cxxabi.h>
#endif

#if defined(__GNUC__)
#if defined(__GNUC__) || defined(__clang__)
#if defined(_WIN32) || defined(__FreeBSD__) || defined(__NetBSD__) || defined(__OpenBSD__) || defined(__CYGWIN__) || defined(__sun) || defined(_AIX) || defined(__MUSL__)
// do nothing
#else
Expand Down Expand Up @@ -262,7 +262,7 @@ SEXP rcpp_can_use_cxx11() {

// [[Rcpp::register]]
SEXP stack_trace(const char* file, int line) {
#if defined(__GNUC__)
#if defined(__GNUC__) || defined(__clang__)
#if defined(_WIN32) || defined(__FreeBSD__) || defined(__NetBSD__) || defined(__OpenBSD__) || defined(__CYGWIN__) || defined(__sun) || defined(_AIX) || defined(__MUSL__)
// Simpler version for Windows and *BSD
List trace = List::create(_["file"] = file,
Expand Down