Browse code

Intermediate files are loaded within the constructIlluminaCNSet function.

- Removed the loading of intermediate files from the vignette.
- Modified function constructIlluminaCNSet accordingly.

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48625 bc3139a8-67e5-0310-9ffc-ced21a209358

Rob Scharp authored on 02/08/2010 08:52:18
Showing 2 changed files

... ...
@@ -3159,9 +3159,13 @@ constructIlluminaAssayData <- function(np, snp, object, storage.mode="environmen
3159 3159
 			   CA=emptyMatrix,
3160 3160
 			   CB=emptyMatrix)
3161 3161
 }
3162
-constructIlluminaCNSet <- function(res,
3163
-				   cnAB,
3164
-				   crlmmResult){
3162
+constructIlluminaCNSet <- function(crlmmResult,
3163
+				   snpFile,
3164
+				   cnFile){
3165
+	load(file.path(outdir, "snpFile.rda"))
3166
+	res <- get("res")
3167
+	load(file.path(outdir, "cnFile.rda"))
3168
+	cnAB <- get("cnAB")	
3165 3169
 	fD <- constructIlluminaFeatureData(c(res$gns, cnAB$gns), cdfName="human370v1c")
3166 3170
 	new.order <- order(fD$chromosome, fD$position)
3167 3171
 	fD <- fD[new.order, ]
... ...
@@ -117,7 +117,7 @@ RG <- readIdatFiles2(samplesheet[1:10, ],
117 117
 		    arrayInfoColNames=list(barcode=NULL, position="SentrixPosition"), 
118 118
 		    saveDate=TRUE)
119 119
 annotation(RG) <- "human370v1c"
120
-crlmmResult <- crlmmIllumina(RG=RG, 
120
+crlmmResult <- crlmmIllumina2(RG=RG, 
121 121
 			     cdfName="human370v1c", 
122 122
 			     sns=pData(RG)$ID, 
123 123
 			     returnParams=TRUE,
... ...
@@ -127,20 +127,20 @@ crlmmResult <- crlmmIllumina(RG=RG,
127 127
 protocolData(crlmmResult)$ScanDate <- protocolData(RG)$ScanDate
128 128
 @ 
129 129
 
130
-\noindent Finally, we load a few of the intermediate files that were
131
-created during the preprocessing and genotyping.
132
-<<loadIntermediate, eval=FALSE>>=
133
-load(file.path(outdir, "snpFile.rda"))
134
-res <- get("res")
135
-load(file.path(outdir, "cnFile.rda"))
136
-cnAB <- get("cnAB")
137
-@ 
138
-
139
-<<loadIntermediate, echo=FALSE>>=
140
-trace(checkExists, browser)
141
-res <- checkExists("snpFile", .path=outdir, .FUN=load, file=file.path(outdir, "snpFile.rda"))
142
-cnAB <- checkExists("cnFile", .path=outdir, .FUN=load, file=file.path(outdir, "cnFile.rda"))
143
-@ 
130
+%\noindent Finally, we load a few of the intermediate files that were
131
+%created during the preprocessing and genotyping.
132
+%<<loadIntermediate, eval=FALSE>>=
133
+%load(file.path(outdir, "snpFile.rda"))
134
+%res <- get("res")
135
+%load(file.path(outdir, "cnFile.rda"))
136
+%cnAB <- get("cnAB")
137
+%@ 
138
+%
139
+%<<loadIntermediate, echo=FALSE>>=
140
+%trace(checkExists, browser)
141
+%res <- checkExists("snpFile", .path=outdir, .FUN=load, file=file.path(outdir, "snpFile.rda"))
142
+%cnAB <- checkExists("cnFile", .path=outdir, .FUN=load, file=file.path(outdir, "cnFile.rda"))
143
+%@ 
144 144
 
145 145
 After running the crlmm algorithm, we construct a container for
146 146
 storing the quantile normalized intensities, genotype calls, and
... ...
@@ -154,9 +154,9 @@ devel version of this package.
154 154
 container <- checkExists("container",
155 155
 			 .path=outdir,
156 156
 			 .FUN=constructIlluminaCNSet,
157
-			 res=res,
158
-			 cnAB=cnAB,
159
-			 crlmmResult=crlmmResult)
157
+			 crlmmResult=crlmmResult,
158
+			 snpFile=snpFile,
159
+			 cnFile=cnFile)
160 160
 @ 
161 161
 
162 162
 <<constructContainer2, eval=FALSE>>=