[R] No traceback available when using try(...)
    Edouard DUCHESNAY 
    duchesnay at shfj.cea.fr
       
    Mon Mar 15 14:58:22 CET 2004
    
    
  
The Luke's proposition it works fine.
I have extended the code proposed by Luke, to implemtent a "myTry()" and a "mytraceback()".
They print the function stack and the variables of each functions, it may helps.
---------- mytry.R -------------------------------------------------------------------------------------------------------------------------------------------------------
myTry <- function(expr) {
  withRestarts(
               withCallingHandlers(expr,
                                   error = function(e) {
                                     error  = e
                                     calls  = sys.calls()
                                     frames = sys.frames()
                                     invokeRestart("myAbort", e, calls, frames)
                                   }),
               myAbort = function(e, calls, frames){
                 err = list(error = e, calls=calls, frames=frames)
                 class(err)<-c("try-error")
                 return(err)
               }
               )
}
myTraceback <- function(trace, optFunctions2Skip=c() ){
  functions2Skip = c('withRestarts','withCallingHandlers','invokeRestart', 'withOneRestart' ,'myTry', 'doWithOneRestart', '.handleSimpleError', optFunctions2Skip)
  for( i in 1:length(trace$frames)){
    env  = trace$frames[[ i ]]
    func = trace$calls [[ i ]]
    funcStr  = as.character(trace$calls[[i]])
    
    funcNameStr = funcStr[1]
    args=FALSE
    simple.Error=FALSE
    
    if(length(funcStr) > 1){
      funcArgs    = funcStr[2:length(funcStr)]
      args = TRUE
      if(any(grep('simpleError',funcArgs))){simple.Error=TRUE}
    }
    if ( !(funcNameStr %in% functions2Skip) && !simple.Error){
      cat('\n---------------------------------\n')
      if(args) cat(funcNameStr,'(',funcArgs,')','\n')
      else     cat(funcNameStr,'()','\n')
      cat('- - - - - - - - - - - - - - - - -\n')
      
      vars=ls(env)
      for(v in vars){
        cat(v,'=')
        print(get(v, envir=env))
      }
    }
  }
}
-------------------------------------------------------------------------------------------------------------------------------------------------------
---- Exemple.R ---------------------------------------------------------------------------------------------------------------------------------
f<-function(a,b){
  return(regexpr(a,b))
}
g<-function(a,b){f(a,b)}
TEST<-function(){
  myTry(1+2)
  r = myTry(g("A",2))
  return( r )
}
r=TEST()
if(inherits(r,'try-error')){
  print(r$error)
  myTraceback(r, optFunctions2Skip='TEST')
}
-------------------------------------------------------------------------------------------------------------------------------------------------------
-- 
Edouard Duchesnay                      Tel: +33 1 69 86 78 52
CEA - SHFJ                             Fax: +33 1 69 86 77 86
4, place du Général Leclerc
91401 Orsay Cedex France
    
    
More information about the R-help
mailing list