Browse code

no longer refs to older installer and robustify one test

ramon diaz-uriarte (at Phelsuma) authored on 16/07/2018 20:27:32
Showing 6 changed files

... ...
@@ -2,7 +2,7 @@ Package: OncoSimulR
2 2
 Type: Package
3 3
 Title: Forward Genetic Simulation of Cancer Progression with Epistasis 
4 4
 Version: 2.11.0
5
-Date: 2018-04-19
5
+Date: 2018-07-16
6 6
 Authors@R: c(person("Ramon", "Diaz-Uriarte", role = c("aut", "cre"),
7 7
 		     email = "rdiaz02@gmail.com"),
8 8
 	      person("Mark", "Taylor", role = "ctb", email = "ningkiling@gmail.com"))
... ...
@@ -1616,6 +1616,7 @@ plotClonePhylog <- function(x, N = 1, t = "last",
1616 1616
 
1617 1617
 closest_time <- function(x, size) {
1618 1618
     ## Find the first time when a given size is reached
1619
+    ## But these are not times, but the position in pops.by.time. Bad naming.
1619 1620
     sizes <- rowSums(x$pops.by.time[, -1, drop = FALSE])
1620 1621
     candidates <- which(sizes >= size)
1621 1622
     if(length(candidates) == 0) {
... ...
@@ -1630,6 +1631,7 @@ closest_time <- function(x, size) {
1630 1631
 
1631 1632
 get.the.time.for.sample <- function(tmp, timeSample, popSizeSample) {
1632 1633
     if( !is.null(popSizeSample) && (popSizeSample >= 0) )  {
1634
+        ## should be "closest_index" and "the.index"
1633 1635
         the.time <- closest_time(tmp, popSizeSample)
1634 1636
     } else if(timeSample == "last") {
1635 1637
         if(tmp$TotalPopSize == 0) {
... ...
@@ -17,7 +17,8 @@
17 17
 ##     plot.genotype_fitness_matrix <- plotFitnessLandscape 
18 18
 
19 19
 ## FIXME: show only accessible paths? 
20
-
20
+## FIXME: when show_labels = FALSE we still show the boxes
21
+##        and some of the labels.!!!
21 22
 ## FIXME: if using only_accessible, maybe we
22 23
 ## can try to use fast_peaks, and use the slower
23 24
 ## approach as fallback (if identical fitness)
... ...
@@ -1,3 +1,6 @@
1
+Changes in version 2.11.1:
2
+	- robustify test.fixation.R, Local max, tolerance
3
+	
1 4
 Changes in version 2.10.0 (for BioC 3.7):
2 5
 	- probDetect mechanism changed. This could be a BREAKING CHANGE.
3 6
 	  The expression divides by the baseline. For fixed initSize, this
... ...
@@ -864,6 +864,14 @@ void addToPhylog(PhylogName& phylog,
864 864
 // Use a map for LOD, and overwrite the parent:
865 865
 // we only add when the size of the child is 0
866 866
 // The key of the map is the child.
867
+
868
+// FIXME: we might want to store the time? Not really clear even if that
869
+// makes sense. We would be storing the last time the child (which had 0
870
+// size at that time) arose from the parent.
871
+// A simple kludge is to have two maps, the second with child and time.
872
+// Or do it properly as map<int, genot_time_struct>
873
+// genot_time_struct {string parent; double time}
874
+
867 875
 void addToLOD(std::map<std::string, std::string>& lod,
868 876
 	      const Genotype& parent,
869 877
 	      const Genotype& child,
... ...
@@ -441,7 +441,7 @@ date()
441 441
 
442 442
 
443 443
 test_that("Local max: not stopping, stopping, and tolerance", {
444
-        initS <- 2000
444
+    initS <- 2000
445 445
     rl1 <- matrix(0, ncol = 6, nrow = 9)
446 446
     colnames(rl1) <- c(LETTERS[1:5], "Fitness")
447 447
     rl1[1, 6] <- 1
... ...
@@ -512,7 +512,10 @@ test_that("Local max: not stopping, stopping, and tolerance", {
512 512
     sgsp2 <- sampledGenotypes(sp2)
513 513
     expect_true(all(sgsp2$Genotype %in% local_max_g))
514 514
     ## tolerance
515
-    r3 <- oncoSimulPop(100,
515
+    ## yes, this can occasionally fail, because all are in
516
+    ## the list of local_max_g
517
+        
518
+    r3 <- oncoSimulPop(200,
516 519
                        fp = fr1,
517 520
                        model = "McFL",
518 521
                        initSize = initS,
... ...
@@ -521,7 +524,7 @@ test_that("Local max: not stopping, stopping, and tolerance", {
521 524
                        sampleEvery = .03,
522 525
                        keepEvery = 1, 
523 526
                        finalTime = 50000,
524
-                       fixation = c(local_max, fixation_tolerance = 0.1),
527
+                       fixation = c(local_max, fixation_tolerance = 0.5),
525 528
                        detectionDrivers = NA,
526 529
                        detectionProb = NA,
527 530
                        onlyCancer = TRUE,
... ...
@@ -535,6 +538,8 @@ test_that("Local max: not stopping, stopping, and tolerance", {
535 538
     sp3 <- samplePop(r3, "last", "singleCell")
536 539
     sgsp3 <- sampledGenotypes(sp3)
537 540
     expect_true(!all(sgsp3$Genotype %in% local_max_g))
541
+    ## sum(sgsp3$Genotype %in% local_max_g)
542
+    ## sum(!(sgsp3$Genotype %in% local_max_g))
538 543
 })
539 544
 
540 545