Browse code

updated description, added AllClasses.R

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

Rob Scharp authored on 10/03/2010 14:53:53
Showing 5 changed files

... ...
@@ -441,3 +441,9 @@ then readIDAT() should work. Thanks to Pierre Cherel who reported this error.
441 441
 2010-03-08 R.Scharpf committed version 1.5.33
442 442
 
443 443
 **	  Added annotatedDataFrameFrom methods for ff_matrix and ffdf (in utils)
444
+
445
+2010-03-10 R.Scharpf committed version 1.5.34
446
+
447
+**	  updated DESCRIPTION to import ff
448
+**        added AllClasses.R with defitions for ff-derived classes
449
+**        temporarily exporting everything in the NAMESPACE
... ...
@@ -7,10 +7,27 @@ Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scha
7 7
 Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
8 8
 Description: Faster implementation of CRLMM specific to SNP 5.0 and 6.0 arrays, as well as a copy number tool specific to 5.0, 6.0, and Illumina platforms
9 9
 License: Artistic-2.0
10
-Depends: methods, Biobase (>= 2.7.2), R (>= 2.11.0), oligoClasses (>= 1.9.21)
11
-Imports: affyio (>= 1.15.2), preprocessCore, utils, stats, genefilter, splines, mvtnorm, ellipse, SNPchip
12
-Suggests: hapmapsnp5, hapmapsnp6, genomewidesnp5Crlmm (>= 1.0.2),genomewidesnp6Crlmm (>= 1.0.2), snpMatrix
10
+Depends: R (>= 2.11.0),
11
+         methods,
12
+         Biobase (>= 2.7.2),
13
+         oligoClasses (>= 1.9.28)
14
+Imports: affyio (>= 1.15.2),
15
+         preprocessCore,
16
+         utils,
17
+         stats,
18
+         genefilter,
19
+         splines,
20
+         mvtnorm,
21
+         ellipse,
22
+         SNPchip,ff
23
+Suggests: hapmapsnp5,
24
+          hapmapsnp6,
25
+          genomewidesnp5Crlmm (>= 1.0.2),
26
+          genomewidesnp6Crlmm (>= 1.0.2),
27
+          snpMatrix,
28
+          metaArray
13 29
 Collate: AllGenerics.R
30
+	 AllClasses.R
14 31
 	 methods-CNSet.R
15 32
 	 methods-eSet.R
16 33
          methods-SnpSuperSet.R
... ...
@@ -1,5 +1,8 @@
1 1
 useDynLib("crlmm", .registration=TRUE)
2 2
 
3
+## this is temporary
4
+exportPattern("^[^\\.]")
5
+
3 6
 ## Biobase
4 7
 importClassesFrom(Biobase, AnnotatedDataFrame, AssayData, eSet, SnpSet,
5 8
 		  NChannelSet, MIAME, Versioned, VersionedBiobase,
... ...
@@ -23,7 +26,7 @@ importClassesFrom(oligoClasses, SnpSuperSet, AlleleSet)
23 26
 
24 27
 importMethodsFrom(oligoClasses, allele, calls, "calls<-", confs,
25 28
 		  "confs<-", cnConfidence, "cnConfidence<-", 
26
-		  isSnp, chromosome, position, CA, "CA<-", CB, "CB<-")
29
+		  isSnp, chromosome, position, CA, "CA<-", CB, "CB<-", A, B)
27 30
 
28 31
 
29 32
 importFrom(oligoClasses, chromosome2integer, celfileDate, list.celfiles)
... ...
@@ -1,5 +1,3 @@
1
-setGeneric("A", function(object) standardGeneric("A"))
2
-setGeneric("B", function(object) standardGeneric("B"))
3 1
 ##setGeneric("A<-", function(object, value) standardGeneric("A<-"))
4 2
 ##setGeneric("B<-", function(object, value) standardGeneric("B<-"))
5 3
 
