git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@54643 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for Affymetrix SNP 5.0 and 6.0 and Illumina arrays. |
4 |
-Version: 1.9.28 |
|
4 |
+Version: 1.9.29 |
|
5 | 5 |
Date: 2010-12-10 |
6 | 6 |
Author: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>, Ingo Ruczinski <iruczins@jhsph.edu>, Rafael A Irizarry |
7 | 7 |
Maintainer: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
... | ... |
@@ -1257,7 +1257,7 @@ fit.lm4 <- function(strata, |
1257 | 1257 |
nuB(object)[marker.index, batch.index] <- nuB |
1258 | 1258 |
phiB(object)[marker.index, batch.index] <- phiB |
1259 | 1259 |
##if(is.lds) {close(object); return(TRUE)} else return(object) |
1260 |
- TRUE |
|
1260 |
+ if(is.lds) {close(object); return(TRUE)} else return(object) |
|
1261 | 1261 |
} |
1262 | 1262 |
|
1263 | 1263 |
whichPlatform <- function(cdfName){ |
... | ... |
@@ -2026,7 +2026,8 @@ crlmmCopynumber <- function(object, |
2026 | 2026 |
MIN.PHI=2^3, |
2027 | 2027 |
THR.NU.PHI=TRUE, |
2028 | 2028 |
type=c("SNP", "NP", "X.SNP", "X.NP")){ |
2029 |
- stopifnot(type %in% c("SNP", "NP", "X.SNP", "X.NP")) |
|
2029 |
+ typeof <- paste(type, collapse=",") |
|
2030 |
+ stopifnot(typeof %in% c("SNP", "NP", "SNP,NP", "SNP,X.SNP", "SNP,X.NP", "SNP,NP,X.SNP", "SNP,NP,X.SNP,X.NP")) |
|
2030 | 2031 |
if(GT.CONF.THR >= 1 | GT.CONF.THR < 0) stop("GT.CONF.THR must be in [0,1)") |
2031 | 2032 |
batch <- batch(object) |
2032 | 2033 |
is.snp <- isSnp(object) |
... | ... |
@@ -2089,7 +2090,7 @@ crlmmCopynumber <- function(object, |
2089 | 2090 |
marker.index <- whichMarkers(marker.type, is.snp, |
2090 | 2091 |
is.autosome, is.annotated, is.X) |
2091 | 2092 |
if(length(marker.index) == 0) next() |
2092 |
- object <- estimateCnParameters(object=object, |
|
2093 |
+ res <- estimateCnParameters(object=object, |
|
2093 | 2094 |
type=marker.type, |
2094 | 2095 |
SNRMin=SNRMin, |
2095 | 2096 |
DF.PRIOR=DF.PRIOR, |
... | ... |
@@ -2103,6 +2104,8 @@ crlmmCopynumber <- function(object, |
2103 | 2104 |
marker.index=marker.index, |
2104 | 2105 |
is.lds=is.lds, |
2105 | 2106 |
CHR.X=CHR.X) |
2107 |
+ ##if(!is.lds) {object <- res; rm(res); gc()} |
|
2108 |
+ ##if(!is.lds) {object <- res; rm(res); gc()} |
|
2106 | 2109 |
} |
2107 | 2110 |
close(object) |
2108 | 2111 |
if(is.lds) return(TRUE) else return(object) |
... | ... |
@@ -1009,16 +1009,16 @@ getProtocolData.Illumina = function(filenames, sep="_", fileExt="Grn.idat", verb |
1009 | 1009 |
|
1010 | 1010 |
|
1011 | 1011 |
constructInf <- function(sampleSheet=NULL, |
1012 |
- arrayNames=NULL, |
|
1013 |
- path=".", |
|
1014 |
- arrayInfoColNames=list(barcode="SentrixBarcode_A", position="SentrixPosition_A"), |
|
1015 |
- highDensity=FALSE, |
|
1016 |
- sep="_", |
|
1017 |
- fileExt=list(green="Grn.idat", red="Red.idat"), |
|
1018 |
- cdfName, |
|
1019 |
- verbose=FALSE, |
|
1020 |
- batch, #fns, |
|
1021 |
- saveDate=TRUE) { #, outdir="."){ |
|
1012 |
+ arrayNames=NULL, |
|
1013 |
+ path=".", |
|
1014 |
+ arrayInfoColNames=list(barcode="SentrixBarcode_A", position="SentrixPosition_A"), |
|
1015 |
+ highDensity=FALSE, |
|
1016 |
+ sep="_", |
|
1017 |
+ fileExt=list(green="Grn.idat", red="Red.idat"), |
|
1018 |
+ cdfName, |
|
1019 |
+ verbose=FALSE, |
|
1020 |
+ batch, #fns, |
|
1021 |
+ saveDate=TRUE) { #, outdir="."){ |
|
1022 | 1022 |
verbose <- FALSE |
1023 | 1023 |
if(!is.null(arrayNames)) { |
1024 | 1024 |
pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames)) |
... | ... |
@@ -127,20 +127,8 @@ crlmmCopynumber(object, MIN.SAMPLES=10, SNRMin = 5, MIN.OBS = 1, |
127 | 127 |
\code{crlmmCopynumber}. 50 or more samples per batch is preferred |
128 | 128 |
and will improve the estimates. |
129 | 129 |
|
130 |
- The function crlmmCopynumber uses matrices instead of ff objects |
|
131 |
- if the ff library is not loaded. When the ff package is loaded, |
|
132 |
- large data support is enabled. Normalized intensities |
|
133 |
- (\code{alleleA} and \code{alleleB}), genotype calls and |
|
134 |
- confidence scores (\code{snpCall} and \code{snpCallProbability}) |
|
135 |
- are stored in \code{assayData} slot. Summary statistics for |
|
136 |
- each batch, including the linear model paramters for copy |
|
137 |
- number, are stored in the \code{batchStatistics} slot. Both the |
|
138 |
- \code{assayData} and \code{batchStatistics} slot are of class |
|
139 |
- \code{AssayData} with elements that are ff objects (if ff |
|
140 |
- package is loaded) or matrices. |
|
141 |
- |
|
142 |
- The functions \code{crlmmCopynumberLD} and |
|
143 |
- \code{crlmmCopynumber2} have been deprecated. |
|
130 |
+ The functions \code{crlmmCopynumberLD} and |
|
131 |
+ \code{crlmmCopynumber2} have been deprecated. |
|
144 | 132 |
|
145 | 133 |
The argument \code{type} can be used to specify a subset of |
146 | 134 |
markers for which the copy number estimation algorithm is run. |
... | ... |
@@ -155,6 +143,9 @@ crlmmCopynumber(object, MIN.SAMPLES=10, SNRMin = 5, MIN.OBS = 1, |
155 | 143 |
|
156 | 144 |
'X.NP' refers to autosomes on chromosome X. |
157 | 145 |
|
146 |
+ However, users must run 'SNP' prior to running 'NP' and 'X.NP', |
|
147 |
+ or specify \code{type = c('SNP', 'X.NP')}. |
|
148 |
+ |
|
158 | 149 |
} |
159 | 150 |
|
160 | 151 |
\value{ |
... | ... |
@@ -162,7 +153,10 @@ crlmmCopynumber(object, MIN.SAMPLES=10, SNRMin = 5, MIN.OBS = 1, |
162 | 153 |
The value returned by the \code{crlmmCopynumber} function |
163 | 154 |
depends on whether the data is stored in RAM or whether the data |
164 | 155 |
is stored on disk using the R package \code{ff} for reading / |
165 |
- writing. Specifically, |
|
156 |
+ writing. If uncertain, the first line of the \code{show} method |
|
157 |
+ defined for \code{CNSet} objects prints whether the |
|
158 |
+ \code{assayData} elements are derived from the \code{ff} package |
|
159 |
+ in the first line. Specifically, |
|
166 | 160 |
|
167 | 161 |
- if the elements of the \code{batchStaticts} slot in the |
168 | 162 |
\code{CNSet} object have the class "ff_matrix" or "ffdf", then |
... | ... |
@@ -177,6 +171,5 @@ crlmmCopynumber(object, MIN.SAMPLES=10, SNRMin = 5, MIN.OBS = 1, |
177 | 171 |
|
178 | 172 |
} |
179 | 173 |
|
180 |
- |
|
181 | 174 |
\author{R. Scharpf} |
182 | 175 |
\keyword{manip} |