[R] How to a handle an error in a loop

Martin Morgan mtmorgan at fhcrc.org
Sun May 7 04:28:17 CEST 2006


Here's another approach -- 'wrap' the problematic function in a
safety-wrapper, so that it always returns some kind of value.

Here's the wrapper

safetyWrapper <- function(FUN, .badValue=NA)
  function(...) tryCatch(FUN(...), error=function(err) .badValue)

and the problmeatic function, stopping with probability 'prob':
 
sometimeStopFunc <- function(i, prob) {
  if (runif(1) < prob) stop("stopped")
  else i
}

Here's the problematic function in action (using sapply to produce
more compact output for email purposes)

> sapply(1:20, sometimeStopFunc, prob=.2)
Error in FUN(X[[2]], ...) : stopped

We can wrap the troublesome function in our wrapper

> neverStopFunc <- safetyWrapper(sometimeStopFunc)

and then obtain results 

> sapply(1:20, neverStopFunc, prob=.2)
 [1]  1  2  3 NA  5  6  7 NA  9 NA NA 12 NA NA NA 16 17 NA 19 20

these could be filtered...

> res <- sapply(1:20, neverStopFunc, prob=.2)
> res[!is.na(res)]
 [1]  1  2  3  4  5  6  7  8 10 11 12 13 14 15 16 18 19 20

or a different type of result used to signal failure...

> neverStopFunc <- safetyWrapper(sometimeStopFunc, .badValue=-1)
> sapply(1:20, neverStopFunc, prob=.2)
 [1]  1  2 -1  4  5  6  7  8 -1 10 11 -1 -1 -1 -1 16 17 -1 19 20

Maybe it's possible to use restarts to do the calculation over again?

Martin


"Farrel Buchinsky" <fjbuch at gmail.com> writes:

> "Berton Gunter" <gunter.berton at gene.com> wrote in message 
> news:008601c67097$de1b46e0$5bc4fea9 at gne.windows.gene.com...
>> ?try
>>
>> as in
>>
>> result<- try (some R expression...)
>> if (inherits(result,'try-error')) ...do something
>> else ...do something else
>
> No heaven on earth yet.
>
> how would I incorporate this kind of functionality into
> Resultdt<-lapply(PGWide[,240:389], tdt)
>
> everything would have to be built into the tdt spot in the above statement.
> How does one get the if...else in there? Does one have to do that as one 
> would program a function or could one write the if...else right into 
> "Resultdt<-lapply(PGWide[,240:389], tdt)"
>
> This works
>> for (few in c(9,10,11,12,243,20)) if 
>> (inherits(try(tdt(PGWide[,few])),'try-error')) print("messed up") else 
>> print("works")
> [1] "works"
> [1] "works"
> [1] "works"
> [1] "works"
> Error in rep.default(1, nrow(U)) : rep() incorrect type for second argument
> In addition: Warning messages:
> 1: 1 misinheritances in: phase.resolve(g.cs, g.mr, g.fr, as.allele.pair = 
> TRUE, allow.ambiguous = (parent ==
> 2: 2 misinheritances in: phase.resolve(g.cs, g.mr, g.fr, as.allele.pair = 
> TRUE, allow.ambiguous = (parent ==
> 3: 2 misinheritances in: phase.resolve(g.cs, g.mr, g.fr, as.allele.pair = 
> TRUE, allow.ambiguous = (parent ==
> 4: 4 misinheritances in: phase.resolve(g.cs, g.mr, g.fr, as.allele.pair = 
> TRUE, allow.ambiguous = (parent ==
> [1] "messed up"
> [1] "works"
> Warning message:
> 1 misinheritances in: phase.resolve(g.cs, g.mr, g.fr, as.allele.pair = TRUE, 
> allow.ambiguous = (parent ==
>
> BUT THIS DOES NOT
>
> lapply(PGWide[,c(9,10,11,12,,243,20)], if (inherits(try(tdt),'try-error') 
> print("messed up") else print("works"))
> Error: syntax error in "lapply(PGWide[,c(9,10,11,12,,243,20)], if 
> (inherits(try(tdt),'try-error') print"
>
> Any idea why...can it be that one cannot have multiple commands on one line
>> p=7 f=8
> Error: syntax error in "p=7 f"
>
> in the lapply, how would R know that I was sending the list to tdt?
>
>
> -- 
> Farrel Buchinsky, MD
> Pediatric Otolaryngologist
> Allegheny General Hospital
> Pittsburgh, PA
>
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html




More information about the R-help mailing list