Browse code

v.2.3.8

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

Ramon Diaz-Uriarte authored on 08/07/2016 11:17:18
Showing 7 changed files

... ...
@@ -1,8 +1,8 @@
1 1
 Package: OncoSimulR
2 2
 Type: Package
3 3
 Title: Forward Genetic Simulation of Cancer Progresion with Epistasis 
4
-Version: 2.3.7
5
-Date: 2016-07-05
4
+Version: 2.3.8
5
+Date: 2016-07-08
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"))
... ...
@@ -1563,7 +1563,7 @@ nr_oncoSimul.internal <- function(rFE,
1563 1563
         ## muEF <- emptyFitnessEffects()
1564 1564
     }
1565 1565
 
1566
-    dpr <- detectionProbCheckParse(detectionProb, initSize)
1566
+    dpr <- detectionProbCheckParse(detectionProb, initSize, verbosity)
1567 1567
     ## if( !is.null(cPDetect) && (sum(!is.null(p2), !is.null(n2)) >= 1 ))
1568 1568
     ##     stop("Specify only cPDetect xor both of p2 and n2")
1569 1569
     ## if( (is.null(p2) + is.null(n2)) == 1 )
... ...
@@ -1747,10 +1747,10 @@ matchGeneIDs <- function(x, refFE) {
1747 1747
 }
1748 1748
 
1749 1749
     
