Browse code

Commit made by the Bioconductor Git-SVN bridge.

Commit id: 2155bb403810b2744c1ee1c364aa2fe6216a6671

bumped version


Commit id: f2df86b5e594d94aa0fd591152f9121554dfc47c

more work on permutations; now including unitTests


Commit id: 040af54e133c6fad141f3047a5b5a60772642b33

unit test for permutation matrix



git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/bsseq@100731 bc3139a8-67e5-0310-9ffc-ced21a209358

khansen authored on 16/03/2015 19:57:19
Showing 4 changed files

... ...
@@ -1,12 +1,12 @@
1 1
 Package: bsseq
2
-Version: 1.3.6
2
+Version: 1.3.7
3 3
 Title: Analyze, manage and store bisulfite sequencing data.
4 4
 Description: Tools for analyzing and visualizing bisulfite sequencing data
5 5
 Authors@R: c(person(c("Kasper", "Daniel"), "Hansen", role = c("aut", "cre"),
6 6
                     email = "kasperdanielhansen@gmail.com"))
7 7
 Depends: R (>= 2.15), methods, BiocGenerics, S4Vectors, IRanges (>= 2.1.10),
8 8
         GenomicRanges (>= 1.19.6), parallel, matrixStats, GenomeInfoDb
9
-Imports: scales, stats, graphics, Biobase, locfit
9
+Imports: scales, stats, graphics, Biobase, locfit, gtools
10 10
 Suggests: RUnit, bsseqData
11 11
 Collate: hasGRanges.R BSseq_class.R BSseqTstat_class.R BSseq_utils.R combine.R 
12 12
         utils.R read.bsmooth.R read.bismark.R BSmooth.R BSmooth.tstat.R dmrFinder.R
... ...
@@ -27,6 +27,7 @@ importFrom(Biobase, "validMsg")
27 27
 importMethodsFrom(GenomeInfoDb, "seqlengths", "seqlengths<-", "seqinfo", "seqinfo<-",
28 28
                   "seqnames", "seqnames<-", "seqlevels", "seqlevels<-")
29 29
 import(S4Vectors)
30
+importFrom(gtools, "combinations")
30 31
 
31 32
 ##
32 33
 ## Exporting
... ...
@@ -68,6 +68,7 @@ getFWER <- function(null, type = "blocks") {
68 68
 }
69 69
        
