* collab:
bump version
made cnSetExample smaller. Fix notes
Trying to revert bad commit
remove cn-functions. update description
comment most of cn-functions.r
Resaved rdas
update data/cnSetExample.rda and data/cnSetExample2.rda
bump version
coercion method from CNSet to oligoSnpSet makes integer matrices of BAFs and lrr's
import ff_or_matrix from oligoClasses. bump dependency on oligoClasses version. Use library(oligoClasses) in some of the crlmm examples.
Cleaning pkg loading process: work still required
move Biobase and methods to imports
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@64324 bc3139a8-67e5-0310-9ffc-ced21a209358
* mymac:
add AffyGW.pdf
update vignettes in inst/scripts
Change argument of validCEL to celfiles
Update constructInf to accommodate GenomeDataFrame class for featureData
bump version to 1.13.7
Add doRUnit.R
Add celfile-utils.Rd
Streamlne some of the Rd files
add validCEL function that checks whether all celfiles can be read
getFeatureData returns GenomeAnnotatedDataFrame
Remove imports from methods. Remove pdf of illumina_copynumber.pdf (large file) and copynumber.pdf
getFeatureDAta returns GenomeAnnotatedDataFrame
Remove separate vignette for copy number in inst/scripts. Include copynumber section in both affy and illumina pipelines.
update documentation files for genotype.Illumina, preprocessInf, and genotypeInf (cdfName added as argument. Indicate that 'batch' should be a character string)
pass cdfName to genotypeInf and preprocessInf
add unitTests and cn-functions for 'simple usage'
Combine AffyPreprocess and copynumber. Combine IlluminaPreprocess and copynumber
remove depency on ff to allow installation on my mac
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@62108 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@58653 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@50352 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@49144 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@49139 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -3,20 +3,3 @@ setOldClass("ff_matrix") |
3 | 3 |
setOldClass("ffdf") |
4 | 4 |
##setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
5 | 5 |
setClassUnion("ff_or_matrix", c("ff_matrix", "matrix")) |
6 |
-setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
7 |
-setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
|
8 |
- .Object@lM <- lM |
|
9 |
- .Object <- callNextMethod(.Object, ...) |
|
10 |
-}) |
|
11 |
-setValidity("CNSetLM", |
|
12 |
- function(object){ |
|
13 |
- if(!"batch" %in% varLabels(protocolData(object))) |
|
14 |
- return("'batch' not defined in protocolData") |
|
15 |
- if(!"chromosome" %in% fvarLabels(object)) |
|
16 |
- return("'chromosome' not defined in featureData") |
|
17 |
- if(!"position" %in% fvarLabels(object)) |
|
18 |
- return("'position' not defined in featureData") |
|
19 |
- if(!"isSnp" %in% fvarLabels(object)) |
|
20 |
- return("'isSnp' not defined in featureData") |
|
21 |
- return(TRUE) |
|
22 |
- }) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@49132 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,10 +1,8 @@ |
1 | 1 |
setOldClass("ellipse") |
2 | 2 |
setOldClass("ff_matrix") |
3 | 3 |
setOldClass("ffdf") |
4 |
-setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
|
5 |
-<<<<<<< HEAD |
|
6 |
- |
|
7 |
-======= |
|
4 |
+##setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
|
5 |
+setClassUnion("ff_or_matrix", c("ff_matrix", "matrix")) |
|
8 | 6 |
setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
9 | 7 |
setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
10 | 8 |
.Object@lM <- lM |
... | ... |
@@ -22,4 +20,3 @@ setValidity("CNSetLM", |
22 | 20 |
return("'isSnp' not defined in featureData") |
23 | 21 |
return(TRUE) |
24 | 22 |
}) |
25 |
->>>>>>> Removed tryCatch() statements in readIdatFiles. Restored previous implementation. |
Added statements to illumina_copynumber.Rnw that make use of checkExists function.
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@49126 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -2,4 +2,24 @@ setOldClass("ellipse") |
2 | 2 |
setOldClass("ff_matrix") |
3 | 3 |
setOldClass("ffdf") |
4 | 4 |
setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
5 |
+<<<<<<< HEAD |
|
5 | 6 |
|
7 |
+======= |
|
8 |
+setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
9 |
+setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
|
10 |
+ .Object@lM <- lM |
|
11 |
+ .Object <- callNextMethod(.Object, ...) |
|
12 |
+}) |
|
13 |
+setValidity("CNSetLM", |
|
14 |
+ function(object){ |
|
15 |
+ if(!"batch" %in% varLabels(protocolData(object))) |
|
16 |
+ return("'batch' not defined in protocolData") |
|
17 |
+ if(!"chromosome" %in% fvarLabels(object)) |
|
18 |
+ return("'chromosome' not defined in featureData") |
|
19 |
+ if(!"position" %in% fvarLabels(object)) |
|
20 |
+ return("'position' not defined in featureData") |
|
21 |
+ if(!"isSnp" %in% fvarLabels(object)) |
|
22 |
+ return("'isSnp' not defined in featureData") |
|
23 |
+ return(TRUE) |
|
24 |
+ }) |
|
25 |
+>>>>>>> Removed tryCatch() statements in readIdatFiles. Restored previous implementation. |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48951 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48950 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -3,6 +3,4 @@ setOldClass("ff_matrix") |
3 | 3 |
setOldClass("ffdf") |
4 | 4 |
setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
5 | 5 |
setClassUnion("integerOrMissing", c("integer", "missing", "numeric")) |
6 |
-##setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
7 |
-##setClass("CNSetTest", contains="SnpSuperSet") |
|
8 | 6 |
|
Added a lot of generics for accessing and updating elements in the
LinearModelParameter class.
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48949 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,26 +1,8 @@ |
1 |
-setOldClass("ffdf") |
|
1 |
+setOldClass("ellipse") |
|
2 | 2 |
setOldClass("ff_matrix") |
3 |
-##setClassUnion("matrix_or_ff", c("matrix", "ff_matrix")) |
|
4 |
-setClassUnion("list_or_ffdf", c("list", "ffdf")) |
|
3 |
+setOldClass("ffdf") |
|
5 | 4 |
setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
6 |
-setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
7 |
-setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
|
8 |
- .Object@lM <- lM |
|
9 |
- .Object <- callNextMethod(.Object, ...) |
|
10 |
-}) |
|
11 |
- |
|
12 |
-setValidity("CNSetLM", |
|
13 |
- function(object){ |
|
14 |
- if(!"batch" %in% varLabels(protocolData(object))) |
|
15 |
- return("'batch' not defined in protocolData") |
|
16 |
- if(!"chromosome" %in% fvarLabels(object)) |
|
17 |
- return("'chromosome' not defined in featureData") |
|
18 |
- if(!"position" %in% fvarLabels(object)) |
|
19 |
- return("'position' not defined in featureData") |
|
20 |
- if(!"isSnp" %in% fvarLabels(object)) |
|
21 |
- return("'isSnp' not defined in featureData") |
|
22 |
- return(TRUE) |
|
23 |
- }) |
|
24 |
- |
|
5 |
+setClassUnion("integerOrMissing", c("integer", "missing", "numeric")) |
|
6 |
+##setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
25 | 7 |
##setClass("CNSetTest", contains="SnpSuperSet") |
26 | 8 |
|
the copynumber vignette has some experimental code that needs to be removed
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48926 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -8,6 +8,7 @@ setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
8 | 8 |
.Object@lM <- lM |
9 | 9 |
.Object <- callNextMethod(.Object, ...) |
10 | 10 |
}) |
11 |
+ |
|
11 | 12 |
setValidity("CNSetLM", |
12 | 13 |
function(object){ |
13 | 14 |
if(!"batch" %in% varLabels(protocolData(object))) |
... | ... |
@@ -20,3 +21,6 @@ setValidity("CNSetLM", |
20 | 21 |
return("'isSnp' not defined in featureData") |
21 | 22 |
return(TRUE) |
22 | 23 |
}) |
24 |
+ |
|
25 |
+##setClass("CNSetTest", contains="SnpSuperSet") |
|
26 |
+ |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48613 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@47121 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -8,3 +8,16 @@ setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
8 | 8 |
.Object@lM <- lM |
9 | 9 |
.Object <- callNextMethod(.Object, ...) |
10 | 10 |
}) |
11 |
+ |
|
12 |
+setValidity("CNSetLM", |
|
13 |
+ function(object){ |
|
14 |
+ if(!"batch" %in% varLabels(protocolData(object))) |
|
15 |
+ return("'batch' not defined in protocolData") |
|
16 |
+ if(!"chromosome" %in% fvarLabels(object)) |
|
17 |
+ return("'chromosome' not defined in featureData") |
|
18 |
+ if(!"position" %in% fvarLabels(object)) |
|
19 |
+ return("'position' not defined in featureData") |
|
20 |
+ if(!"isSnp" %in% fvarLabels(object)) |
|
21 |
+ return("'isSnp' not defined in featureData") |
|
22 |
+ return(TRUE) |
|
23 |
+ }) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45497 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -4,7 +4,7 @@ setOldClass("ff_matrix") |
4 | 4 |
setClassUnion("list_or_ffdf", c("list", "ffdf")) |
5 | 5 |
setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
6 | 6 |
setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
7 |
-setMethod("initialize", "CNSetLM", function(.Object, CA=new("matrix"), CB=new("matrix"), lM=new("list"), ...){ |
|
8 |
- .Object <- callNextMethod(.Object, CA=CA, CB=CB, lM=lM, ...) |
|
9 |
- .Object |
|
7 |
+setMethod("initialize", "CNSetLM", function(.Object, lM=new("list"), ...){ |
|
8 |
+ .Object@lM <- lM |
|
9 |
+ .Object <- callNextMethod(.Object, ...) |
|
10 | 10 |
}) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45348 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -2,6 +2,7 @@ setOldClass("ffdf") |
2 | 2 |
setOldClass("ff_matrix") |
3 | 3 |
##setClassUnion("matrix_or_ff", c("matrix", "ff_matrix")) |
4 | 4 |
setClassUnion("list_or_ffdf", c("list", "ffdf")) |
5 |
+setClassUnion("ff_or_matrix", c("ff_matrix", "matrix", "ffdf")) |
|
5 | 6 |
setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
6 | 7 |
setMethod("initialize", "CNSetLM", function(.Object, CA=new("matrix"), CB=new("matrix"), lM=new("list"), ...){ |
7 | 8 |
.Object <- callNextMethod(.Object, CA=CA, CB=CB, lM=lM, ...) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45177 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,4 +1,9 @@ |
1 | 1 |
setOldClass("ffdf") |
2 | 2 |
setOldClass("ff_matrix") |
3 | 3 |
##setClassUnion("matrix_or_ff", c("matrix", "ff_matrix")) |
4 |
-##setClassUnion("list_or_ffdf", c("list", "ffdf")) |
|
4 |
+setClassUnion("list_or_ffdf", c("list", "ffdf")) |
|
5 |
+setClass("CNSetLM", contains="CNSet", representation(lM="list_or_ffdf")) |
|
6 |
+setMethod("initialize", "CNSetLM", function(.Object, CA=new("matrix"), CB=new("matrix"), lM=new("list"), ...){ |
|
7 |
+ .Object <- callNextMethod(.Object, CA=CA, CB=CB, lM=lM, ...) |
|
8 |
+ .Object |
|
9 |
+}) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45165 bc3139a8-67e5-0310-9ffc-ced21a209358
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45126 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
deleted file mode 100644 |
... | ... |
@@ -1,74 +0,0 @@ |
1 |
-setOldClass("ffdf") |
|
2 |
-setOldClass("ff_matrix") |
|
3 |
-setClassUnion("matrix_or_ff", c("matrix", "ff_matrix")) |
|
4 |
-setClassUnion("list_or_ffdf", c("list", "ffdf")) |
|
5 |
-setClass("CrlmmContainer", contains="eSet", |
|
6 |
- representation(options="list", |
|
7 |
- genomeAnnotation="ANY", |
|
8 |
- "VIRTUAL")) |
|
9 |
- |
|
10 |
-setMethod("show", "CrlmmContainer", function(object){ |
|
11 |
- callNextMethod(object) |
|
12 |
- cat("options: \n") |
|
13 |
- print(names(crlmmOptions(object))) |
|
14 |
- cat("\n") |
|
15 |
- cat("genomeAnnotation:", nrow(genomeAnnotation(object)), " rows, ", ncol(genomeAnnotation(object)), " columns\n") |
|
16 |
- print(genomeAnnotation(object)[1:5, ]) |
|
17 |
- cat("\n") |
|
18 |
-}) |
|
19 |
-setClass("AlleleSet", contains="CrlmmContainer") |
|
20 |
-setClass("CallSet", contains="AlleleSet") |
|
21 |
-setClass("CNSet", contains="CallSet", |
|
22 |
- representation(lM="list_or_ffdf")) |
|
23 |
- |
|
24 |
-setClass("IlluminaRGSet", contains="CrlmmContainer") |
|
25 |
-setClass("IlluminaXYSet", contains="CrlmmContainer") |
|
26 |
- |
|
27 |
-setClass("AffymetrixAlleleSet", contains="AlleleSet") ##AffymetrixAlleleSet |
|
28 |
-setClass("IlluminaAlleleSet", contains="AlleleSet") |
|
29 |
-##setClass("AffymetrixBigData", contains="AffymetrixAlleleSet") |
|
30 |
-##setClass("AffymetrixSmallData", contains="AffymetrixAlleleSet") |
|
31 |
-##setClass("IlluminaSmallData", contains="IlluminaAlleleSet") |
|
32 |
-##setClass("IlluminaBigData", contains="IlluminaAlleleSet") |
|
33 |
-##setMethod("initialize", "AffymetrixBigData", function(.Object, annotation){ |
|
34 |
-## .Object <- callNextMethod(.Object) |
|
35 |
-## if(!missing(annotation)) annotation(.Object) <- annotation |
|
36 |
-## .Object |
|
37 |
-##}) |
|
38 |
-##setClass("AffymetrixCallSet", contains="CallSet") |
|
39 |
-##setClass("IlluminaCallSet", contains="CallSet") |
|
40 |
-setMethod("initialize", "AlleleSet", function(.Object, alleleA=new("matrix"), alleleB=new("matrix"), ...){ |
|
41 |
- .Object <- callNextMethod(.Object, alleleA=alleleA, alleleB=alleleB, ...) |
|
42 |
- storageMode(.Object) <- "environment" |
|
43 |
- .Object |
|
44 |
-}) |
|
45 |
-setMethod("initialize", "CallSet", function(.Object, call=new("matrix"), callProbability=new("matrix"), ...){ |
|
46 |
- .Object <- callNextMethod(.Object, call=call, callProbability=callProbability, ...) |
|
47 |
- storageMode(.Object) <- "environment" |
|
48 |
- .Object |
|
49 |
-}) |
|
50 |
-setMethod("initialize", "CNSet", function(.Object, CA=new("matrix"), CB=new("matrix"), lM=new("list"), ...){ |
|
51 |
- .Object <- callNextMethod(.Object, CA=CA, CB=CB, lM=lM,...) |
|
52 |
- storageMode(.Object) <- "environment" |
|
53 |
- .Object |
|
54 |
-}) |
|
55 |
-setValidity("AlleleSet", function(object) { |
|
56 |
- assayDataValidMembers(assayData(object), c("alleleA", "alleleB")) |
|
57 |
-}) |
|
58 |
-setValidity("IlluminaRGSet", function(object) { |
|
59 |
- assayDataValidMembers(assayData(object), c("R", "G", "zero")) |
|
60 |
-}) |
|
61 |
-setValidity("IlluminaXYSet", function(object) { |
|
62 |
- assayDataValidMembers(assayData(object), c("X", "Y", "zero")) |
|
63 |
-}) |
|
64 |
- |
|
65 |
-setValidity("CallSet", function(object) { |
|
66 |
- assayDataValidMembers(assayData(object), c("alleleA", "alleleB", "call", "callProbability")) |
|
67 |
-}) |
|
68 |
-setValidity("CNSet", function(object) { |
|
69 |
- assayDataValidMembers(assayData(object), c("alleleA", "alleleB", "call", "callProbability", "CA", "CB")) |
|
70 |
-}) |
|
71 |
- |
|
72 |
- |
|
73 |
- |
|
74 |
- |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45083 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,74 @@ |
1 |
+setOldClass("ffdf") |
|
2 |
+setOldClass("ff_matrix") |
|
3 |
+setClassUnion("matrix_or_ff", c("matrix", "ff_matrix")) |
|
4 |
+setClassUnion("list_or_ffdf", c("list", "ffdf")) |
|
5 |
+setClass("CrlmmContainer", contains="eSet", |
|
6 |
+ representation(options="list", |
|
7 |
+ genomeAnnotation="ANY", |
|
8 |
+ "VIRTUAL")) |
|
9 |
+ |
|
10 |
+setMethod("show", "CrlmmContainer", function(object){ |
|
11 |
+ callNextMethod(object) |
|
12 |
+ cat("options: \n") |
|
13 |
+ print(names(crlmmOptions(object))) |
|
14 |
+ cat("\n") |
|
15 |
+ cat("genomeAnnotation:", nrow(genomeAnnotation(object)), " rows, ", ncol(genomeAnnotation(object)), " columns\n") |
|
16 |
+ print(genomeAnnotation(object)[1:5, ]) |
|
17 |
+ cat("\n") |
|
18 |
+}) |
|
19 |
+setClass("AlleleSet", contains="CrlmmContainer") |
|
20 |
+setClass("CallSet", contains="AlleleSet") |
|
21 |
+setClass("CNSet", contains="CallSet", |
|
22 |
+ representation(lM="list_or_ffdf")) |
|
23 |
+ |
|
24 |
+setClass("IlluminaRGSet", contains="CrlmmContainer") |
|
25 |
+setClass("IlluminaXYSet", contains="CrlmmContainer") |
|
26 |
+ |
|
27 |
+setClass("AffymetrixAlleleSet", contains="AlleleSet") ##AffymetrixAlleleSet |
|
28 |
+setClass("IlluminaAlleleSet", contains="AlleleSet") |
|
29 |
+##setClass("AffymetrixBigData", contains="AffymetrixAlleleSet") |
|
30 |
+##setClass("AffymetrixSmallData", contains="AffymetrixAlleleSet") |
|
31 |
+##setClass("IlluminaSmallData", contains="IlluminaAlleleSet") |
|
32 |
+##setClass("IlluminaBigData", contains="IlluminaAlleleSet") |
|
33 |
+##setMethod("initialize", "AffymetrixBigData", function(.Object, annotation){ |
|
34 |
+## .Object <- callNextMethod(.Object) |
|
35 |
+## if(!missing(annotation)) annotation(.Object) <- annotation |
|
36 |
+## .Object |
|
37 |
+##}) |
|
38 |
+##setClass("AffymetrixCallSet", contains="CallSet") |
|
39 |
+##setClass("IlluminaCallSet", contains="CallSet") |
|
40 |
+setMethod("initialize", "AlleleSet", function(.Object, alleleA=new("matrix"), alleleB=new("matrix"), ...){ |
|
41 |
+ .Object <- callNextMethod(.Object, alleleA=alleleA, alleleB=alleleB, ...) |
|
42 |
+ storageMode(.Object) <- "environment" |
|
43 |
+ .Object |
|
44 |
+}) |
|
45 |
+setMethod("initialize", "CallSet", function(.Object, call=new("matrix"), callProbability=new("matrix"), ...){ |
|
46 |
+ .Object <- callNextMethod(.Object, call=call, callProbability=callProbability, ...) |
|
47 |
+ storageMode(.Object) <- "environment" |
|
48 |
+ .Object |
|
49 |
+}) |
|
50 |
+setMethod("initialize", "CNSet", function(.Object, CA=new("matrix"), CB=new("matrix"), lM=new("list"), ...){ |
|
51 |
+ .Object <- callNextMethod(.Object, CA=CA, CB=CB, lM=lM,...) |
|
52 |
+ storageMode(.Object) <- "environment" |
|
53 |
+ .Object |
|
54 |
+}) |
|
55 |
+setValidity("AlleleSet", function(object) { |
|
56 |
+ assayDataValidMembers(assayData(object), c("alleleA", "alleleB")) |
|
57 |
+}) |
|
58 |
+setValidity("IlluminaRGSet", function(object) { |
|
59 |
+ assayDataValidMembers(assayData(object), c("R", "G", "zero")) |
|
60 |
+}) |
|
61 |
+setValidity("IlluminaXYSet", function(object) { |
|
62 |
+ assayDataValidMembers(assayData(object), c("X", "Y", "zero")) |
|
63 |
+}) |
|
64 |
+ |
|
65 |
+setValidity("CallSet", function(object) { |
|
66 |
+ assayDataValidMembers(assayData(object), c("alleleA", "alleleB", "call", "callProbability")) |
|
67 |
+}) |
|
68 |
+setValidity("CNSet", function(object) { |
|
69 |
+ assayDataValidMembers(assayData(object), c("alleleA", "alleleB", "call", "callProbability", "CA", "CB")) |
|
70 |
+}) |
|
71 |
+ |
|
72 |
+ |
|
73 |
+ |
|
74 |
+ |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@43365 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
deleted file mode 100644 |
... | ... |
@@ -1,9 +0,0 @@ |
1 |
-##setClass("CNSet", contains="eSet") |
|
2 |
-##setClass("CNSet", contains=c("SnpCallSetPlus", "CNSet")) |
|
3 |
-setClass("CNSet", contains="SnpCallSetPlus", |
|
4 |
- representation(emissionPr="array", |
|
5 |
- segmentData="RangedData")) |
|
6 |
- |
|
7 |
-##setClass("SegmentSet", contains="CNSet", |
|
8 |
-## representation(emissionPr="array", |
|
9 |
-## segmentData="data.frame")) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@43144 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,9 @@ |
1 |
-setClass("CopyNumberSet", contains="SnpLevelSet") |
|
2 |
-setClass("CrlmmSet", contains=c("SnpCallSetPlus", "CopyNumberSet")) |
|
3 |
-setClass("SnpCallSetPlusFF", contains="SnpCallSetPlus") |
|
4 |
-setClass("CrlmmSetFF", contains="CrlmmSet") |
|
5 |
-setClass("SegmentSet", contains="CrlmmSet", |
|
1 |
+##setClass("CNSet", contains="eSet") |
|
2 |
+##setClass("CNSet", contains=c("SnpCallSetPlus", "CNSet")) |
|
3 |
+setClass("CNSet", contains="SnpCallSetPlus", |
|
6 | 4 |
representation(emissionPr="array", |
7 |
- segmentData="data.frame")) |
|
5 |
+ segmentData="RangedData")) |
|
6 |
+ |
|
7 |
+##setClass("SegmentSet", contains="CNSet", |
|
8 |
+## representation(emissionPr="array", |
|
9 |
+## segmentData="data.frame")) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@43010 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,11 +1,7 @@ |
1 |
-## Class definition |
|
2 |
-setClass("ABset", contains="eSet", |
|
3 |
- prototype = prototype( |
|
4 |
- new("VersionedBiobase", |
|
5 |
- versions=c(classVersion("eSet"), SnpSet="1.0.0")))) |
|
6 |
-setClass("crlmmSet", contains="eSet") |
|
7 |
-setClass("CrlmmSetList", contains="list") |
|
8 |
-setClass("CopyNumberSet", contains="eSet", |
|
9 |
- prototype = prototype( |
|
10 |
- new("VersionedBiobase", |
|
11 |
- versions=c(classVersion("eSet"), SnpSet="1.0.0")))) |
|
1 |
+setClass("CopyNumberSet", contains="SnpLevelSet") |
|
2 |
+setClass("CrlmmSet", contains=c("SnpCallSetPlus", "CopyNumberSet")) |
|
3 |
+setClass("SnpCallSetPlusFF", contains="SnpCallSetPlus") |
|
4 |
+setClass("CrlmmSetFF", contains="CrlmmSet") |
|
5 |
+setClass("SegmentSet", contains="CrlmmSet", |
|
6 |
+ representation(emissionPr="array", |
|
7 |
+ segmentData="data.frame")) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@40309 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,2 +1,11 @@ |
1 | 1 |
## Class definition |
2 |
+setClass("ABset", contains="eSet", |
|
3 |
+ prototype = prototype( |
|
4 |
+ new("VersionedBiobase", |
|
5 |
+ versions=c(classVersion("eSet"), SnpSet="1.0.0")))) |
|
2 | 6 |
setClass("crlmmSet", contains="eSet") |
7 |
+setClass("CrlmmSetList", contains="list") |
|
8 |
+setClass("CopyNumberSet", contains="eSet", |
|
9 |
+ prototype = prototype( |
|
10 |
+ new("VersionedBiobase", |
|
11 |
+ versions=c(classVersion("eSet"), SnpSet="1.0.0")))) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@37667 bc3139a8-67e5-0310-9ffc-ced21a209358