[Zooimage-commits] r96 - pkg/zooimage/R
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Tue Apr 21 11:35:21 CEST 2009
Author: romain
Date: 2009-04-21 11:35:16 +0200 (Tue, 21 Apr 2009)
New Revision: 96
Modified:
pkg/zooimage/R/ZIRes.r
pkg/zooimage/R/utilities.r
Log:
remove NULL from the list in list.add before adding
Modified: pkg/zooimage/R/ZIRes.r
===================================================================
--- pkg/zooimage/R/ZIRes.r 2009-04-21 09:30:07 UTC (rev 95)
+++ pkg/zooimage/R/ZIRes.r 2009-04-21 09:35:16 UTC (rev 96)
@@ -152,15 +152,16 @@
# Extract only data for a given sample
# Sample is everything before a '+' sign
Smps <- sub("[+].*", "", as.character(ZIDat$Label))
- mustcontain( unique(Smps), sample, msg = paste( "sample '", sample, "' is not in ZIDat", sep = "" ) )
+ mustcontain( unique(Smps), sample,
+ msg = paste( "sample '", sample, "' is not in ZIDat", sep = "" ) )
Smp <- ZIDat[Smps == sample, ]
# Determine the number of images in this sample
imgs <- unique(ZIDat$Label)
-
res <- list.add( lapply( imgs, function(im){
- Spectrum(Smp, imgs[1], taxa = taxa, groups = groups,
- breaks = breaks, use.Dil = use.Dil)
+ tryCatch( Spectrum(Smp, im, taxa = taxa, groups = groups,
+ breaks = breaks, use.Dil = use.Dil),
+ zooImageError = NULL )
} ) )
return(res)
}
Modified: pkg/zooimage/R/utilities.r
===================================================================
--- pkg/zooimage/R/utilities.r 2009-04-21 09:30:07 UTC (rev 95)
+++ pkg/zooimage/R/utilities.r 2009-04-21 09:35:16 UTC (rev 96)
@@ -424,8 +424,8 @@
# }}}
# {{{ Add items across two lists (names must be the same)
-# not used
list.add <- function( ..., .list = list(...) ){
+ .list <- .list[ !sapply( .list, is.null) ]
if( length(.list) == 1 ) return( .list[[1]] )
n <- length( .list[[1]] )
out <- lapply( 1:n, function(i){
@@ -507,6 +507,7 @@
tkconfigure( getTemp("statusProg") , value = 0)
tkconfigure( getTemp("statusText") , text = paste("Ready -", getwd()))
}
+ invisible( NULL )
}
backspaces <- function( n = getOption("width") ){
paste( rep("\b", ), collapse = "" )
More information about the Zooimage-commits
mailing list