1750
-detectionProbCheckParse <- function(x, initSize) {
1750
+detectionProbCheckParse <- function(x, initSize, verbosity) {
1751 1751
     default_p2 <- 0.1
1752 1752
     default_n2 <- 2 * initSize
1753
-    default_PDBaseline <- 1.1 * initSize
1753
+    default_PDBaseline <- 1.2 * initSize
1754 1754
     default_checkSizePEvery <- 20
1755 1755
     ## No default cPDetect. That is done from p2 and n2 in C++.
1756 1756
     
... ...
@@ -1787,12 +1787,14 @@ detectionProbCheckParse <- function(x, initSize) {
1787 1787
 
1788 1788
     if(is.na(x["PDBaseline"])) {
1789 1789
         x["PDBaseline"] <- default_PDBaseline
1790
-        cat("\n  PDBaseline set to default value of ", default_PDBaseline, "\n")
1790
+        if(verbosity > -1)
1791
+            message("\n  PDBaseline set to default value of ", default_PDBaseline, "\n")
1791 1792
         }
1792 1793
     if(is.na(x["checkSizePEvery"])) {
1793 1794
         x["checkSizePEvery"] <- default_checkSizePEvery
1794
-        cat("\n  checkSizePEvery set to default value of ",
1795
-            default_checkSizePEvery, "\n")
1795
+        if(verbosity > -1)
1796
+            message("\n  checkSizePEvery set to default value of ",
1797
+                default_checkSizePEvery, "\n")
1796 1798
         }
1797 1799
 
1798 1800
     ## If we get here, we checked consistency of whether cPDetect or p2/n2.
... ...
@@ -1803,8 +1805,9 @@ detectionProbCheckParse <- function(x, initSize) {
1803 1805
             if(!is.na(x["n2"])) stop("Eh? no p2 but n2? Bug")
1804 1806
             x["n2"] <- default_n2
1805 1807
             x["p2"] <- default_p2
1806
-            cat("\n  n2, p2 set to default values of ",
1807
-                default_n2, ", ", default_p2, "\n")
1808
+            if(verbosity > -1)
1809
+                message("\n  n2, p2 set to default values of ",
1810
+                    default_n2, ", ", default_p2, "\n")
1808 1811
         }
1809 1812
     }
1810 1813
     
... ...
@@ -1823,7 +1826,8 @@ detectionProbCheckParse <- function(x, initSize) {
1823 1826
         if(is.na(x["cPDetect"])) stop("eh? you found a bug")## paranoia
1824 1827
         x["n2"] <- -9
1825 1828
         x["p2"] <- -9
1826
-        cat("\n Using user-specified cPDetect as n2, p2 not given.\n")
1829
+        if(verbosity > -1)
1830
+            message("\n Using user-specified cPDetect as n2, p2 not given.\n")
1827 1831
     }
1828 1832
     return(x)
1829 1833
 }
... ...
@@ -1,3 +1,6 @@
1
+Changes in version 2.3.8 (2017-07-08):
2
+	- PDBasline default is now 1.2.
3
+	
1 4
 Changes in version 2.3.7 (2016-07-05):
2 5
 	- Unused C++ code reorganiz.
3 6
 	- Added tests
... ...
@@ -224,7 +224,7 @@ simulations.
224 224
 
225 225
     \item{PDBaseline}{Baseline size subtracted to total population size
226 226
     to compute the probability of detection. If not given explicitly,
227
-    the default is \code{1.1*initSize}.
227
+    the default is \code{1.2 * initSize}.
228 228
     }
229 229
 
230 230
     \item{p2}{The probability of detection at population size
... ...
@@ -501,10 +501,10 @@ of \code{sampleEvery} that is larger than or equal to \code{keepEvery}.
501 501
 
502 502
 
503 503
 
504
-\item{verbosity}{
505
-  If 0, run as silently as possible. Otherwise, increasing values of
506
-  verbosity provide progressively more information about intermediate
507
-  steps, possible numerical notes/warnings from the C++ code, etc.
504
+\item{verbosity}{ If 0, run silently. Iincreasing values of verbosity
505
+  provide progressively more information about intermediate steps,
506
+  possible numerical notes/warnings from the C++ code, etc. Values less
507
+  than 0 supress some default notes: use with care.
508 508
 
509 509
 }
510 510
 
... ...
@@ -1,4 +1,7 @@
1
-
1
+## Some tests below might only work on Linux because of compiler
2
+## differences, because the rng is done in C++, etc.
3
+## Note that the difference is in whether a certain code
4
+## is exercised. The runs should work in all platforms, though.
2 5
 
3 6
 test_that("exercise no positions left for mutation, updating in null mut, old format", {
4 7
     ## Do not do the capture output from oncoSimulPop,
... ...
@@ -17,9 +20,11 @@ test_that("exercise no positions left for mutation, updating in null mut, old fo
17 20
                               extraTime = 3.17,
18 21
                               onlyCancer = FALSE,
19 22
                               seed = NULL)
20
-        })
21
-    expect_true(any(grepl("mutation = 0", st)))
22
-    expect_true(any(grepl("updating in null mutation", st)))
23
+    })
24
+    if(Sys.info()["sysname"] == "Linux") {
25
+        expect_true(any(grepl("mutation = 0", st)))
26
+        expect_true(any(grepl("updating in null mutation", st)))
27
+    }
23 28
     expect_output(print(pp1),
24 29
                    "Individual OncoSimul trajectory", fixed = TRUE)
25 30
 })
... ...
@@ -40,7 +45,9 @@ test_that("exercise mu > 1, old format", {
40 45
                           finalTime = 2000,
41 46
                           onlyCancer = FALSE,
42 47
                           seed = NULL))
48
+    
43 49
     expect_true(any(grepl("mutation > 1", st)))
50
+    
44 51
     expect_output(print(pp1),
45 52
                   "Individual OncoSimul trajectory", fixed = TRUE)
46 53
 })
... ...
@@ -122,8 +129,10 @@ test_that("exercise no positions left for mutation, updating in null mut, new fo
122 129
                           verbosity = 1))
123 130
     expect_output(print(pp1),
124 131
                   "Individual OncoSimul", fixed = TRUE)
125
-    expect_true(any(grepl("mutation = 0", st)))
126
-    expect_true(any(grepl("updating in null mutation", st)))
132
+    if(Sys.info()["sysname"] == "Linux") {
133
+        expect_true(any(grepl("mutation = 0", st)))
134
+        expect_true(any(grepl("updating in null mutation", st)))
135
+    }
127 136
 })