70 70
 makeIdxMatrix <- function(group1, group2, testIsSymmetric = TRUE, includeUnbalanced = TRUE) {
71
+    ## gtools::combinations
71 72
     groupBoth <- c(group1, group2)
72 73
     idxMatrix1 <- NULL
73 74
     subsetByMatrix <- function(vec, mat) {
... ...
@@ -80,7 +81,10 @@ makeIdxMatrix <- function(group1, group2, testIsSymmetric = TRUE, includeUnbalan
80 81
         do.call(rbind, tmp)
81 82
     }
82 83
     if(length(group1) == 1 && length(group1) == 1) {
83
-        idxMatrix1 <- as.matrix(group1)
84
+        if(testIsSymmetric)
85
+            idxMatrix1 <- as.matrix(group1)
86
+        else
87
+            idxMatrix1 <- as.matrix(c(group1, group2))
84 88
     }
85 89
     if(length(group1) == 2 && length(group2) == 2) {
86 90
         if(testIsSymmetric) {
... ...
@@ -93,21 +97,28 @@ makeIdxMatrix <- function(group1, group2, testIsSymmetric = TRUE, includeUnbalan
93 97
         }
94 98
     }
95 99
     if(length(group1) == 3 && length(group1) == 3) {
96
-        newMatrix <- combineMat(subsetByMatrix(group1, combinations(3,2)),
97
-                                as.matrix(group2, ncol = 1))
98
-        idxMatrix1 <- rbind(group1, newMatrix)
99
-        if(!testIsSymmetric) {
100
-            newMatrix <- combineMat(as.matrix(group1, ncol = 1),
101
-                                    subsetByMatrix(group2, combinations(3,2)))
102
-            idxMatrix1 <- rbind(idxMatrix1, group2, newMatrix)
100
+        if(testIsSymmetric) {
101
+            idxMatrix1 <- rbind(group1,
102
+                                combineMat(subsetByMatrix(group1, combinations(3,2)),
103
+                                           as.matrix(group2, ncol = 1)))
104
+
105
+        } else {
106
+            idxMatrix1 <- rbind(group1, group2,
107
+                                combineMat(subsetByMatrix(group1, combinations(3,2)),
108
+                                           as.matrix(group2, ncol = 1)),
109
+                                combineMat(as.matrix(group1, ncol = 1),
110
+                                           subsetByMatrix(group2, combinations(3,2))))
103 111
         }
104 112
     }
105 113
     if(length(group1) == 4 && length(group1) == 4) {
106
-        newMatrix <- combineMat(subsetByMatrix(group1, combinations(4,2)),
107
-                                subsetByMatrix(group2, combinations(4,2)))
108
-        idxMatrix1 <- rbind(group1, newMatrix)
109
-        if(!testIsSymmetric) {
110
-            idxMatrix1 <- rbind(group2, idxMatrix1)
114
+        if(testIsSymmetric) {
115
+            idxMatrix1 <- rbind(group1,
116
+                                combineMat(subsetByMatrix(group1, combinations(3,2)),
117
+                                           subsetByMatrix(group2, combinations(4,2))))
118
+        } else {
119
+            idxMatrix1 <- rbind(group1, group2,
120
+                                combineMat(subsetByMatrix(group1, combinations(4,2)),
121
+                                           subsetByMatrix(group2, combinations(4,2))))
111 122
         }
112 123
         if(includeUnbalanced) {
113 124
             newMatrix <- combineMat(subsetByMatrix(group1, combinations(4,3)),
... ...
@@ -119,15 +130,29 @@ makeIdxMatrix <- function(group1, group2, testIsSymmetric = TRUE, includeUnbalan
119 130
                                     subsetByMatrix(group2, combinations(4,3)))
120 131
             idxMatrix1 <- rbind(idxMatrix1, newMatrix)
121 132
         }
122
-
123 133
     }
124
-    if(length(group1) == 5 && length(group1) == 5 && testIsSymmetric) {
125
-        idxMatrix1 <- rbind(group1,
126
-                            combineMat(subsetByMatrix(group1, combinations(5, 3)),
127
-                                       subsetByMatrix(group2, combinations(5, 2))))
128
-        if(includeUnbalanced)
134
+    if(length(group1) == 5 && length(group1) == 5) {
135
+        if(testIsSymmetric) {
136
+            idxMatrix1 <- rbind(group1,
137
+                                combineMat(subsetByMatrix(group1, combinations(5, 3)),
138
+                                           subsetByMatrix(group2, combinations(5, 2))))
139
+        } else {
140
+            idxMatrix1 <- rbind(group1, group2,
141
+                                combineMat(subsetByMatrix(group1, combinations(5, 3)),
142
+                                           subsetByMatrix(group2, combinations(5, 2))),
143
+                                combineMat(subsetByMatrix(group1, combinations(5, 2)),
144
+                                           subsetByMatrix(group2, combinations(5, 3))))
145
+        }
146
+        if(includeUnbalanced) {
129 147
             idxMatrix1 <- rbind(idxMatrix1,
130
-                                combineMat(subsetByMatrix(group1, combinations(5,4)), group2))
148
+                                combineMat(subsetByMatrix(group1, combinations(5,4)),
149
+                                           as.matrix(group2, ncol = 1)))
150
+        }
151
+        if(includeUnbalanced && !testIsSymmetric) {
152
+            idxMatrix1 <- rbind(idxMatrix1,
153
+                                combineMat(as.matrix(group1, ncol = 1),
154
+                                           subsetByMatrix(group2, combinations(5,4))))
155
+        }
131 156
     }
132 157
     if(is.null(idxMatrix1))
133 158
         stop("unable to handle this combination of 'group1', 'group2' and 'testIsSymmetric'")
134 159
new file mode 100644
... ...
@@ -0,0 +1,84 @@
1
+test_makeIdxMatrix_perm1 <- function() {
2
+    grp1 <- paste0("A", 1)
3
+    grp2 <- paste0("B", 1)
4
+
5
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = FALSE)[[1]]
6
+    checkEquals(anyDuplicated(res), 0L)
7
+    checkEquals(res[1,], grp1)
8
+    checkEquals(res[2,], grp2)
9
+    checkEquals(nrow(res), choose(2,1)) # Fail
10
+
11
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = TRUE)[[1]]
12
+    checkEquals(anyDuplicated(res), 0L)
13
+    checkEquals(res[1,], grp1)
14
+    checkEquals(nrow(res), choose(2,1) / 2)
15
+}
16
+
17
+test_makeIdxMatrix_perm2 <- function() {
18
+    grp1 <- paste0("A", 1:2)
19
+    grp2 <- paste0("B", 1:2)
20
+    
21
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = FALSE)[[1]]
22
+    checkEquals(anyDuplicated(res), 0)
23
+    checkEquals(res[1,], grp1)
24
+    checkEquals(res[2,], grp2)
25
+    checkEquals(nrow(res), choose(4,2))
26
+    
27
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = TRUE)[[1]]
28
+    checkEquals(anyDuplicated(res), 0)
29
+    checkEquals(res[1,], grp1)
30
+    checkEquals(nrow(res), choose(4,2) / 2)
31
+}
32
+
33
+test_makeIdxMatrix_perm3 <- function() {
34
+    grp1 <- paste0("A", 1:3)
35
+    grp2 <- paste0("B", 1:3)
36
+
37
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = FALSE)[[1]]
38
+    checkEquals(anyDuplicated(res), 0)
39
+    checkEquals(res[1,], grp1)
40
+    checkEquals(res[2,], grp2)
41
+    checkEquals(nrow(res), choose(6,3))
42
+
43
+    res <- bsseq:::makeIdxMatrix(grp1, grp2, testIsSymmetric = TRUE)[[1]]
44
+    checkEquals(anyDuplicated(res), 0)
45
+    checkEquals(res[1,], grp1)
46
+    checkEquals(nrow(res), choose(6,3) / 2)
47
+}
48
+    
49
+test_makeIdxMatrix_perm4 <- function() {
50
+    grp1 <- paste0("A", 1:4)
51
+    grp2 <- paste0("B", 1:4)
52
+
53
+    res <- bsseq:::makeIdxMatrix(grp1, grp2,
54
+                                 testIsSymmetric = FALSE, includeUnbalanced = TRUE)[[1]]
55
+    checkEquals(anyDuplicated(res), 0)
56
+    checkEquals(res[1,], grp1)
57
+    checkEquals(res[2,], grp2)
58
+    checkEquals(nrow(res), choose(8,4))
59
+
60
+    res <- bsseq:::makeIdxMatrix(grp1, grp2,
61
+                                 testIsSymmetric = TRUE, includeUnbalanced = TRUE)[[1]]
62
+    checkEquals(anyDuplicated(res), 0)
63
+    checkEquals(res[1,], grp1)
64
+    checkEquals(nrow(res), choose(8,4) / 2) # Fail
65
+}
66
+    
67
+test_makeIdxMatrix_perm5 <- function() {
68
+    grp1 <- paste0("A", 1:5)
69
+    grp2 <- paste0("B", 1:5)
70
+
71
+    res <- bsseq:::makeIdxMatrix(grp1, grp2,
72
+                                 testIsSymmetric = FALSE, includeUnbalanced = TRUE)[[1]]
73
+    checkEquals(anyDuplicated(res), 0)
74
+    checkEquals(res[1,], grp1)
75
+    checkEquals(res[2,], grp2)
76
+    checkEquals(nrow(res), choose(10,5))
77
+
78
+    res <- bsseq:::makeIdxMatrix(grp1, grp2,
79
+                                 testIsSymmetric = TRUE, includeUnbalanced = TRUE)[[1]]
80
+    checkEquals(anyDuplicated(res), 0)
81
+    checkEquals(res[1,], grp1)
82
+    checkEquals(nrow(res), choose(10,5) / 2)
83
+}
84
+