Browse code

added citation and small tests; modified some minor defaults; add endTimeEvery

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

Ramon Diaz-Uriarte authored on 30/04/2015 12:20:21
Showing 10 changed files

... ...
@@ -1,21 +1,20 @@
1 1
 Package: OncoSimulR
2 2
 Type: Package
3 3
 Title: Simulation of cancer progresion with order restrictions
4
-Version: 1.3.0
5
-Date: 2014-07-14
6
-Author: Ramon Diaz-Uriarte.
4
+Version: 1.3.1
5
+Date: 2015-04-30
6
+Author: Ramon Diaz-Uriarte. 
7 7
 Maintainer: Ramon Diaz-Uriarte <rdiaz02@gmail.com>
8 8
 Description: Functions for simulating and plotting cancer progression
9
-        data, including drivers and passengers, and allowing for order
10
-        restrictions. Simulations use continuous-time models (based on
11
-        Bozic et al., 2010 and McFarland et al., 2013) and fitness
12
-        functions account for possible restrictions in the order of
13
-        accumulation of mutations.
9
+    data, including drivers and passengers, and allowing for order
10
+    restrictions. Simulations use continuous-time models (based on Bozic
11
+    et al., 2010 and McFarland et al., 2013) and fitness functions account
12
+    for possible restrictions in the order of accumulation of mutations.
14 13
 biocViews: BiologicalQuestion, SomaticMutation
15 14
 License: GPL (>= 3)
16 15
 Depends: R (>= 3.1.0)
17 16
 Imports: Rcpp (>= 0.11.1), parallel, data.table, graph, Rgraphviz
18
-Suggests: BiocStyle, knitr, Oncotree
17
+Suggests: BiocStyle, knitr, Oncotree, testthat
19 18
 LinkingTo: Rcpp
20 19
 VignetteBuilder: knitr
21 20
 SystemRequirements: C++11