128 137
 
129 138
 
... ...
@@ -377,7 +377,7 @@ test_that("Increasing n2 increases time" , {
377 377
     gi <- rep(0.0,  10)
378 378
     names(gi) <- letters[1:10]
379 379
     oi <- allFitnessEffects(noIntGenes = gi)
380
-    n <- 20
380
+    n <- 30
381 381
     max.tries <- 4  
382 382
     for(tries in 1:max.tries) {
383 383
         sa <- oncoSimulPop(n,
... ...
@@ -385,7 +385,7 @@ test_that("Increasing n2 increases time" , {
385 385
                            model = "McFL",
386 386
                            initSize = 2000,
387 387
                            keepEvery = NA,
388
-                           detectionProb = c(p2 = .1, n2 = 5000, checkSizePEvery = 5,PDBaseline = 1100, cPDetect = NA),
388
+                           detectionProb = c(p2 = .15, n2 = 7000, checkSizePEvery = 5,PDBaseline = 1100, cPDetect = NA),
389 389
                            finalTime = NA, detectionSize = NA,
390 390
                            onlyCancer = FALSE,
391 391
                            detectionDrivers = NA, mc.cores = 2)
... ...
@@ -394,12 +394,13 @@ test_that("Increasing n2 increases time" , {
394 394
                            model = "McFL",
395 395
                            initSize = 2000,
396 396
                            keepEvery = NA,
397
-                           detectionProb = c(p2 = .1, n2 = 2001, checkSizePEvery = 5,PDBaseline = 1100, cPDetect = NA),
397
+                           detectionProb = c(p2 = .15, n2 = 2001, checkSizePEvery = 5,PDBaseline = 1100, cPDetect = NA),
398 398
                            finalTime = NA, detectionSize = NA,
399 399
                            onlyCancer = FALSE,
400 400
                            detectionDrivers = NA, mc.cores = 2)
401 401
         (ta <- unlist(lapply(sa, function(x) x$FinalTime)))
402
-        (tb <- unlist(lapply(sb, function(x) x$FinalTime)))         
402
+        (tb <- unlist(lapply(sb, function(x) x$FinalTime)))
403
+        print(suppressWarnings(wilcox.test(ta, tb, alternative = "greater")$p.value))
403 404
         T1 <- suppressWarnings(wilcox.test(ta, tb, alternative = "greater")$p.value < p.value.threshold)
404 405
         if(T1) break;
405 406
     }
... ...
@@ -534,7 +535,6 @@ test_that("Exercise the default option and other substitutions/defaults" , {
534 535
         detectionDrivers = NA)),
535 536
         "Individual OncoSimul trajectory",
536 537
         fixed = TRUE)
537
-    
538 538
     expect_output(print(oncoSimulIndiv(
539 539
         oi,
540 540
         model = "Exp",
... ...
@@ -547,7 +547,6 @@ test_that("Exercise the default option and other substitutions/defaults" , {
547 547
         detectionDrivers = NA)),
548 548
         "Individual OncoSimul trajectory",
549 549
         fixed = TRUE)
550
-
551 550
     expect_output(print(oncoSimulIndiv(
552 551
         oi,
553 552
         model = "Exp",
... ...
@@ -560,7 +559,6 @@ test_that("Exercise the default option and other substitutions/defaults" , {
560 559
         detectionDrivers = NA)),
561 560
         "Individual OncoSimul trajectory",
562 561
         fixed = TRUE)
563
-
564 562
     expect_output(print(oncoSimulIndiv(
565 563
         oi,
566 564
         model = "Exp",
... ...
@@ -573,7 +571,6 @@ test_that("Exercise the default option and other substitutions/defaults" , {
573 571
         detectionDrivers = NA)),
574 572
         "Individual OncoSimul trajectory",
575 573
         fixed = TRUE)
576
-
577 574
     expect_output(print(oncoSimulIndiv(
578 575
         oi,
579 576
         model = "Exp",
... ...
@@ -586,8 +583,50 @@ test_that("Exercise the default option and other substitutions/defaults" , {
586 583
         detectionDrivers = NA)),
587 584
         "Individual OncoSimul trajectory",
588 585
         fixed = TRUE)
589
-
590
-
586
+    expect_output(print(oncoSimulIndiv(
587
+        oi,
588
+        model = "Exp",
589
+        initSize = 2000, verbosity = -3,
590
+        keepEvery = NA,
591
+        detectionProb = c(cPDetect = 0.001),
592
+        finalTime = NA, detectionSize = NA,
593
+        onlyCancer = TRUE,
594
+        detectionDrivers = NA)),
595
+        "Individual OncoSimul trajectory",
596
+        fixed = TRUE)
597
+    expect_output(print(oncoSimulIndiv(
598
+        oi,
599
+        model = "Exp",
600
+        initSize = 2000, verbosity = -3,
601
+        keepEvery = NA,
602
+        detectionProb = c(p2 = .9, n2 = 3000),
603
+        finalTime = NA, detectionSize = NA,
604
+        onlyCancer = TRUE,
605
+        detectionDrivers = NA)),
606
+        "Individual OncoSimul trajectory",
607
+        fixed = TRUE)
608
+    expect_output(print(oncoSimulIndiv(
609
+        oi,
610
+        model = "Exp",
611
+        initSize = 2000, verbosity = -3,
612
+        keepEvery = NA,
613
+        detectionProb = c(PDBaseline = 2002),
614
+        finalTime = NA, detectionSize = NA,
615
+        onlyCancer = TRUE,
616
+        detectionDrivers = NA)),
617
+        "Individual OncoSimul trajectory",
618
+        fixed = TRUE)
619
+    expect_output(print(oncoSimulIndiv(
620
+        oi,
621
+        model = "Exp",
622
+        initSize = 2000, verbosity = -3,
623
+        keepEvery = NA,
624
+        detectionProb = c(checkSizePEvery = 31),
625
+        finalTime = NA, detectionSize = NA,
626
+        onlyCancer = TRUE,
627
+        detectionDrivers = NA)),
628
+        "Individual OncoSimul trajectory",
629
+        fixed = TRUE)
591 630
 })
592 631
 
593 632
 
... ...
@@ -1,15 +1,15 @@
1 1
 \usepackage[%
2
-		shash={2e4cc36},
3
-		lhash={2e4cc367294be5263e8e2fa2803e7700395684d9},
4
-		authname={Ramon Diaz-Uriarte (at Coleonyx)},
2
+		shash={23758f4},
3
+		lhash={23758f41c637253bd524665045d19c5b159d884c},
4
+		authname={Ramon Diaz-Uriarte (at Lacerta)},
5 5
 		authemail={rdiaz02@gmail.com},
6
-		authsdate={2016-07-05},
7
-		authidate={2016-07-05 13:18:34 +0200},
8
-		authudate={1467717514},
9
-		commname={Ramon Diaz-Uriarte (at Coleonyx)},
6
+		authsdate={2016-07-07},
7
+		authidate={2016-07-07 01:50:25 +0200},
8
+		authudate={1467849025},
9
+		commname={Ramon Diaz-Uriarte (at Lacerta)},
10 10
 		commemail={rdiaz02@gmail.com},
11
-		commsdate={2016-07-05},
12
-		commidate={2016-07-05 13:18:34 +0200},
13
-		commudate={1467717514},
11
+		commsdate={2016-07-07},
12
+		commidate={2016-07-07 01:50:25 +0200},
13
+		commudate={1467849025},
14 14
 		refnames={ (HEAD, origin/master, origin/HEAD)}
15 15
 	]{gitsetinfo}
16 16
\ No newline at end of file