git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@37951 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -23,3 +23,8 @@ BioC data packages |
23 | 23 |
* Added biocViews |
24 | 24 |
|
25 | 25 |
* Removed empty \details{} in cnrma.Rd |
26 |
+ |
|
27 |
+2009-03-14 Benilton Carvalho <bcarvalh@jhsph.edu> - committed version 1.0.56 |
|
28 |
+ |
|
29 |
+* Loaded data in cnrma-functions.R to an environment and extracted from there |
|
30 |
+ so we can get rid of the NOTES complaining about 'no visible bindings'. |
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for SNP 5.0 and 6.0 arrays. |
4 |
-Version: 1.0.55 |
|
4 |
+Version: 1.0.56 |
|
5 | 5 |
Date: 2008-12-28 |
6 | 6 |
Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu> |
7 | 7 |
Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu> |
... | ... |
@@ -91,10 +91,16 @@ celDatesFrom <- function(celfiles, path=""){ |
91 | 91 |
} |
92 | 92 |
|
93 | 93 |
cnrma <- function(filenames, sns, cdfName, seed=1, verbose=FALSE){ |
94 |
- require(genomewidesnp6Crlmm) || stop("Package genomewidesnp6Crlmm not available") |
|
94 |
+ ## BC: 03/14/09 |
|
95 |
+ ## getting pkgname from cdfName, in the future this might be useful |
|
96 |
+ ## as the method might be implemented for other platforms |
|
97 |
+ pkgname <- getCrlmmAnnotationName(cdfName) |
|
98 |
+ |
|
99 |
+ require(pkgname, character.only=TRUE) || stop("Package ", pkgname, " not available") |
|
95 | 100 |
if (missing(sns)) sns <- basename(filenames) |
96 |
- data("npProbesFid", package="genomewidesnp6Crlmm") |
|
97 |
- fid <- npProbesFid |
|
101 |
+ ## Loading data in .crlmmPkgEnv and extracting from there |
|
102 |
+ data("npProbesFid", package=pkgname, envir=.crlmmPkgEnv) |
|
103 |
+ fid <- getVarInEnv("npProbesFid") |
|
98 | 104 |
gc() |
99 | 105 |
set.seed(seed) |
100 | 106 |
idx2 <- sample(length(fid), 10^5) ##for skewness. no need to do everything |
... | ... |
@@ -106,7 +112,8 @@ cnrma <- function(filenames, sns, cdfName, seed=1, verbose=FALSE){ |
106 | 112 |
if (getRversion() > '2.7.0') pb <- txtProgressBar(min=0, max=length(filenames), style=3) |
107 | 113 |
} |
108 | 114 |
##load reference distribution obtained from hapmap |
109 |
- data(list="1m_reference_cn", package="genomewidesnp6Crlmm") |
|
115 |
+ data(list="1m_reference_cn", package="genomewidesnp6Crlmm", envir=.crlmmPkgEnv) |
|
116 |
+ reference <- getVarInEnv("reference") |
|
110 | 117 |
for(i in seq(along=filenames)){ |
111 | 118 |
y <- as.matrix(read.celfile(filenames[i], intensity.means.only=TRUE)[["INTENSITY"]][["MEAN"]][fid]) |
112 | 119 |
x <- log2(y[idx2]) |
... | ... |
@@ -893,10 +900,14 @@ coefs <- function(plateIndex, conf, MIN.OBS=3, envir, CONF.THR=0.99){ |
893 | 900 |
is.complete <- rowSums(is.na(W)) == 0 |
894 | 901 |
##is.complete <- is.complete & correct.orderA & correct.orderB & confInd & notmissing |
895 | 902 |
nuphiAllele(allele="A", Ystar=Ystar[is.complete, ], W=W[is.complete, ], envir=envir, p=p) |
896 |
- nuA[is.complete, p] <- nu |
|
897 |
- phiA[is.complete, p] <- phi |
|
898 |
- nuA.se[is.complete, p] <- nu.se |
|
899 |
- phiA.se[is.complete, p] <- phi.se |
|
903 |
+ ## ROB: can you please double check that my fix is okay? |
|
904 |
+ ## ROB: the parameters nu/phi/nu.se/phi.se aren't defined |
|
905 |
+ ## ROB: in this particular function. So I assume they come |
|
906 |
+ ## ROB: from the nuphiAllele function above. |
|
907 |
+ nuA[is.complete, p] <- get("nu", envir=envir) |
|
908 |
+ phiA[is.complete, p] <- get("phi", envir=envir) |
|
909 |
+ nuA.se[is.complete, p] <- get("nu.se", envir=envir) |
|
910 |
+ phiA.se[is.complete, p] <- get("phi.se", envir=envir) |
|
900 | 911 |
|
901 | 912 |
if(NOHET){ |
902 | 913 |
IB <- IB[, c(1, 3)] |
... | ... |
@@ -912,10 +923,14 @@ coefs <- function(plateIndex, conf, MIN.OBS=3, envir, CONF.THR=0.99){ |
912 | 923 |
Ystar <- IB*W |
913 | 924 |
is.complete <- rowSums(is.na(W)) == 0 |
914 | 925 |
nuphiAllele(allele="B", Ystar=Ystar[is.complete, ], W=W[is.complete, ], envir=envir, p=p) |
915 |
- nuB[is.complete, p] <- nu |
|
916 |
- phiB[is.complete, p] <- phi |
|
917 |
- nuB.se[is.complete, p] <- nu.se |
|
918 |
- phiB.se[is.complete, p] <- phi.se |
|
926 |
+ ## ROB: can you please double check that my fix is okay? |
|
927 |
+ ## ROB: the parameters nu/phi/nu.se/phi.se aren't defined |
|
928 |
+ ## ROB: in this particular function. So I assume they come |
|
929 |
+ ## ROB: from the nuphiAllele function above. |
|
930 |
+ nuB[is.complete, p] <- get("nu", envir=envir) |
|
931 |
+ phiB[is.complete, p] <- get("phi", envir=envir) |
|
932 |
+ nuB.se[is.complete, p] <- get("nu.se", envir=envir) |
|
933 |
+ phiB.se[is.complete, p] <- get("phi.se", envir=envir) |
|
919 | 934 |
phiA <- matrix(as.integer(phiA), nrow(phiA), ncol(phiA)) |
920 | 935 |
phiB <- matrix(as.integer(phiB), nrow(phiA), ncol(phiA)) |
921 | 936 |
|
... | ... |
@@ -2,7 +2,6 @@ |
2 | 2 |
### FOR CRLMM |
3 | 3 |
##################################### |
4 | 4 |
- Decide on output format (BC vote: eSet-like) |
5 |
-- Helper to convert to snpMatrix |
|
6 | 5 |
- Add RS ids to annotation packages |
7 | 6 |
- Allele plots |
8 | 7 |
- M v S plots |
... | ... |
@@ -11,19 +10,6 @@ |
11 | 10 |
##################################### |
12 | 11 |
### FOR CNRMA |
13 | 12 |
##################################### |
14 |
-- fix the following 2 items |
|
15 |
-* checking R code for possible problems ... NOTE |
|
16 |
-cnrma: no visible global function definition for ‘getCnvFid’ |
|
17 |
-cnrma: no visible binding for global variable ‘reference’ |
|
18 |
-coefs: no visible binding for global variable ‘nu’ |
|
19 |
-coefs: no visible binding for global variable ‘phi’ |
|
20 |
-coefs: no visible binding for global variable ‘nu.se’ |
|
21 |
-coefs: no visible binding for global variable ‘phi.se’ |
|
22 |
- |
|
23 |
-* checking for unstated dependencies in R code ... WARNING |
|
24 |
-'library' or 'require' calls not declared from: |
|
25 |
- affyio splines Biobase genefilter |
|
26 |
- |
|
27 |
-* checking for missing documentation entries ... WARNING |
|
28 |
-Undocumented code objects: |
|
29 |
- computeCnBatch |
|
13 |
+- Rob, can you run a: 'grep ROB *' under R/? There are |
|
14 |
+ some notes for you there. Basically because I changed |
|
15 |
+ a few things that I'm not so sure of. |