... ...
@@ -45,12 +45,15 @@ oncoSimulPop <- function(Nindiv,
45 45
                          mu = 1e-6,
46 46
                          detectionSize = 1e8,
47 47
                          detectionDrivers = 4,
48
-                         sampleEvery = 1,
48
+                         sampleEvery = ifelse(model %in% c("Bozic", "Exp"), 1,
49
+                             0.025),
49 50
                          initSize = 500,
50 51
                          s = 0.1,
51 52
                          sh = -1,
52 53
                          K = initSize/(exp(1) - 1),
53 54
                          keepEvery = sampleEvery,
55
+                         endTimeEvery = ifelse(model %in% c("Bozic", "Exp"), -9,
56
+                                               5 * sampleEvery),
54 57
                          finalTime = 0.25 * 25 * 365,
55 58
                          onlyCancer = TRUE,
56 59
                          max.memory = 2000,
... ...
@@ -78,6 +81,7 @@ oncoSimulPop <- function(Nindiv,
78 81
                         sh = sh,
79 82
                         K = K,
80 83
                         keepEvery = keepEvery,
84
+                        endTimeEvery = endTimeEvery,
81 85
                         finalTime = finalTime,
82 86
                         onlyCancer = onlyCancer,
83 87
                         max.memory = max.memory,
... ...
@@ -99,12 +103,15 @@ oncoSimulIndiv <- function(poset,
99 103
                            mu = 1e-6,
100 104
                            detectionSize = 1e8,
101 105
                            detectionDrivers = 4,
102
-                           sampleEvery = 1,
106
+                           sampleEvery = ifelse(model %in% c("Bozic", "Exp"), 1,
107
+                               0.025),
103 108
                            initSize = 500,
104 109
                            s = 0.1,
105 110
                            sh = -1,
106 111
                            K = initSize/(exp(1) - 1),
107 112
                            keepEvery = sampleEvery,
113
+                           endTimeEvery = ifelse(model %in% c("Bozic", "Exp"), -9,
114
+                               5 * sampleEvery),
108 115
                            finalTime = 0.25 * 25 * 365,
109 116
                            onlyCancer = TRUE,
110 117
                            max.memory = 2000,
... ...
@@ -112,7 +119,11 @@ oncoSimulIndiv <- function(poset,
112 119
                            verbosity = 0
113 120
                            ) {
114 121
     call <- match.call()
115
-    rt <- poset.to.restrictTable(poset)
122
+    ## a backdoor to allow passing restrictionTables directly
123
+    if(inherits(poset, "restrictionTable"))
124
+        rt <- poset
125
+    else
126
+        rt <- poset.to.restrictTable(poset)
116 127
 
117 128
 
118 129
     numDrivers <- nrow(rt)
... ...
@@ -148,11 +159,11 @@ oncoSimulIndiv <- function(poset,
148 159
         warning("With the McFarland model you often want smaller sampleEvery")
149 160
     }
150 161
     
151
-    if(typeFitness == "mcfarlandlog") {
152
-        endTimeEvery <- keepEvery
153
-    } else {
154
-        endTimeEvery <- -9
155
-    }
162
+    ## if(typeFitness == "mcfarlandlog") {
163
+    ##     endTimeEvery <- keepEvery
164
+    ## } else {
165
+    ##     endTimeEvery <- -9
166
+    ## }
156 167
 
157 168
 
158 169
 
... ...
@@ -472,7 +483,7 @@ oncoSimul.internal <- function(restrict.table,
472 483
                                keepEvery = 20,
473 484
                                alpha = 0.0015,
474 485
                                K = 1000,
475
-                               endTimeEvery = NULL,
486
+                               endTimeEvery = 5 * sampleEvery,
476 487
                                finalDrivers = 1000) {
477 488
 
478 489
     if(initSize_species < 10) {
... ...
@@ -514,18 +525,18 @@ oncoSimul.internal <- function(restrict.table,
514 525
         warning("Using fitness exp with death != 1")
515 526
 
516 527
 
517
-    if( (is.null(endTimeEvery) || (endTimeEvery > 0)) &&
518
-       (typeFitness %in% c("bozic1", "exp") )) {
519
-        warning(paste("endTimeEvery will take a positive value. ",
520
-                      "This will make simulations not stop until the next ",
521
-                      "endTimeEvery has been reached. Thus, in simulations ",
522
-                      "with very fast growth, simulations can take a long ",
523
-                      "time to finish, or can hit the wall time limit. "))
524
-    }
525
-    if(is.null(endTimeEvery))
526
-        endTimeEvery <- keepEvery
527
-    if( (endTimeEvery > 0) && (endTimeEvery %% keepEvery) )
528
-        warning("!(endTimeEvery %% keepEvery)")
528
+    ## if( (is.null(endTimeEvery) || (endTimeEvery > 0)) &&
529
+    ##    (typeFitness %in% c("bozic1", "exp") )) {
530
+    ##     warning(paste("endTimeEvery will take a positive value. ",
531
+    ##                   "This will make simulations not stop until the next ",
532
+    ##                   "endTimeEvery has been reached. Thus, in simulations ",
533
+    ##                   "with very fast growth, simulations can take a long ",
534
+    ##                   "time to finish, or can hit the wall time limit. "))
535
+    ## }
536
+    ## if(is.null(endTimeEvery))
537
+    ##     endTimeEvery <- keepEvery
538
+    ## if( (endTimeEvery > 0) && (endTimeEvery %% keepEvery) )
539
+    ##     warning("!(endTimeEvery %% keepEvery)")
529 540
     ## a sanity check in restricTable, so no neg. indices for the positive deps
530 541
     neg.deps <- function(x) {
531 542
         ## checks a row of restrict.table
... ...
@@ -743,9 +754,27 @@ convertRestrictTable <- function(x) {
743 754
 
744 755
 
745 756
 
746
-adjmat.to.restrictTable <- function(x) {
757
+adjmat.to.restrictTable <- function(x, root = FALSE,
758
+                                    rootNames = c("0", "root", "Root")) {
747 759
     ## we have the zero
748
-    ## x <- x[-1, -1]
760
+    if( any(colnames(x) %in% c("0", "root", "Root")) & !root)
761
+        warning("Looks like the matrix has a root but you specified root = FALSE")
762
+
763
+    if(!identical(colnames(x), rownames(x)))
764
+        stop("colnames and rownames not identical")
765
+    if(root) {
766
+        posRoot <- which(colnames(x) %in% rootNames)
767
+        if(!length(posRoot))
768
+            stop("No column with the root name")
769
+        if(length(posRoot) > 1)
770
+            stop("Ambiguous location of root")
771
+        x <- x[-posRoot, -posRoot]
772
+    }
773
+
774
+    if(typeof(x) != "integer")
775
+        warning("This is not an _integer_ adjacency matrix")
776
+    if( !all(x %in% c(0, 1) ))
777
+        stop("Values not in [0, 1]")
749 778
     if(!is.null(colnames(x))) {
750 779
         ## FIXME: this makes sense with numeric labels for columns, but
751 780
         ## not ow.
... ...
@@ -758,15 +787,16 @@ adjmat.to.restrictTable <- function(x) {
758 787
     
759 788
     num.deps <- colSums(x)
760 789
     max.n.deps <- max(num.deps)
761
-    rt <- matrix(-9, nrow = nrow(x),
790
+    rt <- matrix(-9L, nrow = nrow(x),
762 791
                  ncol = max.n.deps + 2)
763 792
     for(i in 1:ncol(x)) {
764 793
         if( num.deps[ i ])
765 794
             rt[i , 1:(2 + num.deps[ i ])] <- c(i, num.deps[i ],
766 795
                                                which(x[, i ] != 0))
767 796
         else
768
-            rt[i , 1:2] <- c(i , 0)
797
+            rt[i , 1:2] <- c(i , 0L)
769 798
     }
799
+    class(rt) <- "restrictionTable"
770 800
     return(rt)
771 801
 }
772 802
 
... ...
@@ -800,7 +830,7 @@ posetToGraph <- function(x, names,
800 830
     ## But we do not for now. Note we show lonely nodes, which oncotrees
801 831
     ## do not.  wait: when using root, we do not have "lonely nodes"
802 832
     ## anymore.  But that is irrelevant for metrics based on transitive
803
-    ## closure. Note for Diff, etc.
833
+    ## closure. Not for Diff, etc.
804 834
 
805 835
     ## In fact, this is all OK, but is confussing, because I can
806 836
     ## have two kinds of posets: ones that are full, with NAs, etc, if
... ...
@@ -808,9 +838,10 @@ posetToGraph <- function(x, names,
808 838
     ## using the later, the user needs to make sure that the last node is
809 839
     ## in the poset. This can be used as a shortcut trick, but in the docs
810 840
     ## I do not do it, as it is bad practice.
811
-    
841
+
842
+
812 843
     m <- length(names) 
813
-    m1 <- matrix(0, nrow = m, ncol = m)
844
+    m1 <- matrix(0L, nrow = m, ncol = m)
814 845
     colnames(m1) <- names
815 846
     rownames(m1) <- names
816 847
     if(is.null(dim(x)) ) {
... ...
@@ -829,16 +860,21 @@ posetToGraph <- function(x, names,
829 860
         }
830 861
         if(nrow(x) > 0) {
831 862
             if(addroot)
832
-                m1[x + 1] <- 1
863
+                m1[x + 1] <- 1L
833 864
             else
834
-                m1[x] <- 1
865
+                m1[x] <- 1L ## this will remove all entries with a 0
866
+                            ## index. So posets where explicit the dep. on
867
+                            ## 0.
835 868
         }
836 869
         if((length(names) > 1) & addroot) {
837 870
             no.ancestor <- which(apply(m1, 2, function(x) all(x == 0)))
838 871
             no.ancestor <- no.ancestor[-1]
839
-            m1[cbind(1, no.ancestor)] <- 1
872
+            m1[cbind(1, no.ancestor)] <- 1L
840 873
         } ## o.w. do nothing
841 874
     }
875
+    if(addroot)
876
+        m1[1, 1] <- 0L
877
+    
842 878
     if(type == "adjmat") return(m1)
843 879
     else if (type == "graphNEL") return(as(m1, "graphNEL"))
844 880
     ## does not show the labels
845 881
new file mode 100644
... ...
@@ -0,0 +1,33 @@
1
+citHeader("If you use OncoSimulR, please cite OncoSimulR itself. Note that a former version of OncoSimulR has been used in a large comparative study of methods to infer restrictions, published in BMC Bioinformatics; you might want to cite that too, if appropriate.")
2
+
3
+citEntry(entry="Manual",
4
+         author = "R Diaz-Uriarte",
5
+         title = "OncoSimulR: Simulation of cancer progresion with order restrictions.",
6
+         ## journal = "Bioinformatics",
7
+         year = "2015",
8
+         note = "R package version 1.3.1",
9
+         ## doi = "{10.1093/bioinformatics/btu099}",
10
+         ## volume = "30",
11
+         ## number = "12",
12
+         ## pages = "1759--1761",
13
+         textVersion = paste("R Diaz-Uriarte.",
14
+             "OncoSimulR: Simulation of cancer progression with order restrictions. 2015. R package version 1.3.1. ")
15
+)
16
+
17
+
18
+## citHeader("A former version of OncoSimulR has been used in this paper:")
19
+
20
+citEntry(entry="Article",
21
+         author = "R Diaz-Uriarte",
22
+         title = "Identifying restrictions in the order of accumulation of mutations during tumor progression: effects of passengers, evolutionary models, and sampling",
23
+         journal = "BMC Bioinformatics",
24
+         year = "2015",
25
+         doi = "{10.1186/s12859-015-0466-7}",
26
+         url = "{http://www.biomedcentral.com/1471-2105/16/41/abstract}",
27
+         volume = "16",
28
+         number = "41",
29
+         ## pages = "1759--1761",
30
+         textVersion = paste("R Diaz-Uriarte.",
31
+             "Identifying restrictions in the order of accumulation of mutations during tumor progression: effects of passengers, evolutionary models, and sampling",
32
+             "BMC Bioinformatics, 16(41), 2015.")
33
+)
... ...
@@ -1,3 +1,9 @@
1
+Changes in version 1.3.1 (2015-04-30)
2
+	- Added CITATION
3
+	- Changed defaults for sampleEvery and added endTimeEvery.
4
+	- Added some preliminary tests of poset transformations.
5
+	- (Subsumed all bumps in version in BioC)
6
+
1 7
 Changes in version 0.99.2 (2014-07-14)
2 8
 	- Consistently using indentation in .Rd files.
3 9
 
... ...
@@ -20,16 +20,24 @@
20 20
 \usage{
21 21
  oncoSimulIndiv(poset, model = "Bozic", numPassengers = 30, mu = 1e-6,
22 22
                 detectionSize = 1e8, detectionDrivers = 4,
23
-                sampleEvery = 1, initSize = 500, s = 0.1, sh = -1,
23
+                sampleEvery = ifelse(model \%in\% c("Bozic", "Exp"), 1,
24
+                             0.025),
25
+                initSize = 500, s = 0.1, sh = -1,
24 26
                 K = initSize/(exp(1) - 1), keepEvery = sampleEvery,
27
+                endTimeEvery = ifelse(model \%in\% c("Bozic", "Exp"), -9,
28
+                                               5 * sampleEvery),
25 29
                 finalTime = 0.25 * 25 * 365, onlyCancer = TRUE,
26 30
                 max.memory = 2000, max.wall.time = 200,
27 31
                 verbosity = 0)
28 32
 
29 33
  oncoSimulPop(Nindiv, poset, model = "Bozic", numPassengers = 30, mu = 1e-6,
30 34
                 detectionSize = 1e8, detectionDrivers = 4,
31
-                sampleEvery = 1, initSize = 500, s = 0.1, sh = -1,
35
+                sampleEvery = ifelse(model \%in\% c("Bozic", "Exp"), 1,
36
+                             0.025),
37
+                initSize = 500, s = 0.1, sh = -1,
32 38
                 K = initSize/(exp(1) - 1), keepEvery = sampleEvery,
39
+                endTimeEvery = ifelse(model \%in\% c("Bozic", "Exp"), -9,
40
+                                               5 * sampleEvery),
33 41
                 finalTime = 0.25 * 25 * 365, onlyCancer = TRUE,
34 42
                 max.memory = 2000, max.wall.time = 200,
35 43
                 verbosity = 0, mc.cores = detectCores())
... ...
@@ -121,6 +129,23 @@
121 129
   return objects are not huge.
122 130
 
123 131
 }
132
+
133
+\item{endTimeEvery}{
134
+  If endTimeEvery is > 0, even if conditions for finishing a simulation
135
+  (number of drivers or population size) are met at time \emph{t}, the
136
+  simulation will run at least until \emph{t + endTimeEvery} and
137
+  conditions will be checked again. Only if conditions for finishing a
138
+  simulation are still met, will the simulation end.
139
+
140
+  The reason for this parameter is to ensure that, say, a clone with a
141
+  certain number of drivers that would cause the simulation to end has
142
+  not just appeared but then gone extinct shortly after. Beware, though,
143
+  that in simulations with very fast growth, setting large endTimeEvery
144
+  can result in the simulations taking a long time to finish or hitting
145
+  the wall time limit.}
146
+
147
+
148
+
124 149
 \item{finalTime}{
125 150
   What is the maximum number of time units that the simulation can run.
126 151
 
... ...
@@ -256,7 +281,13 @@
256 281
   Academy of Sciences of the United States of America\/}, \bold{107},
257 282
   18545--18550.
258 283
   
259
-  Diaz-Uriarte, R. (2014). Inferring restrictions in the temporal order
284
+  Diaz-Uriarte, R. (2015). Identifying restrictions in the order of
285
+             accumulation of mutations during tumor progression: effects
286
+             of passengers, evolutionary models, and sampling, \emph{BMC
287
+             Bioinformatics\/},
288
+             \bold{16}(41). \url{http://www.biomedcentral.com/1471-2105/16/41/abstract}.
289
+
290
+  Inferring restrictions in the temporal order
260 291
   of mutations during tumor progression: effects of passenger mutations,
261 292
   evolutionary models, and
262 293
   sampling. \url{http://dx.doi.org/10.1101/005587}
... ...
@@ -295,7 +326,7 @@ summary(b1)
295 326
 
296 327
 plot(b1, addtot = TRUE)
297 328
 
298
-## McFarland; need to modify sampleEvery, but use a reasonable
329
+## McFarland; use a small sampleEvery, but also a reasonable
299 330
 ##   keepEvery.
300 331
 ## We also modify mutation rate to values similar to those in the
301 332
 ##   original paper.
... ...
@@ -63,9 +63,11 @@ samplePop(x, timeSample = "last", typeSample = "whole",
63 63
 }
64 64
 
65 65
 \references{
66
-  Diaz-Uriarte, R. (2014). Inferring restrictions in the temporal order
67
-  of mutations during tumor progression: effects of passenger mutations,
68
-  evolutionary models, and sampling. \url{http://dx.doi.org/10.1101/005587}
66
+  Diaz-Uriarte, R. (2015). Identifying restrictions in the order of
67
+             accumulation of mutations during tumor progression: effects
68
+             of passengers, evolutionary models, and sampling, \emph{BMC
69
+             Bioinformatics\/},
70
+             \bold{16}(41). \url{http://www.biomedcentral.com/1471-2105/16/41/abstract}.
69 71
 }
70 72
 
71 73
 \author{
... ...
@@ -706,7 +706,7 @@ inline void reshape_to_outNS(Rcpp::NumericMatrix& outNS,
706 706
   std::vector<unsigned long long>::const_iterator fend = uniqueGenotV.end();
707 707
 
708 708
   int column;
709
-
709
+  // FIXME keepTheseMany: here, fill up only when index_out[i] takes certain values
710 710
   for(size_t i = 0; i < genot_out_ul.size(); ++i) {
711 711
     column = std::distance(fbeg, lower_bound(fbeg, fend, genot_out_ul[i]) );
712 712
     outNS(index_out[i], column + 1) =  popSizes_out[i];
... ...
@@ -1275,6 +1275,9 @@ SEXP Algorithm5(SEXP restrictTable_,
1275 1275
   IntegerMatrix returnGenotypes(numGenes, uniqueGenotypes_vector.size());
1276 1276
   create_returnGenotypes(returnGenotypes, numGenes, uniqueGenotypes_vector);
1277 1277
 
1278
+  // FIXME: keepTheseMany: redo these calculations
1279
+  // correctly. keepTheseMany, not outNS_i + 1;
1280
+  
1278 1281
   int outNS_r, outNS_c, create_outNS;
1279 1282
   if( ( (uniqueGenotypes.size() + 1) *  (outNS_i + 1) ) > ( pow(2, 31) - 1 ) ) {
1280 1283
     Rcpp::Rcout << "\nWARNING: Return outNS object > 2^31 - 1. Not created.\n";
... ...
@@ -1289,7 +1292,7 @@ SEXP Algorithm5(SEXP restrictTable_,
1289 1292
     outNS_c = 1;
1290 1293
     create_outNS = 0;
1291 1294
   } else {
1292
-    outNS_r = outNS_i + 1;
1295
+    outNS_r = outNS_i + 1; //FIXME: here it is keepTheseMany
1293 1296
     outNS_c = uniqueGenotypes.size() + 1;
1294 1297
     create_outNS = 1;
1295 1298
   }
... ...
@@ -1298,6 +1301,8 @@ SEXP Algorithm5(SEXP restrictTable_,
1298 1301
     reshape_to_outNS(outNS, uniqueGenotypes_vector, genot_out_ullong, 
1299 1302
 		     popSizes_out, 
1300 1303
 		     index_out, time_out);
1304
+
1305
+    //FIXME: keepTheseMany need to prune the uniqueGenotypes
1301 1306
     
1302 1307
   } else {
1303 1308
     outNS(0, 0) = -99;
1304 1309
new file mode 100644
... ...
@@ -0,0 +1,4 @@
1
+library(testthat)
2
+# library(OncoSimulR)
3
+
4
+test_check("OncoSimulR")
0 5
new file mode 100644
... ...
@@ -0,0 +1,164 @@
1
+## A preliminary set of tests. More in the current unreleased code.
2
+## library(OncoSimulR); library(testthat)
3
+
4
+
5
+
6
+
7
+
8
+## This code is in devel
9
+## m0 <- matrix(0L, ncol = 4, nrow = 4)
10
+## colnames(m0) <- rownames(m0) <- c(0, 2, 3, 5)
11
+## m0[1, 4] <- 1L
12
+
13
+## test_that("adjmat illegal even in this conversion",
14
+##           expect_error(OncoSimulR:::OTtoPoset(m0)))
15
+
16
+
17
+## m0 <- matrix(0L, ncol = 4, nrow = 4)
18
+## colnames(m0) <- rownames(m0) <- c(0, 2, 3, 5)
19
+## m0[1,  ] <- 1L
20
+## test_that("does not conform to having root be called Root",
21
+##           expect_error(OncoSimulR:::OTtoPoset(m0)))
22
+
23
+## m0 <- matrix(0L, ncol = 4, nrow = 4)
24
+## colnames(m0) <- rownames(m0) <- c("Root", 2, 3, 5)
25
+## m0[1, ] <- 1L
26
+## test_that("but an edge to Root",
27
+##           expect_error(OncoSimulR:::OTtoPoset(m0)))
28
+
29
+## m0 <- matrix(0L, ncol = 4, nrow = 4)
30
+## colnames(m0) <- rownames(m0) <- c("Root", 2, 3, 5)
31
+## m0[1, 2:4] <- 1L
32
+## test_that("OT to the smallest Poset",
33
+##           expect_equal(matrix(nrow=0, ncol=2), OncoSimulR:::OTtoPoset(m0)))
34
+
35
+## new devel code
36
+## test_that("adjmat illegal because empty nodes",
37
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m0, root = TRUE)))
38
+
39
+## test_that("adjmat illegal because empty nodes, 2",
40
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m0, root = FALSE)))
41
+
42
+## m1 <- matrix(0L, ncol = 4, nrow = 4)
43
+## colnames(m1) <- rownames(m1) <- c(0, 2, 3, 5)
44
+## m1[, 4] <- 1L
45
+
46
+## test_that("adjmat illegal because lack of incoming",
47
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1, root = TRUE)))
48
+## test_that("adjmat illegal because lack of incoming, 2",
49
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1, root = FALSE)))
50
+## test_that("adjmat illegal because non-int column names",
51
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1[-1, -1], root = FALSE)))
52
+## test_that("adjmat illegal because of no root",
53
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1[-1, -1], root = TRUE)))
54
+
55
+## m2 <- matrix(0L, ncol = 4, nrow = 4)
56
+## colnames(m2) <- rownames(m2) <- c(0:3)
57
+## m2[, 4] <- 1L; m2[1, 3] <- 1L
58
+
59
+## test_that("adjmat illegal because lack of incoming",
60
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m2, root = TRUE)))
61
+## test_that("adjmat illegal because lack of incoming, 2",
62
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m2, root = FALSE)))
63
+
64
+
65
+m3 <- matrix(0L, ncol = 4, nrow = 4)
66
+colnames(m3) <- rownames(m3) <- c(0:3)
67
+m3[1, 2:4] <- 1L
68
+
69
+## test_that("inconsistency in root options",
70
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m3, root = FALSE)))
71
+
72
+rt3 <- cbind(1:3, 0L); class(rt3) <- "restrictionTable"
73
+test_that("simple correct adjmat -> rT", {
74
+    expect_equal(rt3, OncoSimulR:::adjmat.to.restrictTable(m3, root = TRUE))})
75
+
76
+
77
+p3 <- cbind(0L, 3L)
78
+test_that("simple correct poset -> graph", {
79
+    expect_equal(m3,
80
+                 OncoSimulR:::posetToGraph(p3, names = 0:3, addroot = TRUE, type = "adjmat"))})
81
+
82
+
83
+
84
+m3 <- matrix(0L, ncol = 4, nrow = 4)
85
+colnames(m3) <- rownames(m3) <- c(0:3)
86
+m3[1, ] <- 1L
87
+## test_that("adjmat illegal because incoming to Root",
88
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m3, root = TRUE)))
89
+## test_that("adjmat illegal because incoming to Root",
90
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m3, root = FALSE)))
91
+
92
+
93
+
94
+
95
+p5 <- cbind(c(0L), c(5L))
96
+m5 <- matrix(0L, ncol = 6, nrow = 6); colnames(m5) <- rownames(m5) <- 0:5
97
+m5[1, 2:6] <- 1L
98
+test_that("simple correct poset -> graph, 5 nodes, root", {
99
+    expect_equal(m5,
100
+                 OncoSimulR:::posetToGraph(p5, names = 0:5,
101
+                                           addroot = TRUE, type = "adjmat"))})
102
+test_that("simple correct poset -> graph, 5 nodes, no root", {
103
+    expect_equal(m5[-1, -1],
104
+                 OncoSimulR:::posetToGraph(p5, names = 1:5,
105
+                                           addroot = FALSE, type = "adjmat"))})
106
+
107
+
108
+test_that("to rT from poset, through adjmat with and w.o. root",
109
+          {
110
+              expect_equal(
111
+                  OncoSimulR:::adjmat.to.restrictTable(
112
+                      OncoSimulR:::posetToGraph(p5, names = 1:5, addroot = FALSE, type = "adjmat"),
113
+                      root = FALSE),
114
+                  OncoSimulR:::adjmat.to.restrictTable(
115
+                      OncoSimulR:::posetToGraph(p5, names = 0:5, addroot = TRUE, type = "adjmat"),
116
+                      root = TRUE))
117
+          })
118
+
119
+
120
+
121
+
122
+## can convert if OT, not o.w.
123
+## m1 <- structure(c(0L, 0L, 0L, 1L, 0L, 0L, 0L, 1L, 0L), .Dim = c(3L, 
124
+## 3L), .Dimnames = list(c("Root", "2", "4"), c("Root", "2", "4"
125
+##                                             )))
126
+## test_that("from adjmat to rT, if OT", {
127
+##           expect_identical(cbind(2L, 4L), OncoSimulR:::OTtoPoset(m1))})
128
+## test_that(".. but fails if not considered OT", {
129
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1, root = TRUE))})
130
+## test_that(".. but fails if not considered OT", {
131
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1, root = FALSE))})
132
+
133
+
134
+
135
+## m1b <- structure(c(0L, 0L, 0L, 0L, 0L, 1L, 1L, 0L, 0L), .Dim = c(3L, 
136
+## 3L), .Dimnames = list(c("Root", "2", "4"), c("Root", "2", "4"
137
+## )))
138
+## test_that("Change pos of elements: from adjmat to rT, if OT", {
139
+##           expect_identical(cbind(4L, 2L), OncoSimulR:::OTtoPoset(m1b))})
140
+## test_that(".. but fails if not considered OT", {
141
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1b, root = TRUE))})
142
+## test_that(".. but fails if not considered OT", {
143
+##           expect_error(OncoSimulR:::adjmat.to.restrictTable(m1b, root = FALSE))})
144
+
145
+
146
+
147
+## posets with some nodes not explicit
148
+pm1 <- structure(c(0L, 2L, 2L, 4L), .Dim = c(2L, 2L))
149
+pm1.nr <- structure(c(2L, 4L), .Dim = 1:2)
150
+test_that("poset to rT, with some nodes missing",{
151
+          expect_identical(OncoSimulR:::poset.to.restrictTable(pm1.nr),
152
+                           OncoSimulR:::poset.to.restrictTable(pm1))})
153
+
154
+
155
+pm1b <- structure(c(4L, 0L, 2L, 4L), .Dim = c(2L, 2L))
156
+pm1b.nr <- structure(c(4L, 2L), .Dim = 1:2)
157
+test_that("poset to rT, with some nodes missing, nodes exchanged",{
158
+          expect_identical(OncoSimulR:::poset.to.restrictTable(pm1b.nr),
159
+                           OncoSimulR:::poset.to.restrictTable(pm1b))})
160
+
161
+
162
+
163
+
164
+
... ...
@@ -1,15 +1,15 @@
1 1
 \usepackage[%
2
-		shash={8c8c022},
3
-		lhash={8c8c02214b27f6421fc91523948e112019728983},
4
-		authname={ramon diaz-uriarte (at Bufo)},
2
+		shash={c523b93},
3
+		lhash={c523b93dcddd79d6547631d4ad7f6a4677187871},
4
+		authname={Ramon Diaz-Uriarte (at Coleonyx)},
5 5
 		authemail={rdiaz02@gmail.com},
6
-		authsdate={2014-07-14},
7
-		authidate={2014-07-14 19:05:47 +0200},
8
-		authudate={1405357547},
9
-		commname={ramon diaz-uriarte (at Bufo)},
6
+		authsdate={2015-04-30},
7
+		authidate={2015-04-30 14:13:55 +0200},
8
+		authudate={1430396035},
9
+		commname={Ramon Diaz-Uriarte (at Coleonyx)},
10 10
 		commemail={rdiaz02@gmail.com},
11
-		commsdate={2014-07-14},
12
-		commidate={2014-07-14 19:05:47 +0200},
13
-		commudate={1405357547},
11
+		commsdate={2015-04-30},
12
+		commidate={2015-04-30 14:13:55 +0200},
13
+		commudate={1430396035},
14 14
 		refnames={ (HEAD, master)}
15 15
 	]{gitsetinfo}
16 16
\ No newline at end of file