... ...
@@ -1,3 +1,80 @@
1
+##---------------------------------------------------------------------------
2
+##---------------------------------------------------------------------------
3
+getProtocolData.Affy <- function(filenames){
4
+	scanDates <- data.frame(ScanDate=sapply(filenames, celfileDate))
5
+	rownames(scanDates) <- basename(rownames(scanDates))
6
+	protocoldata <- new("AnnotatedDataFrame",
7
+			    data=scanDates,
8
+			    varMetadata=data.frame(labelDescription=colnames(scanDates),
9
+			                           row.names=colnames(scanDates)))
10
+	return(protocoldata)
11
+}
12
+getFeatureData.Affy <- function(cdfName, copynumber=FALSE){
13
+	pkgname <- getCrlmmAnnotationName(cdfName)
14
+	if(!require(pkgname, character.only=TRUE)){
15
+		suggCall <- paste("library(", pkgname, ", lib.loc='/Altern/Lib/Loc')", sep="")
16
+		msg <- paste("If", pkgname, "is installed on an alternative location, please load it manually by using", suggCall)
17
+		message(strwrap(msg))
18
+		stop("Package ", pkgname, " could not be found.")
19
+		rm(suggCall, msg)
20
+	}
21
+	loader("preprocStuff.rda", .crlmmPkgEnv, pkgname)
22
+	loader("genotypeStuff.rda", .crlmmPkgEnv, pkgname)
23
+	loader("mixtureStuff.rda", .crlmmPkgEnv, pkgname)
24
+	gns <- getVarInEnv("gns")
25
+	path <- system.file("extdata", package=paste(cdfName, "Crlmm", sep=""))
26
+	load(file.path(path, "snpProbes.rda"))
27
+
28
+	if(copynumber){
29
+		load(file.path(path, "cnProbes.rda"))
30
+		cnProbes <- get("cnProbes")
31
+		snpIndex <- seq(along=gns)
32
+		npIndex <- seq(along=rownames(cnProbes)) + max(snpIndex) 
33
+		featurenames <- c(gns, rownames(cnProbes))
34
+	} else featurenames <- gns
35
+	fvarlabels=c("chromosome", "position", "isSnp")
36
+	M <- matrix(NA, length(featurenames), 3, dimnames=list(featurenames, fvarlabels))
37
+	index <- match(rownames(snpProbes), rownames(M)) #only snp probes in M get assigned position
38
+	M[index, "position"] <- snpProbes[, grep("pos", colnames(snpProbes))]
39
+	M[index, "chromosome"] <- snpProbes[, grep("chr", colnames(snpProbes))]
40
+	M[index, "isSnp"] <- 1L
41
+	index <- which(is.na(M[, "isSnp"]))
42
+	M[index, "isSnp"] <- 1L
43
+
44
+	if(copynumber){
45
+		index <- match(rownames(cnProbes), rownames(M)) #only snp probes in M get assigned position
46
+		M[index, "position"] <- cnProbes[, grep("pos", colnames(cnProbes))]
47
+		M[index, "chromosome"] <- cnProbes[, grep("chr", colnames(cnProbes))]
48
+		M[index, "isSnp"] <- 0L
49
+	}
50
+	return(new("AnnotatedDataFrame", data=data.frame(M)))
51
+	##list(snpIndex, npIndex, fns)
52
+	##crlmmOpts$snpRange <- range(snpIndex)
53
+	##crlmmOpts$npRange <- range(npIndex)
54
+}
55
+construct <- function(filenames, cdfName){
56
+	protocolData <- getProtocolData.Affy(filenames)
57
+	M <- getFeatureData.Affy(cdfName)
58
+	dns <- list(rownames(M), basename(filenames))
59
+	nr <- nrow(M)
60
+	alleleSet <- new("AffymetrixAlleleSet", 
61
+			 alleleA=initializeBigMatrix(dns),
62
+			 alleleB=initializeBigMatrix(dns),
63
+			 genomeAnnotation=M,
64
+			 options=crlmmOptions(object),
65
+			 annotation=annotation(object))
66
+	protocolData(alleleSet) <- protocolData
67
+	sampleNames(alleleSet) <- basename(filenames)
68
+	featureNames(alleleSet) <- dns[[1]]
69
+	return(alleleSet)
70
+}
71
+
72
+
73
+
74
+
75
+
76
+##---------------------------------------------------------------------------
77
+##---------------------------------------------------------------------------
1 78
 rowCovs <- function(x, y, ...){
2 79
 	notna <- !is.na(x)
3 80
 	N <- rowSums(notna)