Browse code

Fixing several warnings and notes

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

Benilton Carvalho authored on 31/07/2009 04:51:13
Showing 11 changed files

... ...
@@ -241,4 +241,14 @@ is decoded and scanned
241 241
 
242 242
 * fixed malformed DESCRIPTION file
243 243
 
244
+2009-07-31 B Carvalho - committed version 1.3.16
244 245
 
246
+* Removed several warnings at the C-level
247
+
248
+* Fixed several incorrect links in the documentation
249
+
250
+* Removed multiple notes "no visible binding for global variable"
251
+  by replacing, in crlmmIlluminaWrapper and crlmmWrapper,
252
+  a) samplesheet5 by get("samplesheet5")
253
+  b) path by get("path")
254
+  c) res by get("res")
... ...
@@ -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.3.15
4
+Version: 1.3.16
5 5
 Date: 2009-07-22
6 6
 Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
7 7
 Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
... ...
@@ -220,21 +220,26 @@ crlmmIlluminaWrapper <- function(sampleSheet, outdir="./", cdfName,
220 220
 				 splitByChr=TRUE,...){
221 221
 	if(file.exists(file.path(outdir, "RG.rda"))) load(file.path(outdir, "RG.rda"))
222 222
 	else {
223
-		RG <- readIdatFiles(sampleSheet=samplesheet5, arrayInfoColNames=list(barcode=NULL, position="SentrixPosition"), saveDate=TRUE,
224
-				    path=path)
223
+		RG <- readIdatFiles(sampleSheet=get("samplesheet5"),
224
+                                    arrayInfoColNames=list(barcode=NULL, position="SentrixPosition"),
225
+                                    saveDate=TRUE, path=get("path"))
225 226
 		J <- match(c("1_A", "3_A", "5_A", "7_A"), sampleNames(RG))
226 227
 		RG <- RG[, -J]
227 228
 		if(save.intermediate) save(RG, file=file.path(outdir, "RG.rda"))  ##935M for 91 samples...better not to save this
228 229
 	}	
229 230
 	if(!file.exists(file.path(outdir, "res.rda"))){
230
-		crlmmOut <- crlmmIllumina(RG=RG, cdfName=cdfName, sns=pData(RG)$ID, returnParams=TRUE, save.it=TRUE, intensityFile=file.path(outdir, "res.rda"))
231
+		crlmmOut <- crlmmIllumina(RG=RG, cdfName=cdfName,
232
+                                          sns=pData(RG)$ID,
233
+                                          returnParams=TRUE,
234
+                                          save.it=TRUE,
235
+                                          intensityFile=file.path(outdir, "res.rda"))
231 236
 		if(save.intermediate) save(crlmmOut, file=file.path(outdir, "crlmmOut.rda"))				
232 237
 	} else{
233 238
 		message("Loading...")		
234 239
 		load(file.path(outdir, "res.rda"))
235 240
 		load(file.path(outdir, "crlmmOut.rda"))		
236 241
 	}
237
-	ABset <- combineIntensities(res, NULL, cdfName=cdfName)
242
+	ABset <- combineIntensities(get("res"), NULL, cdfName=cdfName)
238 243
 	protocolData(ABset)[["ScanDate"]] <- as.character(pData(RG)$ScanDate)
239 244
 	crlmmResult <- harmonizeSnpSet(crlmmOut, ABset)
240 245
 	stopifnot(all.equal(dimnames(crlmmOut), dimnames(ABset)))
... ...
@@ -273,7 +278,7 @@ crlmmWrapper <- function(filenames, outdir="./", cdfName="genomewidesnp6",
273 278
 		load(file.path(outdir, "cnrmaResult.rda"))
274 279
 	}
275 280
 	load(file.path(outdir, "intensities.rda"))
276
-	ABset <- combineIntensities(res, cnrmaResult, cdfName)
281
+	ABset <- combineIntensities(get("res"), cnrmaResult, cdfName)
277 282
 	protocolData(ABset)[["ScanDate"]] <- as.character(celDates(filenames))	
278 283
 	crlmmResult <- harmonizeSnpSet(crlmmResult, ABset)
279 284
 	stopifnot(all.equal(dimnames(crlmmResult), dimnames(ABset)))
... ...
@@ -23,9 +23,9 @@ Objects can be created by calls of the form \code{new("ABset", assayData, phenoD
23 23
   }
24 24
 }
25 25
 \section{Extends}{
26
-Class \code{"\linkS4class{eSet}"}, directly.
27
-Class \code{"\linkS4class{VersionedBiobase}"}, by class "eSet", distance 2.
28
-Class \code{"\linkS4class{Versioned}"}, by class "eSet", distance 3.
26
+Class \code{\link[Biobase:class.eSet]{eSet}}, directly.
27
+Class \code{\link[Biobase:class.VersionedBiobase]{VersionedBiobase}}, by class "eSet", distance 2.
28
+Class \code{\link[Biobase:class.Versioned]{Versioned}}, by class "eSet", distance 3.
29 29
 }
30 30
 \section{Methods}{
31 31
   \describe{
... ...
@@ -34,9 +34,9 @@ Objects can be created by calls of the form \code{new("CopyNumberSet", assayData
34 34
   }
35 35
 }
36 36
 \section{Extends}{
37
-Class \code{"\linkS4class{eSet}"}, directly.
38
-Class \code{"\linkS4class{VersionedBiobase}"}, by class "eSet", distance 2.
39
-Class \code{"\linkS4class{Versioned}"}, by class "eSet", distance 3.
37
+Class \code{\link[Biobase:class.eSet]{eSet}}, directly.
38
+Class \code{\link[Biobase:class.VersionedBiobase]{VersionedBiobase}}, by class "eSet", distance 2.
39
+Class \code{\link[Biobase:class.Versioned]{Versioned}}, by class "eSet", distance 3.
40 40
 }
41 41
 \section{Methods}{
42 42
   \describe{
... ...
@@ -63,7 +63,7 @@
63 63
 \section{Extends}{
64 64
   Class \code{"\linkS4class{list}"}, from data part.
65 65
   Class \code{"\linkS4class{vector}"}, by class "list", distance 2.
66
-  Class \code{"\linkS4class{AssayData}"}, by class "list", distance 2.
66
+  Class \code{\link[Biobase:class.assayData]{assayData}}, by class "list", distance 2.
67 67
 }
68 68
 \section{Methods}{
69 69
   \describe{
... ...
@@ -47,7 +47,7 @@ computeCopynumber(object, CHR, bias.adj=FALSE, batch, SNRmin=5, cdfName="genomew
47 47
 }
48 48
 
49 49
 \seealso{
50
-  \code{\linkS4class{CopyNumberSet}},   \code{\link{".computeCopynumber"}}
50
+  \code{\linkS4class{CopyNumberSet}},   \code{.computeCopynumber}
51 51
 }
52 52
 \author{Rob Scharpf}
53 53
 \keyword{manip}
... ...
@@ -84,7 +84,7 @@ SEXP gtypeCallerPart1(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
84 84
   //const int lenLists=3;
85 85
 
86 86
   // Buffers
87
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2;
87
+  int intbuffer, ibv1[colsAB], ib2;
88 88
   double buffer;
89 89
 
90 90
   // All pointers appear here
... ...
@@ -303,11 +303,8 @@ SEXP gtypeCallerPart2(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
303 303
   colsAB = INTEGER(getAttrib(A, R_DimSymbol))[1];
304 304
   double likelihood[colsAB*3], M[colsAB], S[colsAB], f[colsAB];
305 305
 
306
-  // Constants
307
-  const int lenLists=3;
308
-
309 306
   // Buffers
310
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
307
+  int intbuffer, ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
311 308
   double buffer;
312 309
 
313 310
   ib2 = GET_LENGTH(noTraining);
... ...
@@ -84,7 +84,7 @@ SEXP gtypeCallerPart1nm(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
84 84
   //const int lenLists=3;
85 85
 
86 86
   // Buffers
87
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2;
87
+  int intbuffer, ibv1[colsAB], ib2;
88 88
   double buffer;
89 89
 
90 90
   // All pointers appear here
... ...
@@ -304,10 +304,10 @@ SEXP gtypeCallerPart2nm(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
304 304
   double likelihood[colsAB*3], M[colsAB], S[colsAB], f[colsAB];
305 305
 
306 306
   // Constants
307
-  const int lenLists=3;
307
+  // const int lenLists=3;
308 308
 
309 309
   // Buffers
310
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
310
+  int intbuffer, ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
311 311
   double buffer;
312 312
 
313 313
   ib2 = GET_LENGTH(noTraining);
... ...
@@ -84,7 +84,7 @@ SEXP gtypeCallerPart1NormalNoN(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
84 84
   //const int lenLists=3;
85 85
 
86 86
   // Buffers
87
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2;
87
+  int intbuffer, ibv1[colsAB], ib2;
88 88
   double buffer;
89 89
 
90 90
   // All pointers appear here
... ...
@@ -286,10 +286,10 @@ SEXP gtypeCallerPart2NormalNoN(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
286 286
   double likelihood[colsAB*3], M[colsAB], S[colsAB], f[colsAB];
287 287
 
288 288
   // Constants
289
-  const int lenLists=3;
289
+  // const int lenLists=3;
290 290
 
291 291
   // Buffers
292
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
292
+  int intbuffer, ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
293 293
   double buffer;
294 294
 
295 295
   ib2 = GET_LENGTH(noTraining);
... ...
@@ -84,7 +84,7 @@ SEXP gtypeCallerPart1TNoN(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
84 84
   //const int lenLists=3;
85 85
 
86 86
   // Buffers
87
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2;
87
+  int intbuffer, ibv1[colsAB], ib2;
88 88
   double buffer;
89 89
 
90 90
   // All pointers appear here
... ...
@@ -286,10 +286,10 @@ SEXP gtypeCallerPart2TNoN(SEXP A, SEXP B, SEXP fIndex, SEXP mIndex,
286 286
   double likelihood[colsAB*3], M[colsAB], S[colsAB], f[colsAB];
287 287
 
288 288
   // Constants
289
-  const int lenLists=3;
289
+  // const int lenLists=3;
290 290
 
291 291
   // Buffers
292
-  int intbuffer, ibv1[colsAB], ibv2[colsAB], ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
292
+  int intbuffer, ib2, ib3, ibSnpLevel1=0, ibSnpLevel2=0;
293 293
   double buffer;
294 294
 
295 295
   ib2 = GET_LENGTH(noTraining);