git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@115959 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -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.1.2 |
|
5 |
-Date: 2016-03-27 |
|
4 |
+Version: 2.1.3 |
|
5 |
+Date: 2016-04-07 |
|
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")) |
... | ... |
@@ -500,10 +500,23 @@ allFitnessEffects <- function(rT = NULL, |
500 | 500 |
} |
501 | 501 |
|
502 | 502 |
if(!is.null(noIntGenes)) { |
503 |
+ if(inherits(noIntGenes, "character")) { |
|
504 |
+ wm <- paste("noIntGenes is a character vector.", |
|
505 |
+ "This is probably not what you want, and will", |
|
506 |
+ "likely result in an error downstream.", |
|
507 |
+ "You can get messages like", |
|
508 |
+ " 'not compatible with requested type', and others.", |
|
509 |
+ "We are stopping.") |
|
510 |
+ stop(wm) |
|
511 |
+ } |
|
512 |
+ |
|
503 | 513 |
mg <- max(geneModule[, "GeneNumID"]) |
504 | 514 |
gnum <- seq_along(noIntGenes) + mg |
505 | 515 |
if(!is.null(names(noIntGenes))) { |
506 | 516 |
ng <- names(noIntGenes) |
517 |
+ if( grepl(",", ng, fixed = TRUE) || grepl(">", ng, fixed = TRUE) |
|
518 |
+ || grepl(":", ng, fixed = TRUE)) |
|
519 |
+ stop("The name of some noIntGenes contain a ',' or a '>' or a ':'") |
|
507 | 520 |
if(any(ng %in% geneModule[, "Gene"] )) |
508 | 521 |
stop("A gene in noIntGenes also present in the other terms") |
509 | 522 |
} else { |
... | ... |
@@ -527,7 +540,18 @@ allFitnessEffects <- function(rT = NULL, |
527 | 540 |
} |
528 | 541 |
|
529 | 542 |
if(!is.null(drvNames)) { |
530 |
- drv <- getGeneIDNum(geneModule, geneNoInt, drvNames) |
|
543 |
+ drv <- unique(getGeneIDNum(geneModule, geneNoInt, drvNames)) |
|
544 |
+ ## drivers should never be in the geneNoInt; Why!!!??? |
|
545 |
+ ## Catch the problem. This is an overkill, |
|
546 |
+ ## so since we catch the issue, we could leave the geneNoInt. But |
|
547 |
+ ## that should not be there in this call. |
|
548 |
+ ## if(any(drvNames %in% geneNoInt$Gene)) { |
|
549 |
+ ## stop(paste("At least one gene in drvNames is a geneNoInt gene.", |
|
550 |
+ ## "That is not allowed.", |
|
551 |
+ ## "If that gene is a driver, pass it as gene in the epistasis", |
|
552 |
+ ## "component.")) |
|
553 |
+ ## } |
|
554 |
+ ## drv <- getGeneIDNum(geneModule, NULL, drvNames) |
|
531 | 555 |
} else { |
532 | 556 |
drv <- geneModule$GeneNumID[-1] |
533 | 557 |
} |
... | ... |
@@ -1,7 +1,20 @@ |
1 |
+Changes in version 2.2.0 (for BioC 3.3): |
|
2 |
+ - Plots of genotypes. |
|
3 |
+ - Stacked area and stream plots (code from Marc Taylor). |
|
4 |
+ - Example of modules and no epistasis. |
|
5 |
+ - Removed requirement of Root in geneToModule. |
|
6 |
+ - More tests (and reorganized them) |
|
7 |
+ - Miscell. improvements and typos fixed in documentation and vignette. |
|
8 |
+ - Added mutationPropGrowth as argument. |
|
9 |
+ - Some minor bug fixes and additional checks for user errors. |
|
10 |
+ |
|
11 |
+Changes in version 2.1.3 (2016-04-04): |
|
12 |
+ - Fixed sporadic bug in countDrivers |
|
13 |
+ |
|
1 | 14 |
Changes in version 2.1.2 (2016-03-27): |
2 | 15 |
- Arguments to BNB_Algo5 explicit. |
3 | 16 |
- Example of modules and no epistasis. |
4 |
- - Remove requirement of Root in geneToModule. |
|
17 |
+ - Removed requirement of Root in geneToModule. |
|
5 | 18 |
- More tests (and reorganized them) |
6 | 19 |
- Miscell. improvements in documentation and vignette. |
7 | 20 |
|
... | ... |
@@ -71,11 +71,14 @@ allFitnessEffects(rT = NULL, epistasis = NULL, orderEffects = NULL, |
71 | 71 |
\item{noIntGenes}{ |
72 | 72 |
A numeric vector (optionally named) with the fitness coefficients of genes |
73 | 73 |
(only genes, not modules) that show no interactions. These genes |
74 |
- cannot be part of modules. But you can specify modules that have |
|
75 |
- no epistatic interactions. See examples and vignette. |
|
76 |
- } |
|
77 |
- |
|
78 |
- \item{geneToModule}{ |
|
74 |
+ cannot be part of modules. But you can specify modules that have |
|
75 |
+ no epistatic interactions. See examples and vignette. |
|
76 |
+ |
|
77 |
+ Of course, avoid using potentially confusing characters in the |
|
78 |
+ names. In particular, "," and ">" are not allowed as gene names. |
|
79 |
+} |
|
80 |
+ |
|
81 |
+\item{geneToModule}{ |
|
79 | 82 |
|
80 | 83 |
A named character vector that allows to match genes and modules. The |
81 | 84 |
names are the modules, and each of the values is a character vector |
... | ... |
@@ -159,11 +162,21 @@ allFitnessEffects(rT = NULL, epistasis = NULL, orderEffects = NULL, |
159 | 162 |
|
160 | 163 |
} |
161 | 164 |
|
162 |
-\note{Please, note that the meaning of the fitness effects in the |
|
165 |
+\note{ |
|
166 |
+ Please, note that the meaning of the fitness effects in the |
|
163 | 167 |
McFarland model is not the same as in the original paper; the fitness |
164 | 168 |
coefficients are transformed to allow for a simpler fitness function |
165 | 169 |
as a product of terms. This differs with respect to v.1. See the |
166 |
- vignette for details.} |
|
170 |
+ vignette for details. |
|
171 |
+ |
|
172 |
+ The names of the genes and modules can be fairly arbitrary. But if you |
|
173 |
+ try hard you can confuse the parser. For instance, using gene or |
|
174 |
+ module names that contain "," or ":", or ">" is likely to get you into |
|
175 |
+ trouble. Of course, you know you should not try to use those |
|
176 |
+ characters because you know those characters have special meanings to |
|
177 |
+ separate names or indicate epistasis or order relationships. Right |
|
178 |
+ now, using those characters as names is caught (and result in |
|
179 |
+ stopping) if passed as names for noIntGenes. } |
|
167 | 180 |
|
168 | 181 |
\author{ Ramon Diaz-Uriarte |
169 | 182 |
} |
... | ... |
@@ -1,5 +1,4 @@ |
1 |
- |
|
2 |
-// Copyright 2013, 2014, 2015 Ramon Diaz-Uriarte |
|
1 |
+// Copyright 2013, 2014, 2015, 2016 Ramon Diaz-Uriarte |
|
3 | 2 |
|
4 | 3 |
// This program is free software: you can redistribute it and/or modify |
5 | 4 |
// it under the terms of the GNU General Public License as published by |
... | ... |
@@ -149,6 +148,7 @@ void remove_zero_sp_nr(std::vector<int>& sp_to_remove, |
149 | 148 |
} |
150 | 149 |
} |
151 | 150 |
|
151 |
+ |
|
152 | 152 |
inline void driverCounts(int& maxNumDrivers, |
153 | 153 |
int& totalPresentDrivers, |
154 | 154 |
std::vector<int>& countByDriver, |
... | ... |
@@ -163,24 +163,28 @@ inline void driverCounts(int& maxNumDrivers, |
163 | 163 |
// We used to do count_NumDrivers and then whichDrivers |
164 | 164 |
maxNumDrivers = 0; |
165 | 165 |
int tmpdr = 0; |
166 |
- int driver_indx; |
|
167 |
- |
|
166 |
+ int driver_indx = 0; // the index in the driver table |
|
168 | 167 |
for(int j = 0; j < returnGenotypes.ncol(); ++j) { |
169 | 168 |
tmpdr = 0; |
169 |
+ driver_indx = 0; |
|
170 | 170 |
for(int i : drv) { |
171 |
- driver_indx = i - 1; |
|
172 |
- tmpdr += returnGenotypes(driver_indx, j); |
|
173 |
- countByDriver[driver_indx] += returnGenotypes(driver_indx, j); |
|
171 |
+ tmpdr += returnGenotypes(i - 1, j); |
|
172 |
+ countByDriver[driver_indx] += returnGenotypes(i - 1, j); |
|
173 |
+ ++driver_indx; |
|
174 | 174 |
} |
175 | 175 |
if(tmpdr > maxNumDrivers) maxNumDrivers = tmpdr; |
176 | 176 |
} |
177 |
+ if(returnGenotypes.ncol() > 0) { |
|
178 |
+ STOPASSERT(driver_indx == static_cast<int>( countByDriver.size())); |
|
179 |
+ } else { |
|
180 |
+ STOPASSERT(driver_indx <= static_cast<int>( countByDriver.size())); |
|
181 |
+ } |
|
177 | 182 |
for(size_t i = 0; i < countByDriver.size(); ++i) { |
178 | 183 |
if(countByDriver[i] > 0) { |
179 | 184 |
presentDrivers.push_back(i + 1); |
180 | 185 |
++totalPresentDrivers; |
181 | 186 |
} |
182 | 187 |
} |
183 |
- |
|
184 | 188 |
} |
185 | 189 |
|
186 | 190 |
|
... | ... |
@@ -1596,10 +1600,11 @@ Rcpp::List nr_BNB_Algo5(Rcpp::List rFE, |
1596 | 1600 |
double totPopSize = 0; |
1597 | 1601 |
std::vector<double> sampleTotPopSize; |
1598 | 1602 |
std::vector<double> sampleLargestPopSize; |
1599 |
- std::vector<int> sampleMaxNDr; //The number of drivers in the population |
|
1600 |
- // with the largest number of drivers; and this for each time sample |
|
1601 |
- std::vector<int> sampleNDrLargestPop; //Number of drivers in population |
|
1602 |
- // with largest size (at each time sample) |
|
1603 |
+ std::vector<int> sampleMaxNDr; //The largest number of drivers in any |
|
1604 |
+ //genotype or clone at each time sample |
|
1605 |
+ std::vector<int> sampleNDrLargestPop; //Number of drivers in the clone |
|
1606 |
+ // with largest size (at each time |
|
1607 |
+ // sample) |
|
1603 | 1608 |
sampleTotPopSize.reserve(initIt); |
1604 | 1609 |
sampleLargestPopSize.reserve(initIt); |
1605 | 1610 |
sampleMaxNDr.reserve(initIt); |
... | ... |
@@ -1827,12 +1832,6 @@ Rcpp::List nr_BNB_Algo5(Rcpp::List rFE, |
1827 | 1832 |
countByDriver, presentDrivers, |
1828 | 1833 |
returnGenotypes, fitnessEffects.drv); |
1829 | 1834 |
|
1830 |
- // nr_count_NumDrivers(maxNumDrivers, countByDriver, |
|
1831 |
- // returnGenotypes, fitnessEffects.drv); |
|
1832 |
- |
|
1833 |
- // whichDrivers(totalPresentDrivers, occurringDrivers, countByDriver); |
|
1834 |
- |
|
1835 |
- // std::map<int, std::string> intName = mapGenesIntToNames(fitnessEffects); |
|
1836 | 1835 |
std::vector<std::string> genotypesAsStrings = |
1837 | 1836 |
genotypesToNameString(uniqueGenotypes_vector_nr, genesInFitness, intName); |
1838 | 1837 |
std::string driversAsString = |
... | ... |
@@ -1850,31 +1849,6 @@ Rcpp::List nr_BNB_Algo5(Rcpp::List rFE, |
1850 | 1849 |
fill_SStats(perSampleStats, sampleTotPopSize, sampleLargestPopSize, |
1851 | 1850 |
sampleLargestPopProp, sampleMaxNDr, sampleNDrLargestPop); |
1852 | 1851 |
|
1853 |
- |
|
1854 |
- // // // debuggin: precompute things |
|
1855 |
- // DP2(simulsDone); |
|
1856 |
- // DP2(maxWallTime); |
|
1857 |
- // DP2(hittedWallTime); |
|
1858 |
- // DP2(outNS_i); |
|
1859 |
- // DP2( sampleMaxNDr[outNS_i]); |
|
1860 |
- // DP2(sampleNDrLargestPop[outNS_i]); |
|
1861 |
- // DP2(sampleLargestPopSize[outNS_i]); |
|
1862 |
- // DP2(sampleLargestPopProp[outNS_i]); |
|
1863 |
- // DP2((runningWallTime > maxWallTime)); |
|
1864 |
- // here("after precomp"); |
|
1865 |
- // here("*******************************************"); |
|
1866 |
- |
|
1867 |
- // Rcpp::List returnGenotypesO = Rcpp::wrap(uniqueGenotypesV); |
|
1868 |
- |
|
1869 |
- // if(keepPhylog) { |
|
1870 |
- // Rcpp::DataFrame PhylogDF = Rcpp::DataFrame::create(Named("parent") = phylog.parent, |
|
1871 |
- // Named("child") = phylog.child, |
|
1872 |
- // Named("time") = phylog.time); |
|
1873 |
- // } else { |
|
1874 |
- // Rcpp::DataFrame PhylogDF = Rcpp::DataFrame::create(Named("parent") = NA, |
|
1875 |
- // Named("child") = NA, |
|
1876 |
- // Named("time") = NA); |
|
1877 |
- // } |
|
1878 | 1852 |
|
1879 | 1853 |
return |
1880 | 1854 |
List::create(Named("pops.by.time") = outNS, |
... | ... |
@@ -1920,9 +1894,7 @@ Rcpp::List nr_BNB_Algo5(Rcpp::List rFE, |
1920 | 1894 |
Named("UnrecoverExcept") = false) |
1921 | 1895 |
); |
1922 | 1896 |
|
1923 |
- // END_RCPP |
|
1924 |
- |
|
1925 |
- } |
|
1897 |
+} |
|
1926 | 1898 |
|
1927 | 1899 |
|
1928 | 1900 |
// Creating return object: |
... | ... |
@@ -5,11 +5,18 @@ |
5 | 5 |
|
6 | 6 |
//#define DEBUGZ |
7 | 7 |
// #define DEBUGV |
8 |
-//#define DEBUGW |
|
9 |
- |
|
8 |
+#define DEBUGW |
|
10 | 9 |
|
11 | 10 |
#define DP1(x) {Rcpp::Rcout << "\n DEBUG2: I am at " << x << std::endl;} |
12 | 11 |
#define DP2(x) {Rcpp::Rcout << "\n DEBUG2: Value of " << #x << " = " << x << std::endl;} |
12 |
+#define DP3(x, t){ \ |
|
13 |
+ Rcpp::Rcout <<"\n DEBUG2:" ; \ |
|
14 |
+ for(int xut = 0; xut < t; ++xut) Rcpp::Rcout << "\t "; \ |
|
15 |
+ Rcpp::Rcout << " I am at " << x << std::endl;} |
|
16 |
+#define DP4(x, t){ \ |
|
17 |
+ Rcpp::Rcout <<"\n DEBUG2:" ; \ |
|
18 |
+ for(int xut = 0; xut < t; ++xut) Rcpp::Rcout << "\t "; \ |
|
19 |
+ Rcpp::Rcout << " Value of " << #x << " = " << x << std::endl; } |
|
13 | 20 |
|
14 | 21 |
/* void here(std::string x) { */ |
15 | 22 |
/* Rcpp::Rcout << "\n DEBUG: HERE at " << x << std::endl; */ |
16 | 23 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,59 @@ |
1 |
+cat(paste("\n Starting driverCounts long at", date())) |
|
2 |
+ |
|
3 |
+date() |
|
4 |
+test_that("Runs without crashes", { |
|
5 |
+ |
|
6 |
+ iteration <- 1 |
|
7 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
8 |
+ names(ni) <- paste0("g", 2:11) |
|
9 |
+ ## each single one |
|
10 |
+ for(i in 2:11) { |
|
11 |
+ cat("\n doing iteration", iteration, "\n") |
|
12 |
+ ni[] <- runif(10, min = -0.01, max = 0.1) |
|
13 |
+ ni <- sample(ni) |
|
14 |
+ drvN <- paste0("g", i) |
|
15 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
16 |
+ drvNames = drvN) |
|
17 |
+ expect_silent(uu <- oncoSimulPop(20, |
|
18 |
+ fe31, |
|
19 |
+ mu = 1e-6, |
|
20 |
+ initSize = 1e5, |
|
21 |
+ model = "McFL", |
|
22 |
+ detectionSize = 5e6, |
|
23 |
+ finalTime = 5, |
|
24 |
+ keepEvery = 1, |
|
25 |
+ onlyCancer = FALSE, |
|
26 |
+ mc.cores = 2, |
|
27 |
+ sampleEvery = 0.03 |
|
28 |
+ )) |
|
29 |
+ iteration <- iteration + 1 |
|
30 |
+ } |
|
31 |
+ ## all pairs, trios, etc, shuffled order |
|
32 |
+ for(n in 2:10) { |
|
33 |
+ m <- combinations(10, n, 2:11) |
|
34 |
+ for(j in 1:nrow(m)) { |
|
35 |
+ cat("\n doing iteration", iteration, "\n") |
|
36 |
+ ni[] <- runif(10, min = -0.01, max = 0.1) |
|
37 |
+ ni <- sample(ni) |
|
38 |
+ drvN <- paste0("g", sample(m[j, ])) |
|
39 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
40 |
+ drvNames = drvN) |
|
41 |
+ expect_silent(uu <- oncoSimulPop(10, |
|
42 |
+ fe31, |
|
43 |
+ mu = 1e-6, |
|
44 |
+ initSize = 1e5, |
|
45 |
+ model = "McFL", |
|
46 |
+ detectionSize = 5e6, |
|
47 |
+ finalTime = 5, |
|
48 |
+ keepEvery = 1, |
|
49 |
+ onlyCancer = FALSE, |
|
50 |
+ mc.cores = 2, |
|
51 |
+ sampleEvery = 0.03 |
|
52 |
+ )) |
|
53 |
+ iteration <- iteration + 1 |
|
54 |
+ } |
|
55 |
+ } |
|
56 |
+ |
|
57 |
+}) |
|
58 |
+date() |
|
59 |
+cat(paste("\n Ending driverCounts long at", date())) |
... | ... |
@@ -1,5 +1,10 @@ |
1 | 1 |
cat(paste("\n Starting at mutPropGrowth long", date(), "\n")) |
2 | 2 |
|
3 |
+## Note that many of the tests below where we do a test and have a |
|
4 |
+## comparison like "whatever$p.value > p.fail " are, of course, expected |
|
5 |
+## to fail with prob. ~ p.fail even if things are perfectly OK. |
|
6 |
+ |
|
7 |
+ |
|
3 | 8 |
## Why this does not really reflect what we want, and why number of clones |
4 | 9 |
## is better that capture the idea of "more mutations". NumClones reflects |
5 | 10 |
## the creation of a new clone, something that happens whenever there is a |
... | ... |
@@ -50,7 +55,7 @@ mutsPerClone <- function(x, per.pop.mean = TRUE) { |
50 | 55 |
RNGkind("L'Ecuyer-CMRG") ## for the mclapplies |
51 | 56 |
## If crashes I want to see where: thus output seed. |
52 | 57 |
|
53 |
- |
|
58 |
+p.value.threshold <- 0.001 |
|
54 | 59 |
|
55 | 60 |
## this tests takes 10 seconds. Moved to long. So this was in the standard |
56 | 61 |
## ones. |
... | ... |
@@ -60,7 +65,7 @@ test_that("mutPropGrowth diffs with s> 0", { |
60 | 65 |
set.seed(pseed) |
61 | 66 |
cat("\n mgp1: the seed is", pseed, "\n") |
62 | 67 |
ft <- 4 ## 2.7 |
63 |
- pops <- 100 |
|
68 |
+ pops <- 150 |
|
64 | 69 |
lni <- 150 ## 100 |
65 | 70 |
no <- 1e3 ## 5e1 |
66 | 71 |
ni <- c(2, rep(0, lni)) ## 2 ## 4 ## 5 |
... | ... |
@@ -96,10 +101,12 @@ test_that("mutPropGrowth diffs with s> 0", { |
96 | 101 |
## summary(mutsPerClone(nca)) |
97 | 102 |
## summary(mutsPerClone(nca2)) |
98 | 103 |
## The real comparison |
99 |
- expect_true( median(summary(nca)$NumClones) > |
|
100 |
- median(summary(nca2)$NumClones)) |
|
101 |
- expect_true( mean(mutsPerClone(nca)) > |
|
102 |
- mean(mutsPerClone(nca2))) |
|
104 |
+ expect_true( wilcox.test(summary(nca)$NumClones, |
|
105 |
+ summary(nca2)$NumClones, |
|
106 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
107 |
+ expect_true( wilcox.test(mutsPerClone(nca), |
|
108 |
+ mutsPerClone(nca2), |
|
109 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
103 | 110 |
}) |
104 | 111 |
cat("\n", date(), "\n") |
105 | 112 |
|
... | ... |
@@ -127,7 +134,7 @@ test_that("mutPropGrowth no diffs with s = 0", { |
127 | 134 |
set.seed(pseed) |
128 | 135 |
cat("\n mgp1ND: the seed is", pseed, "\n") |
129 | 136 |
ft <- 4 ## 2.7 |
130 |
- pops <- 200 |
|
137 |
+ pops <- 250 |
|
131 | 138 |
lni <- 150 ## 100 |
132 | 139 |
no <- 1e3 ## 5e1 |
133 | 140 |
ni <- c(0, rep(0, lni)) ## 2 ## 4 ## 5 |
... | ... |
@@ -224,7 +231,7 @@ test_that("mutPropGrowth no diffs with s = 0, oncoSimulSample", { |
224 | 231 |
set.seed(pseed) |
225 | 232 |
cat("\n oss1: the seed is", pseed, "\n") |
226 | 233 |
ft <- 3.5 ## 4 |
227 |
- pops <- 200 |
|
234 |
+ pops <- 250 |
|
228 | 235 |
lni <- 200 ## 150 |
229 | 236 |
no <- 1e3 ## 5e1 |
230 | 237 |
ni <- c(0, rep(0, lni)) ## 2 ## 4 ## 5 |
... | ... |
@@ -290,7 +297,7 @@ test_that("mutPropGrowth no diffs with s = 0, oncoSimulSample, McFL", { |
290 | 297 |
set.seed(pseed) |
291 | 298 |
cat("\n ossmcfND1: the seed is", pseed, "\n") |
292 | 299 |
ft <- 40 ## 4 |
293 |
- pops <- 200 |
|
300 |
+ pops <- 250 |
|
294 | 301 |
lni <- 200 ## 150 |
295 | 302 |
no <- 1e3 ## 5e1 |
296 | 303 |
ni <- c(0, rep(0, lni)) ## 2 ## 4 ## 5 |
... | ... |
@@ -351,14 +358,6 @@ test_that("mutPropGrowth no diffs with s = 0, oncoSimulSample, McFL", { |
351 | 358 |
cat("\n", date(), "\n") |
352 | 359 |
|
353 | 360 |
|
354 |
- |
|
355 |
- |
|
356 |
- |
|
357 |
- |
|
358 |
- |
|
359 |
- |
|
360 |
- |
|
361 |
- |
|
362 | 361 |
## The tests below can occasionally fail (but that probability decreases |
363 | 362 |
## as we increase number of pops), as they should. |
364 | 363 |
## Some of these tests take some time. For now, show times. |
... | ... |
@@ -388,7 +387,7 @@ test_that("oncoSimulSample Without initmutant and modules", { |
388 | 387 |
pseed <- sample(9999999, 1) |
389 | 388 |
set.seed(pseed) |
390 | 389 |
cat("\n osS: the seed is", pseed, "\n") |
391 |
- pops <- 60 |
|
390 |
+ pops <- 150 |
|
392 | 391 |
lni <- 1 ## no fitness effects genes |
393 | 392 |
fni <- 50 ## fitness effects genes |
394 | 393 |
no <- 1e4 |
... | ... |
@@ -450,10 +449,12 @@ test_that("oncoSimulSample Without initmutant and modules", { |
450 | 449 |
(mutsPerClone2 <- rowSums(b2$popSample)) |
451 | 450 |
summary(mutsPerClone1) |
452 | 451 |
summary(mutsPerClone2) |
453 |
- expect_true( mean(mutsPerClone2) > |
|
454 |
- mean(mutsPerClone1)) |
|
455 |
- expect_true( median(b2$popSummary[, "NumClones"]) > |
|
456 |
- median(b1$popSummary[, "NumClones"])) |
|
452 |
+ expect_true( wilcox.test(mutsPerClone2, |
|
453 |
+ mutsPerClone1, |
|
454 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
455 |
+ expect_true( wilcox.test(b2$popSummary[, "NumClones"], |
|
456 |
+ b1$popSummary[, "NumClones"], |
|
457 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
457 | 458 |
}) |
458 | 459 |
cat("\n", date(), "\n") |
459 | 460 |
|
... | ... |
@@ -463,7 +464,7 @@ test_that("oncoSimulSample Without initmutant and modules, McFL", { |
463 | 464 |
pseed <- sample(9999999, 1) |
464 | 465 |
set.seed(pseed) |
465 | 466 |
cat("\n osSMcFL: the seed is", pseed, "\n") |
466 |
- pops <- 60 |
|
467 |
+ pops <- 150 |
|
467 | 468 |
lni <- 1 ## no fitness effects genes |
468 | 469 |
fni <- 50 ## fitness effects genes |
469 | 470 |
no <- 1e4 ## note we use only 10 in the other example below |
... | ... |
@@ -525,14 +526,179 @@ test_that("oncoSimulSample Without initmutant and modules, McFL", { |
525 | 526 |
(mutsPerClone2 <- rowSums(b2$popSample)) |
526 | 527 |
summary(mutsPerClone1) |
527 | 528 |
summary(mutsPerClone2) |
528 |
- expect_true( mean(mutsPerClone2) > |
|
529 |
- mean(mutsPerClone1)) |
|
530 |
- expect_true( median(b2$popSummary[, "NumClones"]) > |
|
531 |
- median(b1$popSummary[, "NumClones"])) |
|
529 |
+ expect_true( wilcox.test(mutsPerClone2, |
|
530 |
+ mutsPerClone1, |
|
531 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
532 |
+ expect_true( wilcox.test(b2$popSummary[, "NumClones"], |
|
533 |
+ b1$popSummary[, "NumClones"], |
|
534 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
532 | 535 |
}) |
533 | 536 |
cat("\n", date(), "\n") |
534 | 537 |
|
535 | 538 |
|
539 |
+ |
|
540 |
+## Same as above, but we stop in detectionSize, so no differences are |
|
541 |
+## attributable just to differences in population size. |
|
542 |
+ |
|
543 |
+ |
|
544 |
+cat("\n", date(), "\n") |
|
545 |
+test_that("oncoSimulSample Without initmutant and modules, fixed size", { |
|
546 |
+ pseed <- sample(9999999, 1) |
|
547 |
+ set.seed(pseed) |
|
548 |
+ cat("\n osSFPS: the seed is", pseed, "\n") |
|
549 |
+ pops <- 150 |
|
550 |
+ lni <- 1 ## no fitness effects genes |
|
551 |
+ fni <- 50 ## fitness effects genes |
|
552 |
+ no <- 1e4 |
|
553 |
+ ft <- 9 #4 |
|
554 |
+ s3 <- 2.5 |
|
555 |
+ mu <- 1e-5 |
|
556 |
+ ## noInt have no fitness effects, but can accumulate mutations |
|
557 |
+ ni <- rep(0, lni) |
|
558 |
+ ## Those with fitness effects in one module, so |
|
559 |
+ ## neither fitness nor mut. rate blow up |
|
560 |
+ gn <- paste(paste0("a", 1:fni), collapse = ", ") |
|
561 |
+ f3 <- allFitnessEffects(epistasis = c("A" = s3), |
|
562 |
+ geneToModule = c("A" = gn), |
|
563 |
+ noIntGenes = ni) |
|
564 |
+ x <- 1e-9 ## so basically anything that appears once |
|
565 |
+ pseed <- sample(9999999, 1) |
|
566 |
+ set.seed(pseed) |
|
567 |
+ cat("\n osSFPSa: the seed is", pseed, "\n") |
|
568 |
+ b1 <- oncoSimulSample(pops, |
|
569 |
+ f3, |
|
570 |
+ mu = mu, |
|
571 |
+ mutationPropGrowth = FALSE, |
|
572 |
+ finalTime =ft, |
|
573 |
+ initSize = no, |
|
574 |
+ onlyCancer = FALSE, |
|
575 |
+ sampleEvery = 0.01, |
|
576 |
+ detectionSize = 6e4, |
|
577 |
+ detectionDrivers = 99, |
|
578 |
+ seed =NULL, |
|
579 |
+ thresholdWhole = x) |
|
580 |
+ pseed <- sample(9999999, 1) |
|
581 |
+ set.seed(pseed) |
|
582 |
+ cat("\n osSFPSb: the seed is", pseed, "\n") |
|
583 |
+ b2 <- oncoSimulSample(pops, |
|
584 |
+ f3, |
|
585 |
+ mu = mu, |
|
586 |
+ mutationPropGrowth = TRUE, |
|
587 |
+ finalTime =ft, |
|
588 |
+ initSize = no, |
|
589 |
+ onlyCancer = FALSE, |
|
590 |
+ sampleEvery = 0.01, |
|
591 |
+ detectionSize = 6e4, |
|
592 |
+ detectionDrivers = 99, |
|
593 |
+ seed =NULL, |
|
594 |
+ thresholdWhole = x) |
|
595 |
+ b1$popSummary[1:5, c(1:3, 8:9)] |
|
596 |
+ summary(b1$popSummary[, "NumClones"]) |
|
597 |
+ summary(b1$popSummary[, "TotalPopSize"]) |
|
598 |
+ b2$popSummary[1:5, c(1:3, 8:9)] |
|
599 |
+ summary(b2$popSummary[, "NumClones"]) |
|
600 |
+ summary(b2$popSummary[, "TotalPopSize"]) |
|
601 |
+ ## cc1 and cc2 should all be smaller than pops, or you are maxing |
|
602 |
+ ## things and not seeing patterns |
|
603 |
+ (cc1 <- colSums(b1$popSample)) |
|
604 |
+ (cc2 <- colSums(b2$popSample)) |
|
605 |
+ ## Of course, these are NOT really mutationsPerClone: we collapse over |
|
606 |
+ ## whole population. |
|
607 |
+ (mutsPerClone1 <- rowSums(b1$popSample)) |
|
608 |
+ (mutsPerClone2 <- rowSums(b2$popSample)) |
|
609 |
+ summary(mutsPerClone1) |
|
610 |
+ summary(mutsPerClone2) |
|
611 |
+ expect_true( wilcox.test(mutsPerClone2, |
|
612 |
+ mutsPerClone1, |
|
613 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
614 |
+ expect_true( wilcox.test(b2$popSummary[, "NumClones"], |
|
615 |
+ b1$popSummary[, "NumClones"], |
|
616 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
617 |
+}) |
|
618 |
+cat("\n", date(), "\n") |
|
619 |
+ |
|
620 |
+ |
|
621 |
+cat("\n", date(), "\n") |
|
622 |
+test_that("oncoSimulSample Without initmutant and modules, McFL, fixed size", { |
|
623 |
+ pseed <- sample(9999999, 1) |
|
624 |
+ set.seed(pseed) |
|
625 |
+ cat("\n osSFPSMcFL: the seed is", pseed, "\n") |
|
626 |
+ pops <- 150 |
|
627 |
+ lni <- 1 ## no fitness effects genes |
|
628 |
+ fni <- 50 ## fitness effects genes |
|
629 |
+ no <- 1e4 ## note we use only 10 in the other example below |
|
630 |
+ ft <- 10 ##4 |
|
631 |
+ s3 <- 2.5 |
|
632 |
+ mu <- 1e-5 |
|
633 |
+ ## noInt have no fitness effects, but can accumulate mutations |
|
634 |
+ ni <- rep(0, lni) |
|
635 |
+ ## Those with fitness effects in one module, so |
|
636 |
+ ## neither fitness nor mut. rate blow up |
|
637 |
+ gn <- paste(paste0("a", 1:fni), collapse = ", ") |
|
638 |
+ f3 <- allFitnessEffects(epistasis = c("A" = s3), |
|
639 |
+ geneToModule = c("A" = gn), |
|
640 |
+ noIntGenes = ni) |
|
641 |
+ x <- 1e-9 ## 1/no |
|
642 |
+ pseed <- sample(9999999, 1) |
|
643 |
+ set.seed(pseed) |
|
644 |
+ cat("\n osSFPSMcFLa: the seed is", pseed, "\n") |
|
645 |
+ b1 <- oncoSimulSample(pops, |
|
646 |
+ f3, |
|
647 |
+ mu = mu, |
|
648 |
+ mutationPropGrowth = FALSE, |
|
649 |
+ finalTime =ft, |
|
650 |
+ initSize = no, |
|
651 |
+ onlyCancer = FALSE, |
|
652 |
+ sampleEvery = 0.01, |
|
653 |
+ detectionSize = 2.5e4, |
|
654 |
+ detectionDrivers = 99, |
|
655 |
+ seed =NULL, |
|
656 |
+ model = "McFL", |
|
657 |
+ thresholdWhole = x) |
|
658 |
+ pseed <- sample(9999999, 1) |
|
659 |
+ set.seed(pseed) |
|
660 |
+ cat("\n osSFPSMcFLb: the seed is", pseed, "\n") |
|
661 |
+ b2 <- oncoSimulSample(pops, |
|
662 |
+ f3, |
|
663 |
+ mu = mu, |
|
664 |
+ mutationPropGrowth = TRUE, |
|
665 |
+ finalTime =ft, |
|
666 |
+ initSize = no, |
|
667 |
+ onlyCancer = FALSE, |
|
668 |
+ sampleEvery = 0.01, |
|
669 |
+ detectionSize = 2.5e4, |
|
670 |
+ detectionDrivers = 99, |
|
671 |
+ seed =NULL, |
|
672 |
+ model = "McFL", |
|
673 |
+ thresholdWhole = x) |
|
674 |
+ b1$popSummary[1:5, c(1:3, 8:9)] |
|
675 |
+ summary(b1$popSummary[, "NumClones"]) |
|
676 |
+ summary(b1$popSummary[, "TotalPopSize"]) |
|
677 |
+ b2$popSummary[1:5, c(1:3, 8:9)] |
|
678 |
+ summary(b2$popSummary[, "NumClones"]) |
|
679 |
+ summary(b2$popSummary[, "TotalPopSize"]) |
|
680 |
+ ## cc1 and cc2 should all be smaller than pops, or you are maxing |
|
681 |
+ ## things and not seeing patterns |
|
682 |
+ (cc1 <- colSums(b1$popSample)) |
|
683 |
+ (cc2 <- colSums(b2$popSample)) |
|
684 |
+ (mutsPerClone1 <- rowSums(b1$popSample)) |
|
685 |
+ (mutsPerClone2 <- rowSums(b2$popSample)) |
|
686 |
+ summary(mutsPerClone1) |
|
687 |
+ summary(mutsPerClone2) |
|
688 |
+ expect_true( wilcox.test(mutsPerClone2, |
|
689 |
+ mutsPerClone1, |
|
690 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
691 |
+ expect_true( wilcox.test(b2$popSummary[, "NumClones"], |
|
692 |
+ b1$popSummary[, "NumClones"], |
|
693 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
694 |
+}) |
|
695 |
+cat("\n", date(), "\n") |
|
696 |
+ |
|
697 |
+ |
|
698 |
+ |
|
699 |
+ |
|
700 |
+ |
|
701 |
+ |
|
536 | 702 |
## This generally works, but not always. Because: a) starting with a you |
537 | 703 |
## can get a mutation in b. Or starting with b you can get a mutation in |
538 | 704 |
## a. When either happens is stochastic. And we are also mixing the |
... | ... |
@@ -546,7 +712,7 @@ test_that("Ordering of number of clones with mutpropgrowth", { |
546 | 712 |
pseed <- sample(9999999, 1) |
547 | 713 |
set.seed(pseed) |
548 | 714 |
cat("\n omp1: the seed is", pseed, "\n") |
549 |
- pops <- 100 |
|
715 |
+ pops <- 150 |
|
550 | 716 |
lni <- 200 |
551 | 717 |
no <- 5e3 |
552 | 718 |
ni <- c(5, 2, rep(0, lni)) |
... | ... |
@@ -590,12 +756,15 @@ test_that("Ordering of number of clones with mutpropgrowth", { |
590 | 756 |
expect_true(var(summary(nca2)$NumClones) > 1e-4) |
591 | 757 |
expect_true(var(summary(ncb2)$NumClones) > 1e-4) |
592 | 758 |
## The real comparison |
593 |
- expect_true( median(summary(nca)$NumClones) > |
|
594 |
- median(summary(nca2)$NumClones)) |
|
595 |
- expect_true( median(summary(nca)$NumClones) > |
|
596 |
- median(summary(ncb)$NumClones)) |
|
597 |
- expect_true( median(summary(ncb)$NumClones) > |
|
598 |
- median(summary(ncb2)$NumClones)) |
|
759 |
+ expect_true( wilcox.test(summary(nca)$NumClones, |
|
760 |
+ summary(nca2)$NumClones, |
|
761 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
762 |
+ expect_true( wilcox.test(summary(nca)$NumClones, |
|
763 |
+ summary(ncb)$NumClones, |
|
764 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
765 |
+ expect_true( wilcox.test(summary(ncb)$NumClones, |
|
766 |
+ summary(ncb2)$NumClones, |
|
767 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
599 | 768 |
}) |
600 | 769 |
cat("\n", date(), "\n") |
601 | 770 |
|
... | ... |
@@ -604,7 +773,7 @@ test_that("Ordering of number of clones with mutpropgrowth, McFL", { |
604 | 773 |
pseed <- sample(9999999, 1) |
605 | 774 |
set.seed(pseed) |
606 | 775 |
cat("\n omp2: the seed is", pseed, "\n") |
607 |
- pops <- 100 |
|
776 |
+ pops <- 150 |
|
608 | 777 |
lni <- 200 |
609 | 778 |
no <- 5e3 |
610 | 779 |
ni <- c(5, 2, rep(0, lni)) |
... | ... |
@@ -648,12 +817,15 @@ test_that("Ordering of number of clones with mutpropgrowth, McFL", { |
648 | 817 |
expect_true(var(summary(nca2)$NumClones) > 1e-4) |
649 | 818 |
expect_true(var(summary(ncb2)$NumClones) > 1e-4) |
650 | 819 |
## The real comparison |
651 |
- expect_true( median(summary(nca)$NumClones) > |
|
652 |
- median(summary(nca2)$NumClones)) |
|
653 |
- expect_true( median(summary(nca)$NumClones) > |
|
654 |
- median(summary(ncb)$NumClones)) |
|
655 |
- expect_true( median(summary(ncb)$NumClones) > |
|
656 |
- median(summary(ncb2)$NumClones)) |
|
820 |
+ expect_true( wilcox.test(summary(nca)$NumClones, |
|
821 |
+ summary(nca2)$NumClones, |
|
822 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
823 |
+ expect_true( wilcox.test(summary(nca)$NumClones, |
|
824 |
+ summary(ncb)$NumClones, |
|
825 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
826 |
+ expect_true( wilcox.test(summary(ncb)$NumClones, |
|
827 |
+ summary(ncb2)$NumClones, |
|
828 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
657 | 829 |
}) |
658 | 830 |
|
659 | 831 |
## Psss ideas. The idea here is that you hit the module with fitness |
... | ... |
@@ -665,7 +837,7 @@ test_that("Without initmutant", { |
665 | 837 |
pseed <- sample(9999999, 1) |
666 | 838 |
set.seed(pseed) |
667 | 839 |
cat("\n s3: the seed is", pseed, "\n") |
668 |
- pops <- 200 |
|
840 |
+ pops <- 250 |
|
669 | 841 |
lni <- 1 ## no fitness effects genes |
670 | 842 |
fni <- 50 ## fitness effects genes |
671 | 843 |
no <- 1e3 |
... | ... |
@@ -704,16 +876,19 @@ test_that("Without initmutant", { |
704 | 876 |
seed = NULL, mc.cores = 2) |
705 | 877 |
## summary(s3.g)[, c(1, 2, 3, 8, 9)] |
706 | 878 |
## summary(s3.ng)[, c(1, 2, 3, 8, 9)] |
707 |
- expect_true( mean(mutsPerClone(s3.g)) > |
|
708 |
- mean(mutsPerClone(s3.ng))) |
|
709 |
- expect_true( median(summary(s3.g)$NumClones) > |
|
710 |
- median(summary(s3.ng)$NumClones)) |
|
879 |
+ expect_true( wilcox.test(mutsPerClone(s3.g), |
|
880 |
+ mutsPerClone(s3.ng), |
|
881 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
882 |
+ expect_true( wilcox.test(summary(s3.g)$NumClones, |
|
883 |
+ summary(s3.ng)$NumClones, |
|
884 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
711 | 885 |
gc() |
712 | 886 |
}) |
713 | 887 |
cat("\n", date(), "\n") |
714 | 888 |
|
715 | 889 |
cat("\n", date(), "\n") |
716 | 890 |
test_that("Without initmutant, 2", { |
891 |
+ |
|
717 | 892 |
## More of the above. Use smaller s2 and smaller mutation, but then to |
718 | 893 |
## see it reliably you need large ft and we also increase |
719 | 894 |
## init. pop. size. |
... | ... |
@@ -722,9 +897,9 @@ test_that("Without initmutant, 2", { |
722 | 897 |
cat("\n s2: the seed is", pseed, "\n") |
723 | 898 |
s2 <- 1.0 |
724 | 899 |
ft <- 15 |
725 |
- pops <- 200 |
|
900 |
+ pops <- 150 |
|
726 | 901 |
lni <- 1 ## no fitness effects genes |
727 |
- fni <- 50 ## fitness effects genes |
|
902 |
+ fni <- 200 ## fitness effects genes |
|
728 | 903 |
no <- 1e4 |
729 | 904 |
mu <- 5e-6 ## easier to see |
730 | 905 |
## noInt have no fitness effects, but can accumulate mutations |
... | ... |
@@ -757,13 +932,16 @@ test_that("Without initmutant, 2", { |
757 | 932 |
initSize = no, keepEvery = 1, |
758 | 933 |
onlyCancer = FALSE, |
759 | 934 |
seed = NULL, mc.cores = 2) |
760 |
- ## summary(s2.g)[, c(1, 2, 3, 8, 9)] |
|
761 |
- ## summary(s2.ng)[, c(1, 2, 3, 8, 9)] |
|
762 |
- expect_true( mean(mutsPerClone(s2.g)) > |
|
763 |
- mean(mutsPerClone(s2.ng))) |
|
764 |
- expect_true( median(summary(s2.g)$NumClones) > |
|
765 |
- median(summary(s2.ng)$NumClones)) |
|
935 |
+ summary(s2.g)[, c(1, 2, 3, 8, 9)] |
|
936 |
+ summary(s2.ng)[, c(1, 2, 3, 8, 9)] |
|
937 |
+ expect_true( wilcox.test(mutsPerClone(s2.g), |
|
938 |
+ mutsPerClone(s2.ng), |
|
939 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
940 |
+ expect_true( wilcox.test(summary(s2.g)$NumClones, |
|
941 |
+ summary(s2.ng)$NumClones, |
|
942 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
766 | 943 |
gc() |
944 |
+ |
|
767 | 945 |
}) |
768 | 946 |
cat("\n", date(), "\n") |
769 | 947 |
|
... | ... |
@@ -774,7 +952,7 @@ test_that("McFL: Without initmutant", { |
774 | 952 |
cat("\n mcfls2: the seed is", pseed, "\n") |
775 | 953 |
s2 <- 2.0 |
776 | 954 |
ft <- 250 |
777 |
- pops <- 200 ## 200 |
|
955 |
+ pops <- 200 |
|
778 | 956 |
lni <- 1 ## no fitness effects genes |
779 | 957 |
fni <- 50 ## fitness effects genes |
780 | 958 |
no <- 1e3 |
... | ... |
@@ -811,10 +989,12 @@ test_that("McFL: Without initmutant", { |
811 | 989 |
seed = NULL, mc.cores = 2) |
812 | 990 |
## summary(s2.g)[, c(1, 2, 3, 8, 9)] |
813 | 991 |
## summary(s2.ng)[, c(1, 2, 3, 8, 9)] |
814 |
- expect_true( mean(mutsPerClone(s2.g)) > |
|
815 |
- mean(mutsPerClone(s2.ng))) |
|
816 |
- expect_true( median(summary(s2.g)$NumClones) > |
|
817 |
- median(summary(s2.ng)$NumClones)) |
|
992 |
+ expect_true( wilcox.test(mutsPerClone(s2.g), |
|
993 |
+ mutsPerClone(s2.ng), |
|
994 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
995 |
+ expect_true( wilcox.test(summary(s2.g)$NumClones, |
|
996 |
+ summary(s2.ng)$NumClones, |
|
997 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
818 | 998 |
## summary(mutsPerClone(s2.g)) |
819 | 999 |
## summary(mutsPerClone(s2.ng)) |
820 | 1000 |
## summary(summary(s2.g)$NumClones) |
... | ... |
@@ -824,6 +1004,216 @@ gc() |
824 | 1004 |
cat("\n", date(), "\n") |
825 | 1005 |
|
826 | 1006 |
|
1007 |
+ |
|
1008 |
+ |
|
1009 |
+ |
|
1010 |
+### As before, but fixing final population size. |
|
1011 |
+cat("\n", date(), "\n") |
|
1012 |
+test_that("detectionSize. Without initmutant", { |
|
1013 |
+ pseed <- sample(9999999, 1) |
|
1014 |
+ set.seed(pseed) |
|
1015 |
+ cat("\n s3FPS: the seed is", pseed, "\n") |
|
1016 |
+ pops <- 200 |
|
1017 |
+ lni <- 1 ## no fitness effects genes |
|
1018 |
+ fni <- 50 ## fitness effects genes |
|
1019 |
+ no <- 1e3 |
|
1020 |
+ ft <- 10 ## 5 |
|
1021 |
+ s3 <- 3.0 |
|
1022 |
+ mu <- 5e-5 ## easier to see |
|
1023 |
+ ## noInt have no fitness effects, but can accumulate mutations |
|
1024 |
+ ni <- rep(0, lni) |
|
1025 |
+ ## Those with fitness effects in one module, so |
|
1026 |
+ ## neither fitness nor mut. rate blow up |
|
1027 |
+ gn <- paste(paste0("a", 1:fni), collapse = ", ") |
|
1028 |
+ f3 <- allFitnessEffects(epistasis = c("A" = s3), |
|
1029 |
+ geneToModule = c("A" = gn), |
|
1030 |
+ noIntGenes = ni) |
|
1031 |
+ pseed <- sample(9999999, 1) |
|
1032 |
+ set.seed(pseed) |
|
1033 |
+ cat("\n s3FPSa: the seed is", pseed, "\n") |
|
1034 |
+ s3.ng <- oncoSimulPop(pops, |
|
1035 |
+ f3, |
|
1036 |
+ mu = mu, |
|
1037 |
+ mutationPropGrowth = FALSE, |
|
1038 |
+ detectionDrivers = 9999, |
|
1039 |
+ detectionSize = 5e5, |
|
1040 |
+ sampleEvery = 0.01, |
|
1041 |
+ keepEvery = 1, |
|
1042 |
+ finalTime =ft, |
|
1043 |
+ initSize = no, |
|
1044 |
+ onlyCancer = FALSE, |
|
1045 |
+ seed = NULL, mc.cores = 2) |
|
1046 |
+ pseed <- sample(9999999, 1) |
|
1047 |
+ set.seed(pseed) |
|
1048 |
+ cat("\n s3FPSb: the seed is", pseed, "\n") |
|
1049 |
+ s3.g <- oncoSimulPop(pops, |
|
1050 |
+ f3, |
|
1051 |
+ mu = mu, |
|
1052 |
+ mutationPropGrowth = TRUE, |
|
1053 |
+ detectionDrivers = 9999, |
|
1054 |
+ detectionSize = 5e5, |
|
1055 |
+ sampleEvery = 0.01, |
|
1056 |
+ keepEvery = 1, |
|
1057 |
+ finalTime =ft, |
|
1058 |
+ initSize = no, |
|
1059 |
+ onlyCancer = FALSE, |
|
1060 |
+ seed = NULL, mc.cores = 2) |
|
1061 |
+ ## summary(s3.g)[, c(1, 2, 3, 8, 9)] |
|
1062 |
+ ## summary(s3.ng)[, c(1, 2, 3, 8, 9)] |
|
1063 |
+ expect_true( wilcox.test(mutsPerClone(s3.g), |
|
1064 |
+ mutsPerClone(s3.ng), |
|
1065 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1066 |
+ expect_true( wilcox.test(summary(s3.g)$NumClones, |
|
1067 |
+ summary(s3.ng)$NumClones, |
|
1068 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1069 |
+ summary(summary(s3.g)[, 2]) |
|
1070 |
+ summary(summary(s3.ng)[, 2]) |
|
1071 |
+ |
|
1072 |
+gc() |
|
1073 |
+}) |
|
1074 |
+cat("\n", date(), "\n") |
|
1075 |
+ |
|
1076 |
+cat("\n", date(), "\n") |
|
1077 |
+test_that("detectionSize. Without initmutant, 2", { |
|
1078 |
+ |
|
1079 |
+ ## More of the above. Use smaller s2 and smaller mutation, but then to |
|
1080 |
+ ## see it reliably you need large final popsize |
|
1081 |
+ ## Can fail sometimes because differences are small |
|
1082 |
+ pseed <- sample(9999999, 1) |
|
1083 |
+ set.seed(pseed) |
|
1084 |
+ cat("\n s2FPS: the seed is", pseed, "\n") |
|
1085 |
+ s2 <- 1.0 |
|
1086 |
+ ft <- 500 ## very large, so we stop on size |
|
1087 |
+ pops <- 200 |
|
1088 |
+ fni <- 300 ## fitness effects genes |
|
1089 |
+ no <- 1e3 |
|
1090 |
+ mu <- 5e-6 |
|
1091 |
+ ## noInt have no fitness effects, but can accumulate mutations |
|
1092 |
+ ## Those with fitness effects in one module, so |
|
1093 |
+ ## neither fitness nor mut. rate blow up |
|
1094 |
+ gn <- paste(paste0("a", 1:fni), collapse = ", ") |
|
1095 |
+ f2 <- allFitnessEffects(epistasis = c("A" = s2), |
|
1096 |
+ geneToModule = c("A" = gn)) |
|
1097 |
+ pseed <- sample(9999999, 1) |
|
1098 |
+ set.seed(pseed) |
|
1099 |
+ cat("\n s2FPSa: the seed is", pseed, "\n") |
|
1100 |
+ s2.ng <- oncoSimulPop(pops, |
|
1101 |
+ f2, |
|
1102 |
+ mu = mu, |
|
1103 |
+ detectionDrivers = 9999, |
|
1104 |
+ detectionSize = 5e6, |
|
1105 |
+ sampleEvery = 0.01, |
|
1106 |
+ mutationPropGrowth = FALSE, |
|
1107 |
+ finalTime =ft, |
|
1108 |
+ initSize = no, keepEvery = 1, |
|
1109 |
+ onlyCancer = FALSE, |
|
1110 |
+ seed = NULL, mc.cores = 2) |
|
1111 |
+ gc(); pseed <- sample(9999999, 1) |
|
1112 |
+ set.seed(pseed) |
|
1113 |
+ cat("\n s2FPSb: the seed is", pseed, "\n") |
|
1114 |
+ s2.g <- oncoSimulPop(pops, |
|
1115 |
+ f2, |
|
1116 |
+ mu = mu, |
|
1117 |
+ detectionDrivers = 9999, |
|
1118 |
+ detectionSize = 5e6, |
|
1119 |
+ sampleEvery = 0.01, |
|
1120 |
+ mutationPropGrowth = TRUE, |
|
1121 |
+ finalTime =ft, |
|
1122 |
+ initSize = no, keepEvery = 1, |
|
1123 |
+ onlyCancer = FALSE, |
|
1124 |
+ seed = NULL, mc.cores = 2) |
|
1125 |
+ ## summary(s2.g)[, c(1, 2, 3, 8, 9)] |
|
1126 |
+ ## summary(s2.ng)[, c(1, 2, 3, 8, 9)] |
|
1127 |
+ expect_true( wilcox.test(mutsPerClone(s2.g), |
|
1128 |
+ mutsPerClone(s2.ng), |
|
1129 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1130 |
+ expect_true( wilcox.test(summary(s2.g)$NumClones, |
|
1131 |
+ summary(s2.ng)$NumClones, |
|
1132 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1133 |
+ summary(summary(s2.g)[, 2]) |
|
1134 |
+ summary(summary(s2.ng)[, 2]) |
|
1135 |
+ |
|
1136 |
+ gc() |
|
1137 |
+}) |
|
1138 |
+cat("\n", date(), "\n") |
|
1139 |
+ |
|
1140 |
+cat("\n", date(), "\n") |
|
1141 |
+test_that("detectionSize. McFL: Without initmutant", { |
|
1142 |
+ ## with McFL limiting popSize in the simuls is not that relevant, as |
|
1143 |
+ ## already limited. |
|
1144 |
+ pseed <- sample(9999999, 1) |
|
1145 |
+ set.seed(pseed) |
|
1146 |
+ cat("\n FPSmcfls2: the seed is", pseed, "\n") |
|
1147 |
+ s2 <- 2.0 |
|
1148 |
+ ft <- 250 |
|
1149 |
+ pops <- 300 ## 200 |
|
1150 |
+ lni <- 1 ## no fitness effects genes |
|
1151 |
+ fni <- 50 ## fitness effects genes |
|
1152 |
+ no <- 1e3 |
|
1153 |
+ mu <- 1e-5 ## easier to see |
|
1154 |
+ ## noInt have no fitness effects, but can accumulate mutations |
|
1155 |
+ ni <- rep(0, lni) |
|
1156 |
+ ## Those with fitness effects in one module, so |
|
1157 |
+ ## neither fitness nor mut. rate blow up |
|
1158 |
+ gn <- paste(paste0("a", 1:fni), collapse = ", ") |
|
1159 |
+ f2 <- allFitnessEffects(epistasis = c("A" = s2), |
|
1160 |
+ geneToModule = c("A" = gn), |
|
1161 |
+ noIntGenes = ni) |
|
1162 |
+ pseed <- sample(9999999, 1) |
|
1163 |
+ set.seed(pseed) |
|
1164 |
+ cat("\n FPSmcfls2a: the seed is", pseed, "\n") |
|
1165 |
+ s2.ng <- oncoSimulPop(pops, |
|
1166 |
+ f2, |
|
1167 |
+ mu = mu, |
|
1168 |
+ mutationPropGrowth = FALSE, |
|
1169 |
+ finalTime =ft, |
|
1170 |
+ detectionDrivers = 9999, |
|
1171 |
+ detectionSize = 1e4, |
|
1172 |
+ sampleEvery = 0.01, |
|
1173 |
+ initSize = no, keepEvery = 5, |
|
1174 |
+ onlyCancer = FALSE, model = "McFL", |
|
1175 |
+ seed = NULL, mc.cores = 2) |
|
1176 |
+ gc(); pseed <- sample(9999999, 1) |
|
1177 |
+ set.seed(pseed) |
|
1178 |
+ cat("\n FPSmcfls2b: the seed is", pseed, "\n") |
|
1179 |
+ s2.g <- oncoSimulPop(pops, |
|
1180 |
+ f2, |
|
1181 |
+ mu = mu, |
|
1182 |
+ mutationPropGrowth = TRUE, |
|
1183 |
+ finalTime =ft, |
|
1184 |
+ detectionDrivers = 9999, |
|
1185 |
+ detectionSize = 1e4, |
|
1186 |
+ sampleEvery = 0.01, |
|
1187 |
+ initSize = no, keepEvery = 5, |
|
1188 |
+ onlyCancer = FALSE, model = "McFL", |
|
1189 |
+ seed = NULL, mc.cores = 2) |
|
1190 |
+ ## summary(s2.g)[, c(1, 2, 3, 8, 9)] |
|
1191 |
+ ## summary(s2.ng)[, c(1, 2, 3, 8, 9)] |
|
1192 |
+ expect_true( wilcox.test(mutsPerClone(s2.g), |
|
1193 |
+ mutsPerClone(s2.ng), |
|
1194 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1195 |
+ expect_true( wilcox.test(summary(s2.g)$NumClones, |
|
1196 |
+ summary(s2.ng)$NumClones, |
|
1197 |
+ alternative = "greater")$p.value < p.value.threshold) |
|
1198 |
+ summary(summary(s2.g)[, 2]) |
|
1199 |
+ summary(summary(s2.ng)[, 2]) |
|
1200 |
+ ## summary(mutsPerClone(s2.g)) |
|
1201 |
+ ## summary(mutsPerClone(s2.ng)) |
|
1202 |
+ ## summary(summary(s2.g)$NumClones) |
|
1203 |
+ ## summary(summary(s2.ng)$NumClones) |
|
1204 |
+gc() |
|
1205 |
+}) |
|
1206 |
+cat("\n", date(), "\n") |
|
1207 |
+ |
|
1208 |
+ |
|
1209 |
+ |
|
1210 |
+ |
|
1211 |
+ |
|
1212 |
+ |
|
1213 |
+ |
|
1214 |
+ |
|
1215 |
+ |
|
1216 |
+ |
|
827 | 1217 |
cat(paste("\n Ending mutPropGrwoth-long at", date(), "\n")) |
828 | 1218 |
|
829 | 1219 |
|
... | ... |
@@ -1214,4 +1214,31 @@ test_that("No epistasis, modules", { |
1214 | 1214 |
(1 + sa) * (1 + sb) * (1 + sc)) |
1215 | 1215 |
}) |
1216 | 1216 |
|
1217 |
+ |
|
1218 |
+test_that("noIntGenes, two common errors: character vector and ,>:", { |
|
1219 |
+ expect_error(allFitnessEffects(noIntGenes = |
|
1220 |
+ c("a1, a2, b1, b2, b3, c1, c2")), |
|
1221 |
+ "noIntGenes is a character vector", fixed = TRUE) |
|
1222 |
+ |
|
1223 |
+ expect_error(allFitnessEffects(noIntGenes = |
|
1224 |
+ c("a1", "a2")), |
|
1225 |
+ "noIntGenes is a character vector", fixed = TRUE) |
|
1226 |
+ u <- 0.3 |
|
1227 |
+ names(u) <- "a,b" |
|
1228 |
+ v <- 0.3 |
|
1229 |
+ names(v) <- "a > b" |
|
1230 |
+ w <- 0.3 |
|
1231 |
+ names(w) <- "a : b" |
|
1232 |
+ |
|
1233 |
+ expect_error(allFitnessEffects(noIntGenes = u), |
|
1234 |
+ "The name of some noIntGenes contain a ',' or a '>' or a ':'", |
|
1235 |
+ fixed = TRUE) |
|
1236 |
+ expect_error(allFitnessEffects(noIntGenes = v), |
|
1237 |
+ "The name of some noIntGenes contain a ',' or a '>' or a ':'", |
|
1238 |
+ fixed = TRUE) |
|
1239 |
+ expect_error(allFitnessEffects(noIntGenes = w), |
|
1240 |
+ "The name of some noIntGenes contain a ',' or a '>' or a ':'", |
|
1241 |
+ fixed = TRUE) |
|
1242 |
+}) |
|
1243 |
+ |
|
1217 | 1244 |
cat(paste("\n Ending all-fitness at", date())) |
1218 | 1245 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,420 @@ |
1 |
+cat(paste("\n Starting driverCounts at", date())) |
|
2 |
+RNGkind("Mersenne-Twister") ## we have some examples below with random |
|
3 |
+ |
|
4 |
+date() |
|
5 |
+test_that("Runs without crashes", { |
|
6 |
+ |
|
7 |
+ iteration <- 1 |
|
8 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
9 |
+ names(ni) <- paste0("g", 2:11) |
|
10 |
+ ## each single one |
|
11 |
+ for(i in 2:11) { |
|
12 |
+ cat("\n doing iteration", iteration, "\n") |
|
13 |
+ ni[] <- runif(10, min = -0.01, max = 0.1) |
|
14 |
+ ni <- sample(ni) |
|
15 |
+ drvN <- paste0("g", i) |
|
16 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
17 |
+ drvNames = drvN) |
|
18 |
+ expect_output(print(oncoSimulPop(20, |
|
19 |
+ fe31, |
|
20 |
+ mu = 1e-6, |
|
21 |
+ initSize = 1e5, |
|
22 |
+ model = "McFL", |
|
23 |
+ detectionSize = 5e6, |
|
24 |
+ finalTime = 5, |
|
25 |
+ keepEvery = 1, |
|
26 |
+ onlyCancer = FALSE, |
|
27 |
+ mc.cores = 2, |
|
28 |
+ sampleEvery = 0.03 |
|
29 |
+ )), |
|
30 |
+ "Population of OncoSimul trajectories", |
|
31 |
+ fixed = TRUE) |
|
32 |
+ iteration <- iteration + 1 |
|
33 |
+ } |
|
34 |
+ ## some pairs, trios, etc, shuffled order; all are run in the long |
|
35 |
+ ## test; this is a paranoid testing set up |
|
36 |
+ ## The ones run here are the most dangerous ones. |
|
37 |
+ require(gtools) |
|
38 |
+ for(n in c(2, 3)) { |
|
39 |
+ m <- gtools::combinations(10, n, 2:11) |
|
40 |
+ for(j in sample(nrow(m), 45)) { ## all for 2, a sample of 45 for 3 |
|
41 |
+ cat("\n doing iteration", iteration, "\n") |
|
42 |
+ ni[] <- runif(10, min = -0.01, max = 0.1) |
|
43 |
+ ni <- sample(ni) |
|
44 |
+ drvN <- paste0("g", sample(m[j, ])) |
|
45 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
46 |
+ drvNames = drvN) |
|
47 |
+ expect_output(print(oncoSimulPop(10, |
|
48 |
+ fe31, |
|
49 |
+ mu = 1e-6, |
|
50 |
+ initSize = 1e5, |
|
51 |
+ model = "McFL", |
|
52 |
+ detectionSize = 5e6, |
|
53 |
+ finalTime = 5, |
|
54 |
+ keepEvery = 1, |
|
55 |
+ onlyCancer = FALSE, |
|
56 |
+ mc.cores = 2, |
|
57 |
+ sampleEvery = 0.03 |
|
58 |
+ )), |
|
59 |
+ "Population of OncoSimul trajectories", |
|
60 |
+ fixed = TRUE) |
|
61 |
+ iteration <- iteration + 1 |
|
62 |
+ } |
|
63 |
+ } |
|
64 |
+ |
|
65 |
+}) |
|
66 |
+date() |
|
67 |
+ |
|
68 |
+date() |
|
69 |
+test_that("driverCounts: we get the right results", { |
|
70 |
+ ## Comparing against know results with something that used to give |
|
71 |
+ ## wrong ones |
|
72 |
+ |
|
73 |
+ ## I also check mue11$Genotypes |
|
74 |
+ ## to know what to expect |
|
75 |
+ |
|
76 |
+ set.seed(1) |
|
77 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
78 |
+ names(ni) <- paste0("g", 2:11) |
|
79 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
80 |
+ drvNames = "g2") |
|
81 |
+ set.seed(1) |
|
82 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
83 |
+ mu = 1e-6, |
|
84 |
+ initSize = 1e5, |
|
85 |
+ model = "McFL", |
|
86 |
+ detectionSize = 5e6, |
|
87 |
+ finalTime = 5, |
|
88 |
+ onlyCancer = FALSE) |
|
89 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
90 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
91 |
+ |
|
92 |
+ set.seed(1) |
|
93 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
94 |
+ names(ni) <- paste0("g", 2:11) |
|
95 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
96 |
+ drvNames = "g3") |
|
97 |
+ set.seed(1) |
|
98 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
99 |
+ mu = 1e-6, |
|
100 |
+ initSize = 1e5, |
|
101 |
+ model = "McFL", |
|
102 |
+ detectionSize = 5e6, |
|
103 |
+ finalTime = 5, |
|
104 |
+ onlyCancer = FALSE) |
|
105 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
106 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
107 |
+ |
|
108 |
+ set.seed(1) |
|
109 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
110 |
+ names(ni) <- paste0("g", 2:11) |
|
111 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
112 |
+ drvNames = "g4") |
|
113 |
+ set.seed(1) |
|
114 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
115 |
+ mu = 1e-6, |
|
116 |
+ initSize = 1e5, |
|
117 |
+ model = "McFL", |
|
118 |
+ detectionSize = 5e6, |
|
119 |
+ finalTime = 5, |
|
120 |
+ onlyCancer = FALSE) |
|
121 |
+ expect_true(mue11$MaxNumDrivers == 0) |
|
122 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
123 |
+ |
|
124 |
+ set.seed(1) |
|
125 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
126 |
+ names(ni) <- paste0("g", 2:11) |
|
127 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
128 |
+ drvNames = "g5") |
|
129 |
+ set.seed(1) |
|
130 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
131 |
+ mu = 1e-6, |
|
132 |
+ initSize = 1e5, |
|
133 |
+ model = "McFL", |
|
134 |
+ detectionSize = 5e6, |
|
135 |
+ finalTime = 5, |
|
136 |
+ onlyCancer = FALSE) |
|
137 |
+ expect_true(mue11$MaxNumDrivers == 0) |
|
138 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
139 |
+ |
|
140 |
+ set.seed(1) |
|
141 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
142 |
+ names(ni) <- paste0("g", 2:11) |
|
143 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
144 |
+ drvNames = "g6") |
|
145 |
+ set.seed(1) |
|
146 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
147 |
+ mu = 1e-6, |
|
148 |
+ initSize = 1e5, |
|
149 |
+ model = "McFL", |
|
150 |
+ detectionSize = 5e6, |
|
151 |
+ finalTime = 5, |
|
152 |
+ onlyCancer = FALSE) |
|
153 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
154 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
155 |
+ |
|
156 |
+ set.seed(1) |
|
157 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
158 |
+ names(ni) <- paste0("g", 2:11) |
|
159 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
160 |
+ drvNames = "g7") |
|
161 |
+ set.seed(1) |
|
162 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
163 |
+ mu = 1e-6, |
|
164 |
+ initSize = 1e5, |
|
165 |
+ model = "McFL", |
|
166 |
+ detectionSize = 5e6, |
|
167 |
+ finalTime = 5, |
|
168 |
+ onlyCancer = FALSE) |
|
169 |
+ expect_true(mue11$MaxNumDrivers == 0) |
|
170 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
171 |
+ |
|
172 |
+ set.seed(1) |
|
173 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
174 |
+ names(ni) <- paste0("g", 2:11) |
|
175 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
176 |
+ drvNames = "g8") |
|
177 |
+ set.seed(1) |
|
178 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
179 |
+ mu = 1e-6, |
|
180 |
+ initSize = 1e5, |
|
181 |
+ model = "McFL", |
|
182 |
+ detectionSize = 5e6, |
|
183 |
+ finalTime = 5, |
|
184 |
+ onlyCancer = FALSE) |
|
185 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
186 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
187 |
+ |
|
188 |
+ set.seed(1) |
|
189 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
190 |
+ names(ni) <- paste0("g", 2:11) |
|
191 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
192 |
+ drvNames = "g9") |
|
193 |
+ set.seed(1) |
|
194 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
195 |
+ mu = 1e-6, |
|
196 |
+ initSize = 1e5, |
|
197 |
+ model = "McFL", |
|
198 |
+ detectionSize = 5e6, |
|
199 |
+ finalTime = 5, |
|
200 |
+ onlyCancer = FALSE) |
|
201 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
202 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
203 |
+ |
|
204 |
+ set.seed(1) |
|
205 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
206 |
+ names(ni) <- paste0("g", 2:11) |
|
207 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
208 |
+ drvNames = "g10") |
|
209 |
+ set.seed(1) |
|
210 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
211 |
+ mu = 1e-6, |
|
212 |
+ initSize = 1e5, |
|
213 |
+ model = "McFL", |
|
214 |
+ detectionSize = 5e6, |
|
215 |
+ finalTime = 5, |
|
216 |
+ onlyCancer = FALSE) |
|
217 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
218 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
219 |
+ |
|
220 |
+ set.seed(1) |
|
221 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
222 |
+ names(ni) <- paste0("g", 2:11) |
|
223 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
224 |
+ drvNames = "g11") |
|
225 |
+ set.seed(1) |
|
226 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
227 |
+ mu = 1e-6, |
|
228 |
+ initSize = 1e5, |
|
229 |
+ model = "McFL", |
|
230 |
+ detectionSize = 5e6, |
|
231 |
+ finalTime = 5, |
|
232 |
+ onlyCancer = FALSE) |
|
233 |
+ expect_true(mue11$MaxNumDrivers == 0) |
|
234 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
235 |
+ |
|
236 |
+ set.seed(1) |
|
237 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
238 |
+ names(ni) <- paste0("g", 2:11) |
|
239 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
240 |
+ drvNames = "g2") |
|
241 |
+ set.seed(1) |
|
242 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
243 |
+ mu = 1e-6, |
|
244 |
+ initSize = 1e5, |
|
245 |
+ model = "McFL", |
|
246 |
+ detectionSize = 5e6, |
|
247 |
+ finalTime = 5, |
|
248 |
+ onlyCancer = FALSE) |
|
249 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
250 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
251 |
+ |
|
252 |
+ set.seed(1) |
|
253 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
254 |
+ names(ni) <- paste0("g", 2:11) |
|
255 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
256 |
+ drvNames = c("g2", "g4")) |
|
257 |
+ set.seed(1) |
|
258 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
259 |
+ mu = 1e-6, |
|
260 |
+ initSize = 1e5, |
|
261 |
+ model = "McFL", |
|
262 |
+ detectionSize = 5e6, |
|
263 |
+ finalTime = 5, |
|
264 |
+ onlyCancer = FALSE) |
|
265 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
266 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
267 |
+ |
|
268 |
+ set.seed(1) |
|
269 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
270 |
+ names(ni) <- paste0("g", 2:11) |
|
271 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
272 |
+ drvNames = c("g4", "g5")) |
|
273 |
+ set.seed(1) |
|
274 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
275 |
+ mu = 1e-6, |
|
276 |
+ initSize = 1e5, |
|
277 |
+ model = "McFL", |
|
278 |
+ detectionSize = 5e6, |
|
279 |
+ finalTime = 5, |
|
280 |
+ onlyCancer = FALSE) |
|
281 |
+ expect_true(mue11$MaxNumDrivers == 0) |
|
282 |
+ expect_true(mue11$MaxDriversLast == 0) |
|
283 |
+ |
|
284 |
+ set.seed(1) |
|
285 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
286 |
+ names(ni) <- paste0("g", 2:11) |
|
287 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
288 |
+ drvNames = c("g3", "g10")) |
|
289 |
+ set.seed(1) |
|
290 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
291 |
+ mu = 1e-6, |
|
292 |
+ initSize = 1e5, |
|
293 |
+ model = "McFL", |
|
294 |
+ detectionSize = 5e6, |
|
295 |
+ finalTime = 5, |
|
296 |
+ onlyCancer = FALSE) |
|
297 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
298 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
299 |
+ |
|
300 |
+ |
|
301 |
+ set.seed(1) |
|
302 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
303 |
+ names(ni) <- paste0("g", 2:11) |
|
304 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
305 |
+ drvNames = c("g5", "g3")) |
|
306 |
+ set.seed(4) |
|
307 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
308 |
+ mu = 1e-6, |
|
309 |
+ initSize = 1e5, |
|
310 |
+ model = "McFL", |
|
311 |
+ detectionSize = 5e6, |
|
312 |
+ finalTime = 90, |
|
313 |
+ onlyCancer = FALSE) |
|
314 |
+ expect_true(mue11$MaxNumDrivers == 2) |
|
315 |
+ expect_true(mue11$MaxDriversLast == 2) |
|
316 |
+ |
|
317 |
+ set.seed(1) |
|
318 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
319 |
+ names(ni) <- paste0("g", 2:11) |
|
320 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
321 |
+ drvNames = c("g6", "g5")) |
|
322 |
+ set.seed(4) |
|
323 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
324 |
+ mu = 1e-6, |
|
325 |
+ initSize = 1e5, |
|
326 |
+ model = "McFL", |
|
327 |
+ detectionSize = 5e6, |
|
328 |
+ finalTime = 90, |
|
329 |
+ onlyCancer = FALSE) |
|
330 |
+ expect_true(mue11$MaxNumDrivers == 2) |
|
331 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
332 |
+ |
|
333 |
+ set.seed(1) |
|
334 |
+ ni <- runif(10, min = -0.01, max = 0.1) |
|
335 |
+ names(ni) <- paste0("g", 2:11) |
|
336 |
+ fe31 <- allFitnessEffects(noIntGenes = ni, |
|
337 |
+ drvNames = c("g6", "g7", "g8", "g9")) |
|
338 |
+ set.seed(4) |
|
339 |
+ mue11 <- oncoSimulIndiv(fe31, |
|
340 |
+ mu = 1e-6, |
|
341 |
+ initSize = 1e5, |
|
342 |
+ model = "McFL", |
|
343 |
+ detectionSize = 5e6, |
|
344 |
+ finalTime = 90, |
|
345 |
+ onlyCancer = FALSE) |
|
346 |
+ expect_true(mue11$MaxNumDrivers == 1) |
|
347 |
+ expect_true(mue11$MaxDriversLast == 1) |
|
348 |
+ |
|
349 |
+ |
|
350 |
+ ## A different fe |
|
351 |
+ set.seed(1) ## for reproducibility |
|
352 |
+ ni <- c(rep(0, 7), runif(10, min = -0.01, max = 0.1)) |
|
353 < |